Statistiques
| Révision :

root / src / blas / zher2k.f @ 4

Historique | Voir | Annoter | Télécharger (12,86 ko)

1
      SUBROUTINE ZHER2K(UPLO,TRANS,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
2
*     .. Scalar Arguments ..
3
      DOUBLE COMPLEX ALPHA
4
      DOUBLE PRECISION BETA
5
      INTEGER K,LDA,LDB,LDC,N
6
      CHARACTER TRANS,UPLO
7
*     ..
8
*     .. Array Arguments ..
9
      DOUBLE COMPLEX A(LDA,*),B(LDB,*),C(LDC,*)
10
*     ..
11
*
12
*  Purpose
13
*  =======
14
*
15
*  ZHER2K  performs one of the hermitian rank 2k operations
16
*
17
*     C := alpha*A*conjg( B' ) + conjg( alpha )*B*conjg( A' ) + beta*C,
18
*
19
*  or
20
*
21
*     C := alpha*conjg( A' )*B + conjg( alpha )*conjg( B' )*A + beta*C,
22
*
23
*  where  alpha and beta  are scalars with  beta  real,  C is an  n by n
24
*  hermitian matrix and  A and B  are  n by k matrices in the first case
25
*  and  k by n  matrices in the second case.
26
*
27
*  Arguments
28
*  ==========
29
*
30
*  UPLO   - CHARACTER*1.
31
*           On  entry,   UPLO  specifies  whether  the  upper  or  lower
32
*           triangular  part  of the  array  C  is to be  referenced  as
33
*           follows:
34
*
35
*              UPLO = 'U' or 'u'   Only the  upper triangular part of  C
36
*                                  is to be referenced.
37
*
38
*              UPLO = 'L' or 'l'   Only the  lower triangular part of  C
39
*                                  is to be referenced.
40
*
41
*           Unchanged on exit.
42
*
43
*  TRANS  - CHARACTER*1.
44
*           On entry,  TRANS  specifies the operation to be performed as
45
*           follows:
46
*
47
*              TRANS = 'N' or 'n'    C := alpha*A*conjg( B' )          +
48
*                                         conjg( alpha )*B*conjg( A' ) +
49
*                                         beta*C.
50
*
51
*              TRANS = 'C' or 'c'    C := alpha*conjg( A' )*B          +
52
*                                         conjg( alpha )*conjg( B' )*A +
53
*                                         beta*C.
54
*
55
*           Unchanged on exit.
56
*
57
*  N      - INTEGER.
58
*           On entry,  N specifies the order of the matrix C.  N must be
59
*           at least zero.
60
*           Unchanged on exit.
61
*
62
*  K      - INTEGER.
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 = 'C' or 'c',  K  specifies  the number of rows of the
66
*           matrices  A and B.  K must be at least zero.
67
*           Unchanged on exit.
68
*
69
*  ALPHA  - COMPLEX*16         .
70
*           On entry, ALPHA specifies the scalar alpha.
71
*           Unchanged on exit.
72
*
73
*  A      - COMPLEX*16       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
78
*           matrix A.
79
*           Unchanged on exit.
80
*
81
*  LDA    - INTEGER.
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 ).
86
*           Unchanged on exit.
87
*
88
*  B      - COMPLEX*16       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
93
*           matrix B.
94
*           Unchanged on exit.
95
*
96
*  LDB    - INTEGER.
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 ).
101
*           Unchanged on exit.
102
*
103
*  BETA   - DOUBLE PRECISION            .
104
*           On entry, BETA specifies the scalar beta.
105
*           Unchanged on exit.
106
*
107
*  C      - COMPLEX*16          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  hermitian 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  hermitian 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.
120
*           Note that the imaginary parts of the diagonal elements need
121
*           not be set,  they are assumed to be zero,  and on exit they
122
*           are set to zero.
123
*
124
*  LDC    - INTEGER.
125
*           On entry, LDC specifies the first dimension of C as declared
126
*           in  the  calling  (sub)  program.   LDC  must  be  at  least
127
*           max( 1, n ).
128
*           Unchanged on exit.
129
*
130
*
131
*  Level 3 Blas routine.
132
*
133
*  -- Written on 8-February-1989.
134
*     Jack Dongarra, Argonne National Laboratory.
135
*     Iain Duff, AERE Harwell.
136
*     Jeremy Du Croz, Numerical Algorithms Group Ltd.
137
*     Sven Hammarling, Numerical Algorithms Group Ltd.
138
*
139
*  -- Modified 8-Nov-93 to set C(J,J) to DBLE( C(J,J) ) when BETA = 1.
140
*     Ed Anderson, Cray Research Inc.
141
*
142
*
143
*     .. External Functions ..
144
      LOGICAL LSAME
145
      EXTERNAL LSAME
146
*     ..
147
*     .. External Subroutines ..
148
      EXTERNAL XERBLA
149
*     ..
150
*     .. Intrinsic Functions ..
151
      INTRINSIC DBLE,DCONJG,MAX
152
*     ..
153
*     .. Local Scalars ..
154
      DOUBLE COMPLEX TEMP1,TEMP2
155
      INTEGER I,INFO,J,L,NROWA
156
      LOGICAL UPPER
157
*     ..
158
*     .. Parameters ..
159
      DOUBLE PRECISION ONE
160
      PARAMETER (ONE=1.0D+0)
161
      DOUBLE COMPLEX ZERO
162
      PARAMETER (ZERO= (0.0D+0,0.0D+0))
163
*     ..
164
*
165
*     Test the input parameters.
166
*
167
      IF (LSAME(TRANS,'N')) THEN
168
          NROWA = N
169
      ELSE
170
          NROWA = K
171
      END IF
172
      UPPER = LSAME(UPLO,'U')
173
*
174
      INFO = 0
175
      IF ((.NOT.UPPER) .AND. (.NOT.LSAME(UPLO,'L'))) THEN
176
          INFO = 1
177
      ELSE IF ((.NOT.LSAME(TRANS,'N')) .AND.
178
     +         (.NOT.LSAME(TRANS,'C'))) THEN
179
          INFO = 2
180
      ELSE IF (N.LT.0) THEN
181
          INFO = 3
182
      ELSE IF (K.LT.0) THEN
183
          INFO = 4
184
      ELSE IF (LDA.LT.MAX(1,NROWA)) THEN
185
          INFO = 7
186
      ELSE IF (LDB.LT.MAX(1,NROWA)) THEN
187
          INFO = 9
188
      ELSE IF (LDC.LT.MAX(1,N)) THEN
189
          INFO = 12
190
      END IF
191
      IF (INFO.NE.0) THEN
192
          CALL XERBLA('ZHER2K',INFO)
193
          RETURN
194
      END IF
195
*
196
*     Quick return if possible.
197
*
198
      IF ((N.EQ.0) .OR. (((ALPHA.EQ.ZERO).OR.
199
     +    (K.EQ.0)).AND. (BETA.EQ.ONE))) RETURN
200
*
201
*     And when  alpha.eq.zero.
202
*
203
      IF (ALPHA.EQ.ZERO) THEN
204
          IF (UPPER) THEN
205
              IF (BETA.EQ.DBLE(ZERO)) THEN
206
                  DO 20 J = 1,N
207
                      DO 10 I = 1,J
208
                          C(I,J) = ZERO
209
   10                 CONTINUE
210
   20             CONTINUE
211
              ELSE
212
                  DO 40 J = 1,N
213
                      DO 30 I = 1,J - 1
214
                          C(I,J) = BETA*C(I,J)
215
   30                 CONTINUE
216
                      C(J,J) = BETA*DBLE(C(J,J))
217
   40             CONTINUE
218
              END IF
219
          ELSE
220
              IF (BETA.EQ.DBLE(ZERO)) THEN
221
                  DO 60 J = 1,N
222
                      DO 50 I = J,N
223
                          C(I,J) = ZERO
224
   50                 CONTINUE
225
   60             CONTINUE
226
              ELSE
227
                  DO 80 J = 1,N
228
                      C(J,J) = BETA*DBLE(C(J,J))
229
                      DO 70 I = J + 1,N
230
                          C(I,J) = BETA*C(I,J)
231
   70                 CONTINUE
232
   80             CONTINUE
233
              END IF
234
          END IF
235
          RETURN
236
      END IF
237
*
238
*     Start the operations.
239
*
240
      IF (LSAME(TRANS,'N')) THEN
241
*
242
*        Form  C := alpha*A*conjg( B' ) + conjg( alpha )*B*conjg( A' ) +
243
*                   C.
244
*
245
          IF (UPPER) THEN
246
              DO 130 J = 1,N
247
                  IF (BETA.EQ.DBLE(ZERO)) THEN
248
                      DO 90 I = 1,J
249
                          C(I,J) = ZERO
250
   90                 CONTINUE
251
                  ELSE IF (BETA.NE.ONE) THEN
252
                      DO 100 I = 1,J - 1
253
                          C(I,J) = BETA*C(I,J)
254
  100                 CONTINUE
255
                      C(J,J) = BETA*DBLE(C(J,J))
256
                  ELSE
257
                      C(J,J) = DBLE(C(J,J))
258
                  END IF
259
                  DO 120 L = 1,K
260
                      IF ((A(J,L).NE.ZERO) .OR. (B(J,L).NE.ZERO)) THEN
261
                          TEMP1 = ALPHA*DCONJG(B(J,L))
262
                          TEMP2 = DCONJG(ALPHA*A(J,L))
263
                          DO 110 I = 1,J - 1
264
                              C(I,J) = C(I,J) + A(I,L)*TEMP1 +
265
     +                                 B(I,L)*TEMP2
266
  110                     CONTINUE
267
                          C(J,J) = DBLE(C(J,J)) +
268
     +                             DBLE(A(J,L)*TEMP1+B(J,L)*TEMP2)
269
                      END IF
270
  120             CONTINUE
271
  130         CONTINUE
272
          ELSE
273
              DO 180 J = 1,N
274
                  IF (BETA.EQ.DBLE(ZERO)) THEN
275
                      DO 140 I = J,N
276
                          C(I,J) = ZERO
277
  140                 CONTINUE
278
                  ELSE IF (BETA.NE.ONE) THEN
279
                      DO 150 I = J + 1,N
280
                          C(I,J) = BETA*C(I,J)
281
  150                 CONTINUE
282
                      C(J,J) = BETA*DBLE(C(J,J))
283
                  ELSE
284
                      C(J,J) = DBLE(C(J,J))
285
                  END IF
286
                  DO 170 L = 1,K
287
                      IF ((A(J,L).NE.ZERO) .OR. (B(J,L).NE.ZERO)) THEN
288
                          TEMP1 = ALPHA*DCONJG(B(J,L))
289
                          TEMP2 = DCONJG(ALPHA*A(J,L))
290
                          DO 160 I = J + 1,N
291
                              C(I,J) = C(I,J) + A(I,L)*TEMP1 +
292
     +                                 B(I,L)*TEMP2
293
  160                     CONTINUE
294
                          C(J,J) = DBLE(C(J,J)) +
295
     +                             DBLE(A(J,L)*TEMP1+B(J,L)*TEMP2)
296
                      END IF
297
  170             CONTINUE
298
  180         CONTINUE
299
          END IF
300
      ELSE
301
*
302
*        Form  C := alpha*conjg( A' )*B + conjg( alpha )*conjg( B' )*A +
303
*                   C.
304
*
305
          IF (UPPER) THEN
306
              DO 210 J = 1,N
307
                  DO 200 I = 1,J
308
                      TEMP1 = ZERO
309
                      TEMP2 = ZERO
310
                      DO 190 L = 1,K
311
                          TEMP1 = TEMP1 + DCONJG(A(L,I))*B(L,J)
312
                          TEMP2 = TEMP2 + DCONJG(B(L,I))*A(L,J)
313
  190                 CONTINUE
314
                      IF (I.EQ.J) THEN
315
                          IF (BETA.EQ.DBLE(ZERO)) THEN
316
                              C(J,J) = DBLE(ALPHA*TEMP1+
317
     +                                 DCONJG(ALPHA)*TEMP2)
318
                          ELSE
319
                              C(J,J) = BETA*DBLE(C(J,J)) +
320
     +                                 DBLE(ALPHA*TEMP1+
321
     +                                 DCONJG(ALPHA)*TEMP2)
322
                          END IF
323
                      ELSE
324
                          IF (BETA.EQ.DBLE(ZERO)) THEN
325
                              C(I,J) = ALPHA*TEMP1 + DCONJG(ALPHA)*TEMP2
326
                          ELSE
327
                              C(I,J) = BETA*C(I,J) + ALPHA*TEMP1 +
328
     +                                 DCONJG(ALPHA)*TEMP2
329
                          END IF
330
                      END IF
331
  200             CONTINUE
332
  210         CONTINUE
333
          ELSE
334
              DO 240 J = 1,N
335
                  DO 230 I = J,N
336
                      TEMP1 = ZERO
337
                      TEMP2 = ZERO
338
                      DO 220 L = 1,K
339
                          TEMP1 = TEMP1 + DCONJG(A(L,I))*B(L,J)
340
                          TEMP2 = TEMP2 + DCONJG(B(L,I))*A(L,J)
341
  220                 CONTINUE
342
                      IF (I.EQ.J) THEN
343
                          IF (BETA.EQ.DBLE(ZERO)) THEN
344
                              C(J,J) = DBLE(ALPHA*TEMP1+
345
     +                                 DCONJG(ALPHA)*TEMP2)
346
                          ELSE
347
                              C(J,J) = BETA*DBLE(C(J,J)) +
348
     +                                 DBLE(ALPHA*TEMP1+
349
     +                                 DCONJG(ALPHA)*TEMP2)
350
                          END IF
351
                      ELSE
352
                          IF (BETA.EQ.DBLE(ZERO)) THEN
353
                              C(I,J) = ALPHA*TEMP1 + DCONJG(ALPHA)*TEMP2
354
                          ELSE
355
                              C(I,J) = BETA*C(I,J) + ALPHA*TEMP1 +
356
     +                                 DCONJG(ALPHA)*TEMP2
357
                          END IF
358
                      END IF
359
  230             CONTINUE
360
  240         CONTINUE
361
          END IF
362
      END IF
363
*
364
      RETURN
365
*
366
*     End of ZHER2K.
367
*
368
      END