ScaLAPACK 2.1
2.1
ScaLAPACK: Scalable Linear Algebra PACKage
dtzpad.f
Go to the documentation of this file.
1
SUBROUTINE
dtzpad
( 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
DOUBLE PRECISION
ALPHA, BETA
12
* ..
13
* .. Array Arguments ..
14
DOUBLE PRECISION
A( LDA, * )
15
* ..
16
*
17
* Purpose
18
* =======
19
*
20
* DTZPAD 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) DOUBLE PRECISION
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) DOUBLE PRECISION
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) DOUBLE PRECISION 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
* .. Local Scalars ..
123
INTEGER
I, J, JTMP, MN
124
* ..
125
* .. External Functions ..
126
LOGICAL
LSAME
127
EXTERNAL
lsame
128
* ..
129
* .. Intrinsic Functions ..
130
INTRINSIC
max
,
min
131
* ..
132
* .. Executable Statements ..
133
*
134
* Quick return if possible
135
*
136
IF
( m.LE.0 .OR. n.LE.0 )
137
$
RETURN
138
*
139
* Start the operations
140
*
141
IF
( lsame( uplo,
'L'
) )
THEN
142
*
143
* Set the diagonal to BETA or zero the imaginary part of the
144
* diagonals and set the strictly lower triangular part of the
145
* array to ALPHA.
146
*
147
mn =
max
( 0, -ioffd )
148
DO
20 j = 1,
min
( mn, n )
149
DO
10 i = 1, m
150
a( i, j ) = alpha
151
10
CONTINUE
152
20
CONTINUE
153
*
154
IF
( lsame( herm,
'Z'
) )
THEN
155
DO
40 j = mn + 1,
min
( m - ioffd, n )
156
jtmp = j + ioffd
157
DO
30 i = jtmp + 1, m
158
a( i, j ) = alpha
159
30
CONTINUE
160
40
CONTINUE
161
ELSE
162
DO
60 j = mn + 1,
min
( m - ioffd, n )
163
jtmp = j + ioffd
164
a( jtmp, j ) = beta
165
DO
50 i = jtmp + 1, m
166
a( i, j ) = alpha
167
50
CONTINUE
168
60
CONTINUE
169
END IF
170
*
171
ELSE
IF
( lsame( uplo,
'U'
) )
THEN
172
*
173
* Set the diagonal to BETA or zero the imaginary part of the
174
* diagonals and set the strictly upper triangular part of the
175
* array to ALPHA.
176
*
177
mn =
min
( m - ioffd, n )
178
IF
( lsame( herm,
'Z'
) )
THEN
179
DO
80 j =
max
( 0, -ioffd ) + 1, mn
180
jtmp = j + ioffd
181
DO
70 i = 1, jtmp - 1
182
a( i, j ) = alpha
183
70
CONTINUE
184
80
CONTINUE
185
ELSE
186
DO
100 j =
max
( 0, -ioffd ) + 1, mn
187
jtmp = j + ioffd
188
DO
90 i = 1, jtmp - 1
189
a( i, j ) = alpha
190
90
CONTINUE
191
a( jtmp, j ) = beta
192
100
CONTINUE
193
END IF
194
DO
120 j =
max
( 0, mn ) + 1, n
195
DO
110 i = 1, m
196
a( i, j ) = alpha
197
110
CONTINUE
198
120
CONTINUE
199
*
200
ELSE
IF
( lsame( uplo,
'D'
) )
THEN
201
*
202
* Set the diagonal to BETA
203
*
204
IF
( .NOT.( lsame( herm,
'Z'
) ) )
THEN
205
IF
( ( ioffd.LT.m ).AND.( ioffd.GT.-n ) )
THEN
206
DO
130 j =
max
( 0, -ioffd ) + 1,
min
( m - ioffd, n )
207
a( j + ioffd, j ) = beta
208
130
CONTINUE
209
END IF
210
END IF
211
*
212
ELSE
213
*
214
* Set the diagonals to BETA and the offdiagonals to ALPHA.
215
*
216
DO
150 j = 1, n
217
DO
140 i = 1, m
218
a( i, j ) = alpha
219
140
CONTINUE
220
150
CONTINUE
221
IF
( alpha.NE.beta .AND. ioffd.LT.m .AND. ioffd.GT.-n )
THEN
222
DO
160 j =
max
( 0, -ioffd ) + 1,
min
( m - ioffd, n )
223
a( j + ioffd, j ) = beta
224
160
CONTINUE
225
END IF
226
*
227
END IF
228
*
229
RETURN
230
*
231
* End of DTZPAD
232
*
233
END
max
#define max(A, B)
Definition:
pcgemr.c:180
dtzpad
subroutine dtzpad(UPLO, HERM, M, N, IOFFD, ALPHA, BETA, A, LDA)
Definition:
dtzpad.f:2
min
#define min(A, B)
Definition:
pcgemr.c:181
PBLAS
SRC
PTZBLAS
dtzpad.f
Generated by
1.8.16