SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ztzscal.f
Go to the documentation of this file.
1 SUBROUTINE ztzscal( UPLO, M, N, IOFFD, ALPHA, A, LDA )
2*
3* -- PBLAS auxiliary routine (version 2.0) --
4* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5* and University of California, Berkeley.
6* April 1, 1998
7*
8* .. Scalar Arguments ..
9 CHARACTER*1 UPLO
10 INTEGER IOFFD, LDA, M, N
11 COMPLEX*16 ALPHA
12* ..
13* .. Array Arguments ..
14 COMPLEX*16 A( LDA, * )
15* ..
16*
17* Purpose
18* =======
19*
20* ZTZSCAL scales a two-dimensional array A by the scalar alpha.
21*
22* Arguments
23* =========
24*
25* UPLO (input) CHARACTER*1
26* On entry, UPLO specifies which trapezoidal part of the ar-
27* ray A is to be scaled as follows:
28* = 'L' or 'l': the lower trapezoid of A is scaled,
29* = 'U' or 'u': the upper trapezoid of A is scaled,
30* = 'D' or 'd': diagonal specified by IOFFD is scaled,
31* Otherwise: all of the array A is scaled.
32*
33* M (input) INTEGER
34* On entry, M specifies the number of rows of the array A. M
35* must be at least zero.
36*
37* N (input) INTEGER
38* On entry, N specifies the number of columns of the array A.
39* N must be at least zero.
40*
41* IOFFD (input) INTEGER
42* On entry, IOFFD specifies the position of the offdiagonal de-
43* limiting the upper and lower trapezoidal part of A as follows
44* (see the notes below):
45*
46* IOFFD = 0 specifies the main diagonal A( i, i ),
47* with i = 1 ... MIN( M, N ),
48* IOFFD > 0 specifies the subdiagonal A( i+IOFFD, i ),
49* with i = 1 ... MIN( M-IOFFD, N ),
50* IOFFD < 0 specifies the superdiagonal A( i, i-IOFFD ),
51* with i = 1 ... MIN( M, N+IOFFD ).
52*
53* ALPHA (input) COMPLEX*16
54* On entry, ALPHA specifies the scalar alpha, i.e., the value
55* by which the diagonal and offdiagonal entries of the array A
56* as specified by UPLO and IOFFD are scaled.
57*
58* A (input/output) COMPLEX*16 array
59* On entry, A is an array of dimension (LDA,N). Before entry
60* with UPLO = 'U' or 'u', the leading m by n part of the array
61* A must contain the upper trapezoidal part of the matrix as
62* specified by IOFFD to be scaled, and the strictly lower tra-
63* pezoidal part of A is not referenced; When UPLO = 'L' or 'l',
64* the leading m by n part of the array A must contain the lower
65* trapezoidal part of the matrix as specified by IOFFD to be
66* scaled, and the strictly upper trapezoidal part of A is not
67* referenced. On exit, the entries of the trapezoid part of A
68* determined by UPLO and IOFFD are scaled.
69*
70* LDA (input) INTEGER
71* On entry, LDA specifies the leading dimension of the array A.
72* LDA must be at least max( 1, M ).
73*
74* Notes
75* =====
76* N N
77* ---------------------------- -----------
78* | d | | |
79* M | d 'U' | | 'U' |
80* | 'L' 'D' | |d |
81* | d | M | d |
82* ---------------------------- | 'D' |
83* | d |
84* IOFFD < 0 | 'L' d |
85* | d|
86* N | |
87* ----------- -----------
88* | d 'U'|
89* | d | IOFFD > 0
90* M | 'D' |
91* | d| N
92* | 'L' | ----------------------------
93* | | | 'U' |
94* | | |d |
95* | | | 'D' |
96* | | | d |
97* | | |'L' d |
98* ----------- ----------------------------
99*
100* -- Written on April 1, 1998 by
101* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
102*
103* =====================================================================
104*
105* .. Parameters ..
106 COMPLEX*16 ONE, ZERO
107 parameter( one = ( 1.0d+0, 0.0d+0 ),
108 $ zero = ( 0.0d+0, 0.0d+0 ) )
109* ..
110* .. Local Scalars ..
111 INTEGER J, JTMP, MN
112* ..
113* .. External Subroutines ..
114 EXTERNAL zscal, ztzpad
115* ..
116* .. External Functions ..
117 LOGICAL LSAME
118 EXTERNAL lsame
119* ..
120* .. Intrinsic Functions ..
121 INTRINSIC max, min
122* ..
123* .. Executable Statements ..
124*
125* Quick return if possible
126*
127 IF( ( m.LE.0 ).OR.( n.LE.0 ).OR.( alpha.EQ.one ) )
128 $ RETURN
129*
130* Start the operations
131*
132 IF( alpha.EQ.zero ) THEN
133 CALL ztzpad( uplo, 'N', m, n, ioffd, zero, zero, a, lda )
134 RETURN
135 END IF
136*
137 IF( lsame( uplo, 'L' ) ) THEN
138*
139* Scales the lower triangular part of the array by ALPHA.
140*
141 mn = max( 0, -ioffd )
142 DO 10 j = 1, min( mn, n )
143 CALL zscal( m, alpha, a( 1, j ), 1 )
144 10 CONTINUE
145 DO 20 j = mn + 1, min( m - ioffd, n )
146 jtmp = j + ioffd
147 IF( m.GE.jtmp )
148 $ CALL zscal( m-jtmp+1, alpha, a( jtmp, j ), 1 )
149 20 CONTINUE
150*
151 ELSE IF( lsame( uplo, 'U' ) ) THEN
152*
153* Scales the upper triangular part of the array by ALPHA.
154*
155 mn = min( m - ioffd, n )
156 DO 30 j = max( 0, -ioffd ) + 1, mn
157 CALL zscal( j + ioffd, alpha, a( 1, j ), 1 )
158 30 CONTINUE
159 DO 40 j = max( 0, mn ) + 1, n
160 CALL zscal( m, alpha, a( 1, j ), 1 )
161 40 CONTINUE
162*
163 ELSE IF( lsame( uplo, 'D' ) ) THEN
164*
165* Scales the diagonal entries by ALPHA.
166*
167 DO 50 j = max( 0, -ioffd ) + 1, min( m - ioffd, n )
168 jtmp = j + ioffd
169 a( jtmp, j ) = alpha * a( jtmp, j )
170 50 CONTINUE
171*
172 ELSE
173*
174* Scales the entire array by ALPHA.
175*
176 DO 60 j = 1, n
177 CALL zscal( m, alpha, a( 1, j ), 1 )
178 60 CONTINUE
179*
180 END IF
181*
182 RETURN
183*
184* End of ZTZSCAL
185*
186 END
#define max(A, B)
Definition pcgemr.c:180
#define min(A, B)
Definition pcgemr.c:181
subroutine ztzpad(uplo, herm, m, n, ioffd, alpha, beta, a, lda)
Definition ztzpad.f:2
subroutine ztzscal(uplo, m, n, ioffd, alpha, a, lda)
Definition ztzscal.f:2