ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
stzscal.f
Go to the documentation of this file.
1  SUBROUTINE stzscal( 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  REAL ALPHA
12 * ..
13 * .. Array Arguments ..
14  REAL A( LDA, * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * STZSCAL 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) REAL
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) REAL 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  REAL ONE, ZERO
107  parameter( one = 1.0e+0, zero = 0.0e+0 )
108 * ..
109 * .. Local Scalars ..
110  INTEGER J, JTMP, MN
111 * ..
112 * .. External Subroutines ..
113  EXTERNAL sscal, stzpad
114 * ..
115 * .. External Functions ..
116  LOGICAL LSAME
117  EXTERNAL lsame
118 * ..
119 * .. Intrinsic Functions ..
120  INTRINSIC max, min
121 * ..
122 * .. Executable Statements ..
123 *
124 * Quick return if possible
125 *
126  IF( ( m.LE.0 ).OR.( n.LE.0 ).OR.( alpha.EQ.one ) )
127  $ RETURN
128 *
129 * Start the operations
130 *
131  IF( alpha.EQ.zero ) THEN
132  CALL stzpad( uplo, 'N', m, n, ioffd, zero, zero, a, lda )
133  RETURN
134  END IF
135 *
136  IF( lsame( uplo, 'L' ) ) THEN
137 *
138 * Scales the lower triangular part of the array by ALPHA.
139 *
140  mn = max( 0, -ioffd )
141  DO 10 j = 1, min( mn, n )
142  CALL sscal( m, alpha, a( 1, j ), 1 )
143  10 CONTINUE
144  DO 20 j = mn + 1, min( m - ioffd, n )
145  jtmp = j + ioffd
146  IF( m.GE.jtmp )
147  $ CALL sscal( m-jtmp+1, alpha, a( jtmp, j ), 1 )
148  20 CONTINUE
149 *
150  ELSE IF( lsame( uplo, 'U' ) ) THEN
151 *
152 * Scales the upper triangular part of the array by ALPHA.
153 *
154  mn = min( m - ioffd, n )
155  DO 30 j = max( 0, -ioffd ) + 1, mn
156  CALL sscal( j + ioffd, alpha, a( 1, j ), 1 )
157  30 CONTINUE
158  DO 40 j = max( 0, mn ) + 1, n
159  CALL sscal( m, alpha, a( 1, j ), 1 )
160  40 CONTINUE
161 *
162  ELSE IF( lsame( uplo, 'D' ) ) THEN
163 *
164 * Scales the diagonal entries by ALPHA.
165 *
166  DO 50 j = max( 0, -ioffd ) + 1, min( m - ioffd, n )
167  jtmp = j + ioffd
168  a( jtmp, j ) = alpha * a( jtmp, j )
169  50 CONTINUE
170 *
171  ELSE
172 *
173 * Scales the entire array by ALPHA.
174 *
175  DO 60 j = 1, n
176  CALL sscal( m, alpha, a( 1, j ), 1 )
177  60 CONTINUE
178 *
179  END IF
180 *
181  RETURN
182 *
183 * End of STZSCAL
184 *
185  END
max
#define max(A, B)
Definition: pcgemr.c:180
stzpad
subroutine stzpad(UPLO, HERM, M, N, IOFFD, ALPHA, BETA, A, LDA)
Definition: stzpad.f:2
stzscal
subroutine stzscal(UPLO, M, N, IOFFD, ALPHA, A, LDA)
Definition: stzscal.f:2
min
#define min(A, B)
Definition: pcgemr.c:181