1 SUBROUTINE DSYR2K
( UPLO
, TRANS
, N
, K
, ALPHA
, A
, LDA
, B
, LDB
,
3 * .. Scalar Arguments
..
4 CHARACTER*1 UPLO
, TRANS
5 INTEGER N
, K
, LDA
, LDB
, LDC
6 DOUBLE PRECISION ALPHA
, BETA
7 * .. Array Arguments
..
8 DOUBLE PRECISION A
( LDA
, * ), B
( LDB
, * ), C
( LDC
, * )
14 * DSYR2K performs one of the symmetric rank
2k operations
16 * C
:= alpha*A*B
' + alpha*B*A' + beta*C
,
20 * C
:= alpha*A
'*B + alpha*B'*A
+ beta*C
,
22 * where alpha and beta are scalars
, C is an n by n symmetric matrix
23 * and A and B are n by k matrices in the first case and k by n
24 * matrices in the second case
.
30 * On entry
, UPLO specifies whether the upper or lower
31 * triangular part of the array C is
to be referenced as
34 * UPLO
= 'U' or
'u' Only the upper triangular part of C
35 * is
to be referenced
.
37 * UPLO
= 'L' or
'l' Only the lower triangular part of C
38 * is
to be referenced
.
42 * TRANS
- CHARACTER*1
.
43 * On entry
, TRANS specifies the operation
to be performed as
46 * TRANS
= 'N' or
'n' C
:= alpha*A*B
' + alpha*B*A' +
49 * TRANS
= 'T' or
't' C
:= alpha*A
'*B + alpha*B'*A
+
52 * TRANS
= 'C' or
'c' C
:= alpha*A
'*B + alpha*B'*A
+
58 * On entry
, N specifies the order of the matrix C
. N must be
63 * On entry with TRANS
= 'N' or
'n', K specifies the number
64 * of columns of the matrices A and B
, and on entry with
65 * TRANS
= 'T' or
't' or
'C' or
'c', K specifies the number
66 * of rows of the matrices A and B
. K must be at least zero
.
69 * ALPHA
- DOUBLE PRECISION.
70 * On entry
, ALPHA specifies the scalar alpha
.
73 * A
- DOUBLE PRECISION array of
DIMENSION ( LDA
, ka
), where ka is
74 * k when TRANS
= 'N' or
'n', and is n otherwise
.
75 * Before entry with TRANS
= 'N' or
'n', the leading n by k
76 * part of the array A must contain the matrix A
, otherwise
77 * the leading k by n part of the array A must contain the
82 * On entry
, LDA specifies the first
dimension of A as declared
83 * in the calling
(sub
) program. When TRANS
= 'N' or
'n'
84 * then LDA must be at least max
( 1, n
), otherwise LDA must
85 * be at least max
( 1, k
).
88 * B
- DOUBLE PRECISION array of
DIMENSION ( LDB
, kb
), where kb is
89 * k when TRANS
= 'N' or
'n', and is n otherwise
.
90 * Before entry with TRANS
= 'N' or
'n', the leading n by k
91 * part of the array B must contain the matrix B
, otherwise
92 * the leading k by n part of the array B must contain the
97 * On entry
, LDB specifies the first
dimension of B as declared
98 * in the calling
(sub
) program. When TRANS
= 'N' or
'n'
99 * then LDB must be at least max
( 1, n
), otherwise LDB must
100 * be at least max
( 1, k
).
103 * BETA
- DOUBLE PRECISION.
104 * On entry
, BETA specifies the scalar beta
.
107 * C
- DOUBLE PRECISION array of
DIMENSION ( LDC
, n
).
108 * Before entry with UPLO
= 'U' or
'u', the leading n by n
109 * upper triangular part of the array C must contain the upper
110 * triangular part of the symmetric matrix and the strictly
111 * lower triangular part of C is not referenced
. On exit
, the
112 * upper triangular part of the array C is overwritten by the
113 * upper triangular part of the updated matrix
.
114 * Before entry with UPLO
= 'L' or
'l', the leading n by n
115 * lower triangular part of the array C must contain the lower
116 * triangular part of the symmetric matrix and the strictly
117 * upper triangular part of C is not referenced
. On exit
, the
118 * lower triangular part of the array C is overwritten by the
119 * lower triangular part of the updated matrix
.
122 * On entry
, LDC specifies the first
dimension of C as declared
123 * in the calling
(sub
) program. LDC must be at least
128 * Level
3 Blas routine
.
131 * -- Written on
8-February
-1989.
132 * Jack Dongarra
, Argonne National Laboratory
.
133 * Iain Duff
, AERE Harwell
.
134 * Jeremy Du Croz
, Numerical Algorithms Group Ltd
.
135 * Sven Hammarling
, Numerical Algorithms Group Ltd
.
138 * .. External Functions
..
141 * .. External Subroutines
..
143 * .. Intrinsic Functions
..
145 * .. Local Scalars
..
147 INTEGER I
, INFO
, J
, L
, NROWA
148 DOUBLE PRECISION TEMP1
, TEMP2
150 DOUBLE PRECISION ONE
, ZERO
151 PARAMETER ( ONE
= 1.0D
+0, ZERO
= 0.0D
+0 )
153 * .. Executable Statements
..
155 * Test the input parameters
.
157 IF( LSAME
( TRANS
, 'N' ) )THEN
162 UPPER
= LSAME
( UPLO
, 'U' )
165 IF( ( .NOT
.UPPER
).AND
.
166 $
( .NOT
.LSAME
( UPLO
, 'L' ) ) )THEN
168 ELSE IF( ( .NOT
.LSAME
( TRANS
, 'N' ) ).AND
.
169 $
( .NOT
.LSAME
( TRANS
, 'T' ) ).AND
.
170 $
( .NOT
.LSAME
( TRANS
, 'C' ) ) )THEN
172 ELSE IF( N
.LT
.0 )THEN
174 ELSE IF( K
.LT
.0 )THEN
176 ELSE IF( LDA
.LT
.MAX
( 1, NROWA
) )THEN
178 ELSE IF( LDB
.LT
.MAX
( 1, NROWA
) )THEN
180 ELSE IF( LDC
.LT
.MAX
( 1, N
) )THEN
184 CALL XERBLA
( 'DSYR2K', INFO
)
188 * Quick
return if possible
.
191 $
( ( ( ALPHA
.EQ
.ZERO
).OR
.( K
.EQ
.0 ) ).AND
.( BETA
.EQ
.ONE
) ) )
194 * And when alpha
.eq
.zero
.
196 IF( ALPHA
.EQ
.ZERO
)THEN
198 IF( BETA
.EQ
.ZERO
)THEN
207 C
( I
, J
) = BETA*C
( I
, J
)
212 IF( BETA
.EQ
.ZERO
)THEN
221 C
( I
, J
) = BETA*C
( I
, J
)
229 * Start the operations
.
231 IF( LSAME
( TRANS
, 'N' ) )THEN
233 * Form C
:= alpha*A*B
' + alpha*B*A' + C
.
237 IF( BETA
.EQ
.ZERO
)THEN
241 ELSE IF( BETA
.NE
.ONE
)THEN
243 C
( I
, J
) = BETA*C
( I
, J
)
247 IF( ( A
( J
, L
).NE
.ZERO
).OR
.
248 $
( B
( J
, L
).NE
.ZERO
) )THEN
249 TEMP1
= ALPHA*B
( J
, L
)
250 TEMP2
= ALPHA*A
( J
, L
)
252 C
( I
, J
) = C
( I
, J
) +
253 $ A
( I
, L
)*TEMP1
+ B
( I
, L
)*TEMP2
260 IF( BETA
.EQ
.ZERO
)THEN
264 ELSE IF( BETA
.NE
.ONE
)THEN
266 C
( I
, J
) = BETA*C
( I
, J
)
270 IF( ( A
( J
, L
).NE
.ZERO
).OR
.
271 $
( B
( J
, L
).NE
.ZERO
) )THEN
272 TEMP1
= ALPHA*B
( J
, L
)
273 TEMP2
= ALPHA*A
( J
, L
)
275 C
( I
, J
) = C
( I
, J
) +
276 $ A
( I
, L
)*TEMP1
+ B
( I
, L
)*TEMP2
284 * Form C
:= alpha*A
'*B + alpha*B'*A
+ C
.
292 TEMP1
= TEMP1
+ A
( L
, I
)*B
( L
, J
)
293 TEMP2
= TEMP2
+ B
( L
, I
)*A
( L
, J
)
295 IF( BETA
.EQ
.ZERO
)THEN
296 C
( I
, J
) = ALPHA*TEMP1
+ ALPHA*TEMP2
298 C
( I
, J
) = BETA
*C
( I
, J
) +
299 $ ALPHA*TEMP1
+ ALPHA*TEMP2
309 TEMP1
= TEMP1
+ A
( L
, I
)*B
( L
, J
)
310 TEMP2
= TEMP2
+ B
( L
, I
)*A
( L
, J
)
312 IF( BETA
.EQ
.ZERO
)THEN
313 C
( I
, J
) = ALPHA*TEMP1
+ ALPHA*TEMP2
315 C
( I
, J
) = BETA
*C
( I
, J
) +
316 $ ALPHA*TEMP1
+ ALPHA*TEMP2