1 SUBROUTINE ZHEMM
( SIDE
, UPLO
, M
, N
, ALPHA
, A
, LDA
, B
, LDB
,
3 * .. Scalar Arguments
..
5 INTEGER M
, N
, LDA
, LDB
, LDC
7 * .. Array Arguments
..
8 COMPLEX*16 A
( LDA
, * ), B
( LDB
, * ), C
( LDC
, * )
14 * ZHEMM performs one of the matrix
-matrix operations
16 * C
:= alpha*A*B
+ beta*C
,
20 * C
:= alpha*B*A
+ beta*C
,
22 * where alpha and beta are scalars
, A is an hermitian matrix and B and
23 * C are m by n matrices
.
29 * On entry
, SIDE specifies whether the hermitian matrix A
30 * appears on the left or right in the operation as follows
:
32 * SIDE
= 'L' or
'l' C
:= alpha*A*B
+ beta*C
,
34 * SIDE
= 'R' or
'r' C
:= alpha*B*A
+ beta*C
,
39 * On entry
, UPLO specifies whether the upper or lower
40 * triangular part of the hermitian matrix A is
to be
41 * referenced as follows
:
43 * UPLO
= 'U' or
'u' Only the upper triangular part of the
44 * hermitian matrix is
to be referenced
.
46 * UPLO
= 'L' or
'l' Only the lower triangular part of the
47 * hermitian matrix is
to be referenced
.
52 * On entry
, M specifies the number of rows of the matrix C
.
53 * M must be at least zero
.
57 * On entry
, N specifies the number of columns of the matrix C
.
58 * N must be at least zero
.
61 * ALPHA
- COMPLEX*16
.
62 * On entry
, ALPHA specifies the scalar alpha
.
65 * A
- COMPLEX*16 array of
DIMENSION ( LDA
, ka
), where ka is
66 * m when SIDE
= 'L' or
'l' and is n otherwise
.
67 * Before entry with SIDE
= 'L' or
'l', the m by m part of
68 * the array A must contain the hermitian matrix
, such that
69 * when UPLO
= 'U' or
'u', the leading m by m upper triangular
70 * part of the array A must contain the upper triangular part
71 * of the hermitian matrix and the strictly lower triangular
72 * part of A is not referenced
, and when UPLO
= 'L' or
'l',
73 * the leading m by m lower triangular part of the array A
74 * must contain the lower triangular part of the hermitian
75 * matrix and the strictly upper triangular part of A is not
77 * Before entry with SIDE
= 'R' or
'r', the n by n part of
78 * the array A must contain the hermitian matrix
, such that
79 * when UPLO
= 'U' or
'u', the leading n by n upper triangular
80 * part of the array A must contain the upper triangular part
81 * of the hermitian matrix and the strictly lower triangular
82 * part of A is not referenced
, and when UPLO
= 'L' or
'l',
83 * the leading n by n lower triangular part of the array A
84 * must contain the lower triangular part of the hermitian
85 * matrix and the strictly upper triangular part of A is not
87 * Note that the imaginary parts of the diagonal elements need
88 * not be set
, they are assumed
to be zero
.
92 * On entry
, LDA specifies the first
dimension of A as declared
93 * in the calling
(sub
) program. When SIDE
= 'L' or
'l' then
94 * LDA must be at least max
( 1, m
), otherwise LDA must be at
98 * B
- COMPLEX*16 array of
DIMENSION ( LDB
, n
).
99 * Before entry
, the leading m by n part of the array B must
100 * contain the matrix B
.
104 * On entry
, LDB specifies the first
dimension of B as declared
105 * in the calling
(sub
) program. LDB must be at least
109 * BETA
- COMPLEX*16
.
110 * On entry
, BETA specifies the scalar beta
. When BETA is
111 * supplied as zero
then C need not be set on input
.
114 * C
- COMPLEX*16 array of
DIMENSION ( LDC
, n
).
115 * Before entry
, the leading m by n part of the array C must
116 * contain the matrix C
, except when beta is zero
, in which
117 * case C need not be set on entry
.
118 * On exit
, the array C is overwritten by the m by n updated
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
.
130 * -- Written on
8-February
-1989.
131 * Jack Dongarra
, Argonne National Laboratory
.
132 * Iain Duff
, AERE Harwell
.
133 * Jeremy Du Croz
, Numerical Algorithms Group Ltd
.
134 * Sven Hammarling
, Numerical Algorithms Group Ltd
.
137 * .. External Functions
..
140 * .. External Subroutines
..
142 * .. Intrinsic Functions
..
143 INTRINSIC DCONJG
, MAX
, DBLE
144 * .. Local Scalars
..
146 INTEGER I
, INFO
, J
, K
, NROWA
147 COMPLEX*16 TEMP1
, TEMP2
150 PARAMETER ( ONE
= ( 1.0D
+0, 0.0D
+0 ) )
152 PARAMETER ( ZERO
= ( 0.0D
+0, 0.0D
+0 ) )
154 * .. Executable Statements
..
156 * Set NROWA as the number of rows of A
.
158 IF( LSAME
( SIDE
, 'L' ) )THEN
163 UPPER
= LSAME
( UPLO
, 'U' )
165 * Test the input parameters
.
168 IF( ( .NOT
.LSAME
( SIDE
, 'L' ) ).AND
.
169 $
( .NOT
.LSAME
( SIDE
, 'R' ) ) )THEN
171 ELSE IF( ( .NOT
.UPPER
).AND
.
172 $
( .NOT
.LSAME
( UPLO
, 'L' ) ) )THEN
174 ELSE IF( M
.LT
.0 )THEN
176 ELSE IF( N
.LT
.0 )THEN
178 ELSE IF( LDA
.LT
.MAX
( 1, NROWA
) )THEN
180 ELSE IF( LDB
.LT
.MAX
( 1, M
) )THEN
182 ELSE IF( LDC
.LT
.MAX
( 1, M
) )THEN
186 CALL XERBLA
( 'ZHEMM ', INFO
)
190 * Quick
return if possible
.
192 IF( ( M
.EQ
.0 ).OR
.( N
.EQ
.0 ).OR
.
193 $
( ( ALPHA
.EQ
.ZERO
).AND
.( BETA
.EQ
.ONE
) ) )
196 * And when alpha
.eq
.zero
.
198 IF( ALPHA
.EQ
.ZERO
)THEN
199 IF( BETA
.EQ
.ZERO
)THEN
208 C
( I
, J
) = BETA*C
( I
, J
)
215 * Start the operations
.
217 IF( LSAME
( SIDE
, 'L' ) )THEN
219 * Form C
:= alpha*A*B
+ beta*C
.
224 TEMP1
= ALPHA*B
( I
, J
)
227 C
( K
, J
) = C
( K
, J
) + TEMP1*A
( K
, I
)
229 $ B
( K
, J
)*DCONJG
( A
( K
, I
) )
231 IF( BETA
.EQ
.ZERO
)THEN
232 C
( I
, J
) = TEMP1*DBLE
( A
( I
, I
) ) +
235 C
( I
, J
) = BETA
*C
( I
, J
) +
236 $ TEMP1*DBLE
( A
( I
, I
) ) +
244 TEMP1
= ALPHA*B
( I
, J
)
247 C
( K
, J
) = C
( K
, J
) + TEMP1*A
( K
, I
)
249 $ B
( K
, J
)*DCONJG
( A
( K
, I
) )
251 IF( BETA
.EQ
.ZERO
)THEN
252 C
( I
, J
) = TEMP1*DBLE
( A
( I
, I
) ) +
255 C
( I
, J
) = BETA
*C
( I
, J
) +
256 $ TEMP1*DBLE
( A
( I
, I
) ) +
264 * Form C
:= alpha*B*A
+ beta*C
.
267 TEMP1
= ALPHA*DBLE
( A
( J
, J
) )
268 IF( BETA
.EQ
.ZERO
)THEN
270 C
( I
, J
) = TEMP1*B
( I
, J
)
274 C
( I
, J
) = BETA*C
( I
, J
) + TEMP1*B
( I
, J
)
279 TEMP1
= ALPHA*A
( K
, J
)
281 TEMP1
= ALPHA*DCONJG
( A
( J
, K
) )
284 C
( I
, J
) = C
( I
, J
) + TEMP1*B
( I
, K
)
289 TEMP1
= ALPHA*DCONJG
( A
( J
, K
) )
291 TEMP1
= ALPHA*A
( K
, J
)
294 C
( I
, J
) = C
( I
, J
) + TEMP1*B
( I
, K
)