File:
[local] /
rpl /
lapack /
blas /
zhemm.f
Revision
1.10:
download - view:
text,
annotated -
select for diffs -
revision graph
Mon Jan 27 09:28:14 2014 UTC (11 years, 3 months ago) by
bertrand
Branches:
MAIN
CVS tags:
rpl-4_1_24,
rpl-4_1_23,
rpl-4_1_22,
rpl-4_1_21,
rpl-4_1_20,
rpl-4_1_19,
rpl-4_1_18,
rpl-4_1_17,
HEAD
Cohérence.
1: *> \brief \b ZHEMM
2: *
3: * =========== DOCUMENTATION ===========
4: *
5: * Online html documentation available at
6: * http://www.netlib.org/lapack/explore-html/
7: *
8: * Definition:
9: * ===========
10: *
11: * SUBROUTINE ZHEMM(SIDE,UPLO,M,N,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
12: *
13: * .. Scalar Arguments ..
14: * COMPLEX*16 ALPHA,BETA
15: * INTEGER LDA,LDB,LDC,M,N
16: * CHARACTER SIDE,UPLO
17: * ..
18: * .. Array Arguments ..
19: * COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)
20: * ..
21: *
22: *
23: *> \par Purpose:
24: * =============
25: *>
26: *> \verbatim
27: *>
28: *> ZHEMM performs one of the matrix-matrix operations
29: *>
30: *> C := alpha*A*B + beta*C,
31: *>
32: *> or
33: *>
34: *> C := alpha*B*A + beta*C,
35: *>
36: *> where alpha and beta are scalars, A is an hermitian matrix and B and
37: *> C are m by n matrices.
38: *> \endverbatim
39: *
40: * Arguments:
41: * ==========
42: *
43: *> \param[in] SIDE
44: *> \verbatim
45: *> SIDE is CHARACTER*1
46: *> On entry, SIDE specifies whether the hermitian matrix A
47: *> appears on the left or right in the operation as follows:
48: *>
49: *> SIDE = 'L' or 'l' C := alpha*A*B + beta*C,
50: *>
51: *> SIDE = 'R' or 'r' C := alpha*B*A + beta*C,
52: *> \endverbatim
53: *>
54: *> \param[in] UPLO
55: *> \verbatim
56: *> UPLO is CHARACTER*1
57: *> On entry, UPLO specifies whether the upper or lower
58: *> triangular part of the hermitian matrix A is to be
59: *> referenced as follows:
60: *>
61: *> UPLO = 'U' or 'u' Only the upper triangular part of the
62: *> hermitian matrix is to be referenced.
63: *>
64: *> UPLO = 'L' or 'l' Only the lower triangular part of the
65: *> hermitian matrix is to be referenced.
66: *> \endverbatim
67: *>
68: *> \param[in] M
69: *> \verbatim
70: *> M is INTEGER
71: *> On entry, M specifies the number of rows of the matrix C.
72: *> M must be at least zero.
73: *> \endverbatim
74: *>
75: *> \param[in] N
76: *> \verbatim
77: *> N is INTEGER
78: *> On entry, N specifies the number of columns of the matrix C.
79: *> N must be at least zero.
80: *> \endverbatim
81: *>
82: *> \param[in] ALPHA
83: *> \verbatim
84: *> ALPHA is COMPLEX*16
85: *> On entry, ALPHA specifies the scalar alpha.
86: *> \endverbatim
87: *>
88: *> \param[in] A
89: *> \verbatim
90: *> A is COMPLEX*16 array of DIMENSION ( LDA, ka ), where ka is
91: *> m when SIDE = 'L' or 'l' and is n otherwise.
92: *> Before entry with SIDE = 'L' or 'l', the m by m part of
93: *> the array A must contain the hermitian matrix, such that
94: *> when UPLO = 'U' or 'u', the leading m by m upper triangular
95: *> part of the array A must contain the upper triangular part
96: *> of the hermitian matrix and the strictly lower triangular
97: *> part of A is not referenced, and when UPLO = 'L' or 'l',
98: *> the leading m by m lower triangular part of the array A
99: *> must contain the lower triangular part of the hermitian
100: *> matrix and the strictly upper triangular part of A is not
101: *> referenced.
102: *> Before entry with SIDE = 'R' or 'r', the n by n part of
103: *> the array A must contain the hermitian matrix, such that
104: *> when UPLO = 'U' or 'u', the leading n by n upper triangular
105: *> part of the array A must contain the upper triangular part
106: *> of the hermitian matrix and the strictly lower triangular
107: *> part of A is not referenced, and when UPLO = 'L' or 'l',
108: *> the leading n by n lower triangular part of the array A
109: *> must contain the lower triangular part of the hermitian
110: *> matrix and the strictly upper triangular part of A is not
111: *> referenced.
112: *> Note that the imaginary parts of the diagonal elements need
113: *> not be set, they are assumed to be zero.
114: *> \endverbatim
115: *>
116: *> \param[in] LDA
117: *> \verbatim
118: *> LDA is INTEGER
119: *> On entry, LDA specifies the first dimension of A as declared
120: *> in the calling (sub) program. When SIDE = 'L' or 'l' then
121: *> LDA must be at least max( 1, m ), otherwise LDA must be at
122: *> least max( 1, n ).
123: *> \endverbatim
124: *>
125: *> \param[in] B
126: *> \verbatim
127: *> B is COMPLEX*16 array of DIMENSION ( LDB, n ).
128: *> Before entry, the leading m by n part of the array B must
129: *> contain the matrix B.
130: *> \endverbatim
131: *>
132: *> \param[in] LDB
133: *> \verbatim
134: *> LDB is INTEGER
135: *> On entry, LDB specifies the first dimension of B as declared
136: *> in the calling (sub) program. LDB must be at least
137: *> max( 1, m ).
138: *> \endverbatim
139: *>
140: *> \param[in] BETA
141: *> \verbatim
142: *> BETA is COMPLEX*16
143: *> On entry, BETA specifies the scalar beta. When BETA is
144: *> supplied as zero then C need not be set on input.
145: *> \endverbatim
146: *>
147: *> \param[in,out] C
148: *> \verbatim
149: *> C is COMPLEX*16 array of DIMENSION ( LDC, n ).
150: *> Before entry, the leading m by n part of the array C must
151: *> contain the matrix C, except when beta is zero, in which
152: *> case C need not be set on entry.
153: *> On exit, the array C is overwritten by the m by n updated
154: *> matrix.
155: *> \endverbatim
156: *>
157: *> \param[in] LDC
158: *> \verbatim
159: *> LDC is INTEGER
160: *> On entry, LDC specifies the first dimension of C as declared
161: *> in the calling (sub) program. LDC must be at least
162: *> max( 1, m ).
163: *> \endverbatim
164: *
165: * Authors:
166: * ========
167: *
168: *> \author Univ. of Tennessee
169: *> \author Univ. of California Berkeley
170: *> \author Univ. of Colorado Denver
171: *> \author NAG Ltd.
172: *
173: *> \date November 2011
174: *
175: *> \ingroup complex16_blas_level3
176: *
177: *> \par Further Details:
178: * =====================
179: *>
180: *> \verbatim
181: *>
182: *> Level 3 Blas routine.
183: *>
184: *> -- Written on 8-February-1989.
185: *> Jack Dongarra, Argonne National Laboratory.
186: *> Iain Duff, AERE Harwell.
187: *> Jeremy Du Croz, Numerical Algorithms Group Ltd.
188: *> Sven Hammarling, Numerical Algorithms Group Ltd.
189: *> \endverbatim
190: *>
191: * =====================================================================
192: SUBROUTINE ZHEMM(SIDE,UPLO,M,N,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
193: *
194: * -- Reference BLAS level3 routine (version 3.4.0) --
195: * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
196: * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
197: * November 2011
198: *
199: * .. Scalar Arguments ..
200: COMPLEX*16 ALPHA,BETA
201: INTEGER LDA,LDB,LDC,M,N
202: CHARACTER SIDE,UPLO
203: * ..
204: * .. Array Arguments ..
205: COMPLEX*16 A(LDA,*),B(LDB,*),C(LDC,*)
206: * ..
207: *
208: * =====================================================================
209: *
210: * .. External Functions ..
211: LOGICAL LSAME
212: EXTERNAL LSAME
213: * ..
214: * .. External Subroutines ..
215: EXTERNAL XERBLA
216: * ..
217: * .. Intrinsic Functions ..
218: INTRINSIC DBLE,DCONJG,MAX
219: * ..
220: * .. Local Scalars ..
221: COMPLEX*16 TEMP1,TEMP2
222: INTEGER I,INFO,J,K,NROWA
223: LOGICAL UPPER
224: * ..
225: * .. Parameters ..
226: COMPLEX*16 ONE
227: PARAMETER (ONE= (1.0D+0,0.0D+0))
228: COMPLEX*16 ZERO
229: PARAMETER (ZERO= (0.0D+0,0.0D+0))
230: * ..
231: *
232: * Set NROWA as the number of rows of A.
233: *
234: IF (LSAME(SIDE,'L')) THEN
235: NROWA = M
236: ELSE
237: NROWA = N
238: END IF
239: UPPER = LSAME(UPLO,'U')
240: *
241: * Test the input parameters.
242: *
243: INFO = 0
244: IF ((.NOT.LSAME(SIDE,'L')) .AND. (.NOT.LSAME(SIDE,'R'))) THEN
245: INFO = 1
246: ELSE IF ((.NOT.UPPER) .AND. (.NOT.LSAME(UPLO,'L'))) THEN
247: INFO = 2
248: ELSE IF (M.LT.0) THEN
249: INFO = 3
250: ELSE IF (N.LT.0) THEN
251: INFO = 4
252: ELSE IF (LDA.LT.MAX(1,NROWA)) THEN
253: INFO = 7
254: ELSE IF (LDB.LT.MAX(1,M)) THEN
255: INFO = 9
256: ELSE IF (LDC.LT.MAX(1,M)) THEN
257: INFO = 12
258: END IF
259: IF (INFO.NE.0) THEN
260: CALL XERBLA('ZHEMM ',INFO)
261: RETURN
262: END IF
263: *
264: * Quick return if possible.
265: *
266: IF ((M.EQ.0) .OR. (N.EQ.0) .OR.
267: + ((ALPHA.EQ.ZERO).AND. (BETA.EQ.ONE))) RETURN
268: *
269: * And when alpha.eq.zero.
270: *
271: IF (ALPHA.EQ.ZERO) THEN
272: IF (BETA.EQ.ZERO) THEN
273: DO 20 J = 1,N
274: DO 10 I = 1,M
275: C(I,J) = ZERO
276: 10 CONTINUE
277: 20 CONTINUE
278: ELSE
279: DO 40 J = 1,N
280: DO 30 I = 1,M
281: C(I,J) = BETA*C(I,J)
282: 30 CONTINUE
283: 40 CONTINUE
284: END IF
285: RETURN
286: END IF
287: *
288: * Start the operations.
289: *
290: IF (LSAME(SIDE,'L')) THEN
291: *
292: * Form C := alpha*A*B + beta*C.
293: *
294: IF (UPPER) THEN
295: DO 70 J = 1,N
296: DO 60 I = 1,M
297: TEMP1 = ALPHA*B(I,J)
298: TEMP2 = ZERO
299: DO 50 K = 1,I - 1
300: C(K,J) = C(K,J) + TEMP1*A(K,I)
301: TEMP2 = TEMP2 + B(K,J)*DCONJG(A(K,I))
302: 50 CONTINUE
303: IF (BETA.EQ.ZERO) THEN
304: C(I,J) = TEMP1*DBLE(A(I,I)) + ALPHA*TEMP2
305: ELSE
306: C(I,J) = BETA*C(I,J) + TEMP1*DBLE(A(I,I)) +
307: + ALPHA*TEMP2
308: END IF
309: 60 CONTINUE
310: 70 CONTINUE
311: ELSE
312: DO 100 J = 1,N
313: DO 90 I = M,1,-1
314: TEMP1 = ALPHA*B(I,J)
315: TEMP2 = ZERO
316: DO 80 K = I + 1,M
317: C(K,J) = C(K,J) + TEMP1*A(K,I)
318: TEMP2 = TEMP2 + B(K,J)*DCONJG(A(K,I))
319: 80 CONTINUE
320: IF (BETA.EQ.ZERO) THEN
321: C(I,J) = TEMP1*DBLE(A(I,I)) + ALPHA*TEMP2
322: ELSE
323: C(I,J) = BETA*C(I,J) + TEMP1*DBLE(A(I,I)) +
324: + ALPHA*TEMP2
325: END IF
326: 90 CONTINUE
327: 100 CONTINUE
328: END IF
329: ELSE
330: *
331: * Form C := alpha*B*A + beta*C.
332: *
333: DO 170 J = 1,N
334: TEMP1 = ALPHA*DBLE(A(J,J))
335: IF (BETA.EQ.ZERO) THEN
336: DO 110 I = 1,M
337: C(I,J) = TEMP1*B(I,J)
338: 110 CONTINUE
339: ELSE
340: DO 120 I = 1,M
341: C(I,J) = BETA*C(I,J) + TEMP1*B(I,J)
342: 120 CONTINUE
343: END IF
344: DO 140 K = 1,J - 1
345: IF (UPPER) THEN
346: TEMP1 = ALPHA*A(K,J)
347: ELSE
348: TEMP1 = ALPHA*DCONJG(A(J,K))
349: END IF
350: DO 130 I = 1,M
351: C(I,J) = C(I,J) + TEMP1*B(I,K)
352: 130 CONTINUE
353: 140 CONTINUE
354: DO 160 K = J + 1,N
355: IF (UPPER) THEN
356: TEMP1 = ALPHA*DCONJG(A(J,K))
357: ELSE
358: TEMP1 = ALPHA*A(K,J)
359: END IF
360: DO 150 I = 1,M
361: C(I,J) = C(I,J) + TEMP1*B(I,K)
362: 150 CONTINUE
363: 160 CONTINUE
364: 170 CONTINUE
365: END IF
366: *
367: RETURN
368: *
369: * End of ZHEMM .
370: *
371: END
CVSweb interface <joel.bertrand@systella.fr>