ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
ctzpad.f
Go to the documentation of this file.
1  SUBROUTINE ctzpad( UPLO, HERM, M, N, IOFFD, ALPHA, BETA, 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 HERM, UPLO
10  INTEGER IOFFD, LDA, M, N
11  COMPLEX ALPHA, BETA
12 * ..
13 * .. Array Arguments ..
14  COMPLEX A( LDA, * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * CTZPAD initializes a two-dimensional array A to beta on the diagonal
21 * specified by IOFFD or zeros the imaginary part of those diagonals and
22 * set the offdiagonals to alpha.
23 *
24 * Arguments
25 * =========
26 *
27 * UPLO (input) CHARACTER*1
28 * On entry, UPLO specifies which trapezoidal part of the ar-
29 * ray A is to be set as follows:
30 * = 'L' or 'l': Lower triangular part is set; the strictly
31 * upper triangular part of A is not changed,
32 * = 'D' or 'd': diagonal specified by IOFFD is set; the
33 * rest of the array A is unchanged,
34 * = 'U' or 'u': Upper triangular part is set; the strictly
35 * lower triangular part of A is not changed,
36 * Otherwise: All of the array A is set.
37 *
38 * HERM (input) CHARACTER*1
39 * On entry, HERM specifies what should be done to the diagonals
40 * as follows. When UPLO is 'L', 'l', 'D', 'd', 'U' or 'u' and
41 * HERM is 'Z' or 'z', the imaginary part of the diagonals is
42 * set to zero. Otherwise, the diagonals are set to beta.
43 *
44 * M (input) INTEGER
45 * On entry, M specifies the number of rows of the array A. M
46 * must be at least zero.
47 *
48 * N (input) INTEGER
49 * On entry, N specifies the number of columns of the array A.
50 * N must be at least zero.
51 *
52 * IOFFD (input) INTEGER
53 * On entry, IOFFD specifies the position of the offdiagonal de-
54 * limiting the upper and lower trapezoidal part of A as follows
55 * (see the notes below):
56 *
57 * IOFFD = 0 specifies the main diagonal A( i, i ),
58 * with i = 1 ... MIN( M, N ),
59 * IOFFD > 0 specifies the subdiagonal A( i+IOFFD, i ),
60 * with i = 1 ... MIN( M-IOFFD, N ),
61 * IOFFD < 0 specifies the superdiagonal A( i, i-IOFFD ),
62 * with i = 1 ... MIN( M, N+IOFFD ).
63 *
64 * ALPHA (input) COMPLEX
65 * On entry, ALPHA specifies the scalar alpha, i.e., the value
66 * to which the offdiagonal entries of the array A determined by
67 * UPLO and IOFFD are set.
68 *
69 * BETA (input) COMPLEX
70 * On entry, BETA specifies the scalar beta, i.e., the value to
71 * which the diagonal entries specified by IOFFD of the array A
72 * are set. BETA is not referenced when UPLO is 'L', 'l', 'U' or
73 * 'u' and HERM is 'Z'.
74 *
75 * A (input/output) COMPLEX array
76 * On entry, A is an array of dimension (LDA,N). Before entry
77 * with UPLO = 'U', the leading m by n part of the array A must
78 * contain the upper trapezoidal part of the matrix to be set as
79 * specified by IOFFD, and the strictly lower trapezoidal part
80 * of A is not referenced; When UPLO = 'L', the leading m by n
81 * part of the array A must contain the lower trapezoidal part
82 * of the matrix to be set as specified by IOFFD, and the
83 * strictly upper trapezoidal part of A is not referenced. On
84 * exit, the entries of the trapezoid part of A determined by
85 * UPLO, HERM and IOFFD are set.
86 *
87 * LDA (input) INTEGER
88 * On entry, LDA specifies the leading dimension of the array A.
89 * LDA must be at least max( 1, M ).
90 *
91 * Notes
92 * =====
93 * N N
94 * ---------------------------- -----------
95 * | d | | |
96 * M | d 'U' | | 'U' |
97 * | 'L' 'D' | |d |
98 * | d | M | d |
99 * ---------------------------- | 'D' |
100 * | d |
101 * IOFFD < 0 | 'L' d |
102 * | d|
103 * N | |
104 * ----------- -----------
105 * | d 'U'|
106 * | d | IOFFD > 0
107 * M | 'D' |
108 * | d| N
109 * | 'L' | ----------------------------
110 * | | | 'U' |
111 * | | |d |
112 * | | | 'D' |
113 * | | | d |
114 * | | |'L' d |
115 * ----------- ----------------------------
116 *
117 * -- Written on April 1, 1998 by
118 * Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
119 *
120 * =====================================================================
121 *
122 * .. Parameters ..
123  REAL RZERO
124  parameter( rzero = 0.0e+0 )
125 * ..
126 * .. Local Scalars ..
127  INTEGER I, J, JTMP, MN
128 * ..
129 * .. External Functions ..
130  LOGICAL LSAME
131  EXTERNAL lsame
132 * ..
133 * .. Intrinsic Functions ..
134  INTRINSIC cmplx, max, min, real
135 * ..
136 * .. Executable Statements ..
137 *
138 * Quick return if possible
139 *
140  IF( m.LE.0 .OR. n.LE.0 )
141  $ RETURN
142 *
143 * Start the operations
144 *
145  IF( lsame( uplo, 'L' ) ) THEN
146 *
147 * Set the diagonal to BETA or zero the imaginary part of the
148 * diagonals and set the strictly lower triangular part of the
149 * array to ALPHA.
150 *
151  mn = max( 0, -ioffd )
152  DO 20 j = 1, min( mn, n )
153  DO 10 i = 1, m
154  a( i, j ) = alpha
155  10 CONTINUE
156  20 CONTINUE
157 *
158  IF( lsame( herm, 'Z' ) ) THEN
159  DO 40 j = mn + 1, min( m - ioffd, n )
160  jtmp = j + ioffd
161  a( jtmp, j ) = cmplx( real( a( jtmp, j ) ), rzero )
162  DO 30 i = jtmp + 1, m
163  a( i, j ) = alpha
164  30 CONTINUE
165  40 CONTINUE
166  ELSE
167  DO 60 j = mn + 1, min( m - ioffd, n )
168  jtmp = j + ioffd
169  a( jtmp, j ) = beta
170  DO 50 i = jtmp + 1, m
171  a( i, j ) = alpha
172  50 CONTINUE
173  60 CONTINUE
174  END IF
175 *
176  ELSE IF( lsame( uplo, 'U' ) ) THEN
177 *
178 * Set the diagonal to BETA or zero the imaginary part of the
179 * diagonals and set the strictly upper triangular part of the
180 * array to ALPHA.
181 *
182  mn = min( m - ioffd, n )
183  IF( lsame( herm, 'Z' ) ) THEN
184  DO 80 j = max( 0, -ioffd ) + 1, mn
185  jtmp = j + ioffd
186  DO 70 i = 1, jtmp - 1
187  a( i, j ) = alpha
188  70 CONTINUE
189  a( jtmp, j ) = cmplx( real( a( jtmp, j ) ), rzero )
190  80 CONTINUE
191  ELSE
192  DO 100 j = max( 0, -ioffd ) + 1, mn
193  jtmp = j + ioffd
194  DO 90 i = 1, jtmp - 1
195  a( i, j ) = alpha
196  90 CONTINUE
197  a( jtmp, j ) = beta
198  100 CONTINUE
199  END IF
200  DO 120 j = max( 0, mn ) + 1, n
201  DO 110 i = 1, m
202  a( i, j ) = alpha
203  110 CONTINUE
204  120 CONTINUE
205 *
206  ELSE IF( lsame( uplo, 'D' ) ) THEN
207 *
208 * Set the diagonal to BETA or zero the imaginary part of the
209 * diagonals.
210 *
211  IF( lsame( herm, 'Z' ) ) THEN
212  IF( ( ioffd.LT.m ).AND.( ioffd.GT.-n ) ) THEN
213  DO 130 j = max( 0, -ioffd ) + 1, min( m - ioffd, n )
214  jtmp = j + ioffd
215  a( jtmp, j ) = cmplx( real( a( jtmp, j ) ), rzero )
216  130 CONTINUE
217  END IF
218  ELSE
219  IF( ( ioffd.LT.m ).AND.( ioffd.GT.-n ) ) THEN
220  DO 140 j = max( 0, -ioffd ) + 1, min( m - ioffd, n )
221  a( j + ioffd, j ) = beta
222  140 CONTINUE
223  END IF
224  END IF
225 *
226  ELSE
227 *
228 * Set the diagonals to BETA and the offdiagonals to ALPHA.
229 *
230  DO 160 j = 1, n
231  DO 150 i = 1, m
232  a( i, j ) = alpha
233  150 CONTINUE
234  160 CONTINUE
235  IF( alpha.NE.beta .AND. ioffd.LT.m .AND. ioffd.GT.-n ) THEN
236  DO 170 j = max( 0, -ioffd ) + 1, min( m - ioffd, n )
237  a( j + ioffd, j ) = beta
238  170 CONTINUE
239  END IF
240 *
241  END IF
242 *
243  RETURN
244 *
245 * End of CTZPAD
246 *
247  END
cmplx
float cmplx[2]
Definition: pblas.h:132
max
#define max(A, B)
Definition: pcgemr.c:180
ctzpad
subroutine ctzpad(UPLO, HERM, M, N, IOFFD, ALPHA, BETA, A, LDA)
Definition: ctzpad.f:2
min
#define min(A, B)
Definition: pcgemr.c:181