Statistiques
| Révision :

root / src / blas / zsyr2k.f @ 5

Historique | Voir | Annoter | Télécharger (10,49 ko)

1
      SUBROUTINE ZSYR2K(UPLO,TRANS,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
2
*     .. Scalar Arguments ..
3
      DOUBLE COMPLEX ALPHA,BETA
4
      INTEGER K,LDA,LDB,LDC,N
5
      CHARACTER TRANS,UPLO
6
*     ..
7
*     .. Array Arguments ..
8
      DOUBLE COMPLEX A(LDA,*),B(LDB,*),C(LDC,*)
9
*     ..
10
*
11
*  Purpose
12
*  =======
13
*
14
*  ZSYR2K  performs one of the symmetric rank 2k operations
15
*
16
*     C := alpha*A*B' + alpha*B*A' + beta*C,
17
*
18
*  or
19
*
20
*     C := alpha*A'*B + alpha*B'*A + beta*C,
21
*
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.
25
*
26
*  Arguments
27
*  ==========
28
*
29
*  UPLO   - CHARACTER*1.
30
*           On  entry,   UPLO  specifies  whether  the  upper  or  lower
31
*           triangular  part  of the  array  C  is to be  referenced  as
32
*           follows:
33
*
34
*              UPLO = 'U' or 'u'   Only the  upper triangular part of  C
35
*                                  is to be referenced.
36
*
37
*              UPLO = 'L' or 'l'   Only the  lower triangular part of  C
38
*                                  is to be referenced.
39
*
40
*           Unchanged on exit.
41
*
42
*  TRANS  - CHARACTER*1.
43
*           On entry,  TRANS  specifies the operation to be performed as
44
*           follows:
45
*
46
*              TRANS = 'N' or 'n'    C := alpha*A*B' + alpha*B*A' +
47
*                                         beta*C.
48
*
49
*              TRANS = 'T' or 't'    C := alpha*A'*B + alpha*B'*A +
50
*                                         beta*C.
51
*
52
*           Unchanged on exit.
53
*
54
*  N      - INTEGER.
55
*           On entry,  N specifies the order of the matrix C.  N must be
56
*           at least zero.
57
*           Unchanged on exit.
58
*
59
*  K      - INTEGER.
60
*           On entry with  TRANS = 'N' or 'n',  K  specifies  the number
61
*           of  columns  of the  matrices  A and B,  and on  entry  with
62
*           TRANS = 'T' or 't',  K  specifies  the number of rows of the
63
*           matrices  A and B.  K must be at least zero.
64
*           Unchanged on exit.
65
*
66
*  ALPHA  - COMPLEX*16      .
67
*           On entry, ALPHA specifies the scalar alpha.
68
*           Unchanged on exit.
69
*
70
*  A      - COMPLEX*16       array of DIMENSION ( LDA, ka ), where ka is
71
*           k  when  TRANS = 'N' or 'n',  and is  n  otherwise.
72
*           Before entry with  TRANS = 'N' or 'n',  the  leading  n by k
73
*           part of the array  A  must contain the matrix  A,  otherwise
74
*           the leading  k by n  part of the array  A  must contain  the
75
*           matrix A.
76
*           Unchanged on exit.
77
*
78
*  LDA    - INTEGER.
79
*           On entry, LDA specifies the first dimension of A as declared
80
*           in  the  calling  (sub)  program.   When  TRANS = 'N' or 'n'
81
*           then  LDA must be at least  max( 1, n ), otherwise  LDA must
82
*           be at least  max( 1, k ).
83
*           Unchanged on exit.
84
*
85
*  B      - COMPLEX*16       array of DIMENSION ( LDB, kb ), where kb is
86
*           k  when  TRANS = 'N' or 'n',  and is  n  otherwise.
87
*           Before entry with  TRANS = 'N' or 'n',  the  leading  n by k
88
*           part of the array  B  must contain the matrix  B,  otherwise
89
*           the leading  k by n  part of the array  B  must contain  the
90
*           matrix B.
91
*           Unchanged on exit.
92
*
93
*  LDB    - INTEGER.
94
*           On entry, LDB specifies the first dimension of B as declared
95
*           in  the  calling  (sub)  program.   When  TRANS = 'N' or 'n'
96
*           then  LDB must be at least  max( 1, n ), otherwise  LDB must
97
*           be at least  max( 1, k ).
98
*           Unchanged on exit.
99
*
100
*  BETA   - COMPLEX*16      .
101
*           On entry, BETA specifies the scalar beta.
102
*           Unchanged on exit.
103
*
104
*  C      - COMPLEX*16       array of DIMENSION ( LDC, n ).
105
*           Before entry  with  UPLO = 'U' or 'u',  the leading  n by n
106
*           upper triangular part of the array C must contain the upper
107
*           triangular part  of the  symmetric matrix  and the strictly
108
*           lower triangular part of C is not referenced.  On exit, the
109
*           upper triangular part of the array  C is overwritten by the
110
*           upper triangular part of the updated matrix.
111
*           Before entry  with  UPLO = 'L' or 'l',  the leading  n by n
112
*           lower triangular part of the array C must contain the lower
113
*           triangular part  of the  symmetric matrix  and the strictly
114
*           upper triangular part of C is not referenced.  On exit, the
115
*           lower triangular part of the array  C is overwritten by the
116
*           lower triangular part of the updated matrix.
117
*
118
*  LDC    - INTEGER.
119
*           On entry, LDC specifies the first dimension of C as declared
120
*           in  the  calling  (sub)  program.   LDC  must  be  at  least
121
*           max( 1, n ).
122
*           Unchanged on exit.
123
*
124
*
125
*  Level 3 Blas routine.
126
*
127
*  -- Written on 8-February-1989.
128
*     Jack Dongarra, Argonne National Laboratory.
129
*     Iain Duff, AERE Harwell.
130
*     Jeremy Du Croz, Numerical Algorithms Group Ltd.
131
*     Sven Hammarling, Numerical Algorithms Group Ltd.
132
*
133
*
134
*     .. External Functions ..
135
      LOGICAL LSAME
136
      EXTERNAL LSAME
137
*     ..
138
*     .. External Subroutines ..
139
      EXTERNAL XERBLA
140
*     ..
141
*     .. Intrinsic Functions ..
142
      INTRINSIC MAX
143
*     ..
144
*     .. Local Scalars ..
145
      DOUBLE COMPLEX TEMP1,TEMP2
146
      INTEGER I,INFO,J,L,NROWA
147
      LOGICAL UPPER
148
*     ..
149
*     .. Parameters ..
150
      DOUBLE COMPLEX ONE
151
      PARAMETER (ONE= (1.0D+0,0.0D+0))
152
      DOUBLE COMPLEX ZERO
153
      PARAMETER (ZERO= (0.0D+0,0.0D+0))
154
*     ..
155
*
156
*     Test the input parameters.
157
*
158
      IF (LSAME(TRANS,'N')) THEN
159
          NROWA = N
160
      ELSE
161
          NROWA = K
162
      END IF
163
      UPPER = LSAME(UPLO,'U')
164
*
165
      INFO = 0
166
      IF ((.NOT.UPPER) .AND. (.NOT.LSAME(UPLO,'L'))) THEN
167
          INFO = 1
168
      ELSE IF ((.NOT.LSAME(TRANS,'N')) .AND.
169
     +         (.NOT.LSAME(TRANS,'T'))) THEN
170
          INFO = 2
171
      ELSE IF (N.LT.0) THEN
172
          INFO = 3
173
      ELSE IF (K.LT.0) THEN
174
          INFO = 4
175
      ELSE IF (LDA.LT.MAX(1,NROWA)) THEN
176
          INFO = 7
177
      ELSE IF (LDB.LT.MAX(1,NROWA)) THEN
178
          INFO = 9
179
      ELSE IF (LDC.LT.MAX(1,N)) THEN
180
          INFO = 12
181
      END IF
182
      IF (INFO.NE.0) THEN
183
          CALL XERBLA('ZSYR2K',INFO)
184
          RETURN
185
      END IF
186
*
187
*     Quick return if possible.
188
*
189
      IF ((N.EQ.0) .OR. (((ALPHA.EQ.ZERO).OR.
190
     +    (K.EQ.0)).AND. (BETA.EQ.ONE))) RETURN
191
*
192
*     And when  alpha.eq.zero.
193
*
194
      IF (ALPHA.EQ.ZERO) THEN
195
          IF (UPPER) THEN
196
              IF (BETA.EQ.ZERO) THEN
197
                  DO 20 J = 1,N
198
                      DO 10 I = 1,J
199
                          C(I,J) = ZERO
200
   10                 CONTINUE
201
   20             CONTINUE
202
              ELSE
203
                  DO 40 J = 1,N
204
                      DO 30 I = 1,J
205
                          C(I,J) = BETA*C(I,J)
206
   30                 CONTINUE
207
   40             CONTINUE
208
              END IF
209
          ELSE
210
              IF (BETA.EQ.ZERO) THEN
211
                  DO 60 J = 1,N
212
                      DO 50 I = J,N
213
                          C(I,J) = ZERO
214
   50                 CONTINUE
215
   60             CONTINUE
216
              ELSE
217
                  DO 80 J = 1,N
218
                      DO 70 I = J,N
219
                          C(I,J) = BETA*C(I,J)
220
   70                 CONTINUE
221
   80             CONTINUE
222
              END IF
223
          END IF
224
          RETURN
225
      END IF
226
*
227
*     Start the operations.
228
*
229
      IF (LSAME(TRANS,'N')) THEN
230
*
231
*        Form  C := alpha*A*B' + alpha*B*A' + C.
232
*
233
          IF (UPPER) THEN
234
              DO 130 J = 1,N
235
                  IF (BETA.EQ.ZERO) THEN
236
                      DO 90 I = 1,J
237
                          C(I,J) = ZERO
238
   90                 CONTINUE
239
                  ELSE IF (BETA.NE.ONE) THEN
240
                      DO 100 I = 1,J
241
                          C(I,J) = BETA*C(I,J)
242
  100                 CONTINUE
243
                  END IF
244
                  DO 120 L = 1,K
245
                      IF ((A(J,L).NE.ZERO) .OR. (B(J,L).NE.ZERO)) THEN
246
                          TEMP1 = ALPHA*B(J,L)
247
                          TEMP2 = ALPHA*A(J,L)
248
                          DO 110 I = 1,J
249
                              C(I,J) = C(I,J) + A(I,L)*TEMP1 +
250
     +                                 B(I,L)*TEMP2
251
  110                     CONTINUE
252
                      END IF
253
  120             CONTINUE
254
  130         CONTINUE
255
          ELSE
256
              DO 180 J = 1,N
257
                  IF (BETA.EQ.ZERO) THEN
258
                      DO 140 I = J,N
259
                          C(I,J) = ZERO
260
  140                 CONTINUE
261
                  ELSE IF (BETA.NE.ONE) THEN
262
                      DO 150 I = J,N
263
                          C(I,J) = BETA*C(I,J)
264
  150                 CONTINUE
265
                  END IF
266
                  DO 170 L = 1,K
267
                      IF ((A(J,L).NE.ZERO) .OR. (B(J,L).NE.ZERO)) THEN
268
                          TEMP1 = ALPHA*B(J,L)
269
                          TEMP2 = ALPHA*A(J,L)
270
                          DO 160 I = J,N
271
                              C(I,J) = C(I,J) + A(I,L)*TEMP1 +
272
     +                                 B(I,L)*TEMP2
273
  160                     CONTINUE
274
                      END IF
275
  170             CONTINUE
276
  180         CONTINUE
277
          END IF
278
      ELSE
279
*
280
*        Form  C := alpha*A'*B + alpha*B'*A + C.
281
*
282
          IF (UPPER) THEN
283
              DO 210 J = 1,N
284
                  DO 200 I = 1,J
285
                      TEMP1 = ZERO
286
                      TEMP2 = ZERO
287
                      DO 190 L = 1,K
288
                          TEMP1 = TEMP1 + A(L,I)*B(L,J)
289
                          TEMP2 = TEMP2 + B(L,I)*A(L,J)
290
  190                 CONTINUE
291
                      IF (BETA.EQ.ZERO) THEN
292
                          C(I,J) = ALPHA*TEMP1 + ALPHA*TEMP2
293
                      ELSE
294
                          C(I,J) = BETA*C(I,J) + ALPHA*TEMP1 +
295
     +                             ALPHA*TEMP2
296
                      END IF
297
  200             CONTINUE
298
  210         CONTINUE
299
          ELSE
300
              DO 240 J = 1,N
301
                  DO 230 I = J,N
302
                      TEMP1 = ZERO
303
                      TEMP2 = ZERO
304
                      DO 220 L = 1,K
305
                          TEMP1 = TEMP1 + A(L,I)*B(L,J)
306
                          TEMP2 = TEMP2 + B(L,I)*A(L,J)
307
  220                 CONTINUE
308
                      IF (BETA.EQ.ZERO) THEN
309
                          C(I,J) = ALPHA*TEMP1 + ALPHA*TEMP2
310
                      ELSE
311
                          C(I,J) = BETA*C(I,J) + ALPHA*TEMP1 +
312
     +                             ALPHA*TEMP2
313
                      END IF
314
  230             CONTINUE
315
  240         CONTINUE
316
          END IF
317
      END IF
318
*
319
      RETURN
320
*
321
*     End of ZSYR2K.
322
*
323
      END