001:       SUBROUTINE SSYR2K(UPLO,TRANS,N,K,ALPHA,A,LDA,B,LDB,BETA,C,LDC)
002: *     .. Scalar Arguments ..
003:       REAL ALPHA,BETA
004:       INTEGER K,LDA,LDB,LDC,N
005:       CHARACTER TRANS,UPLO
006: *     ..
007: *     .. Array Arguments ..
008:       REAL A(LDA,*),B(LDB,*),C(LDC,*)
009: *     ..
010: *
011: *  Purpose
012: *  =======
013: *
014: *  SSYR2K  performs one of the symmetric rank 2k operations
015: *
016: *     C := alpha*A*B' + alpha*B*A' + beta*C,
017: *
018: *  or
019: *
020: *     C := alpha*A'*B + alpha*B'*A + beta*C,
021: *
022: *  where  alpha and beta  are scalars, C is an  n by n  symmetric matrix
023: *  and  A and B  are  n by k  matrices  in the  first  case  and  k by n
024: *  matrices in the second case.
025: *
026: *  Arguments
027: *  ==========
028: *
029: *  UPLO   - CHARACTER*1.
030: *           On  entry,   UPLO  specifies  whether  the  upper  or  lower
031: *           triangular  part  of the  array  C  is to be  referenced  as
032: *           follows:
033: *
034: *              UPLO = 'U' or 'u'   Only the  upper triangular part of  C
035: *                                  is to be referenced.
036: *
037: *              UPLO = 'L' or 'l'   Only the  lower triangular part of  C
038: *                                  is to be referenced.
039: *
040: *           Unchanged on exit.
041: *
042: *  TRANS  - CHARACTER*1.
043: *           On entry,  TRANS  specifies the operation to be performed as
044: *           follows:
045: *
046: *              TRANS = 'N' or 'n'   C := alpha*A*B' + alpha*B*A' +
047: *                                        beta*C.
048: *
049: *              TRANS = 'T' or 't'   C := alpha*A'*B + alpha*B'*A +
050: *                                        beta*C.
051: *
052: *              TRANS = 'C' or 'c'   C := alpha*A'*B + alpha*B'*A +
053: *                                        beta*C.
054: *
055: *           Unchanged on exit.
056: *
057: *  N      - INTEGER.
058: *           On entry,  N specifies the order of the matrix C.  N must be
059: *           at least zero.
060: *           Unchanged on exit.
061: *
062: *  K      - INTEGER.
063: *           On entry with  TRANS = 'N' or 'n',  K  specifies  the number
064: *           of  columns  of the  matrices  A and B,  and on  entry  with
065: *           TRANS = 'T' or 't' or 'C' or 'c',  K  specifies  the  number
066: *           of rows of the matrices  A and B.  K must be at least  zero.
067: *           Unchanged on exit.
068: *
069: *  ALPHA  - REAL            .
070: *           On entry, ALPHA specifies the scalar alpha.
071: *           Unchanged on exit.
072: *
073: *  A      - REAL             array of DIMENSION ( LDA, ka ), where ka is
074: *           k  when  TRANS = 'N' or 'n',  and is  n  otherwise.
075: *           Before entry with  TRANS = 'N' or 'n',  the  leading  n by k
076: *           part of the array  A  must contain the matrix  A,  otherwise
077: *           the leading  k by n  part of the array  A  must contain  the
078: *           matrix A.
079: *           Unchanged on exit.
080: *
081: *  LDA    - INTEGER.
082: *           On entry, LDA specifies the first dimension of A as declared
083: *           in  the  calling  (sub)  program.   When  TRANS = 'N' or 'n'
084: *           then  LDA must be at least  max( 1, n ), otherwise  LDA must
085: *           be at least  max( 1, k ).
086: *           Unchanged on exit.
087: *
088: *  B      - REAL             array of DIMENSION ( LDB, kb ), where kb is
089: *           k  when  TRANS = 'N' or 'n',  and is  n  otherwise.
090: *           Before entry with  TRANS = 'N' or 'n',  the  leading  n by k
091: *           part of the array  B  must contain the matrix  B,  otherwise
092: *           the leading  k by n  part of the array  B  must contain  the
093: *           matrix B.
094: *           Unchanged on exit.
095: *
096: *  LDB    - INTEGER.
097: *           On entry, LDB specifies the first dimension of B as declared
098: *           in  the  calling  (sub)  program.   When  TRANS = 'N' or 'n'
099: *           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   - REAL            .
104: *           On entry, BETA specifies the scalar beta.
105: *           Unchanged on exit.
106: *
107: *  C      - REAL             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.
120: *
121: *  LDC    - INTEGER.
122: *           On entry, LDC specifies the first dimension of C as declared
123: *           in  the  calling  (sub)  program.   LDC  must  be  at  least
124: *           max( 1, n ).
125: *           Unchanged on exit.
126: *
127: *
128: *  Level 3 Blas routine.
129: *
130: *
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.
136: *
137: *
138: *     .. External Functions ..
139:       LOGICAL LSAME
140:       EXTERNAL LSAME
141: *     ..
142: *     .. External Subroutines ..
143:       EXTERNAL XERBLA
144: *     ..
145: *     .. Intrinsic Functions ..
146:       INTRINSIC MAX
147: *     ..
148: *     .. Local Scalars ..
149:       REAL TEMP1,TEMP2
150:       INTEGER I,INFO,J,L,NROWA
151:       LOGICAL UPPER
152: *     ..
153: *     .. Parameters ..
154:       REAL ONE,ZERO
155:       PARAMETER (ONE=1.0E+0,ZERO=0.0E+0)
156: *     ..
157: *
158: *     Test the input parameters.
159: *
160:       IF (LSAME(TRANS,'N')) THEN
161:           NROWA = N
162:       ELSE
163:           NROWA = K
164:       END IF
165:       UPPER = LSAME(UPLO,'U')
166: *
167:       INFO = 0
168:       IF ((.NOT.UPPER) .AND. (.NOT.LSAME(UPLO,'L'))) THEN
169:           INFO = 1
170:       ELSE IF ((.NOT.LSAME(TRANS,'N')) .AND.
171:      +         (.NOT.LSAME(TRANS,'T')) .AND.
172:      +         (.NOT.LSAME(TRANS,'C'))) THEN
173:           INFO = 2
174:       ELSE IF (N.LT.0) THEN
175:           INFO = 3
176:       ELSE IF (K.LT.0) THEN
177:           INFO = 4
178:       ELSE IF (LDA.LT.MAX(1,NROWA)) THEN
179:           INFO = 7
180:       ELSE IF (LDB.LT.MAX(1,NROWA)) THEN
181:           INFO = 9
182:       ELSE IF (LDC.LT.MAX(1,N)) THEN
183:           INFO = 12
184:       END IF
185:       IF (INFO.NE.0) THEN
186:           CALL XERBLA('SSYR2K',INFO)
187:           RETURN
188:       END IF
189: *
190: *     Quick return if possible.
191: *
192:       IF ((N.EQ.0) .OR. (((ALPHA.EQ.ZERO).OR.
193:      +    (K.EQ.0)).AND. (BETA.EQ.ONE))) RETURN
194: *
195: *     And when  alpha.eq.zero.
196: *
197:       IF (ALPHA.EQ.ZERO) THEN
198:           IF (UPPER) THEN
199:               IF (BETA.EQ.ZERO) THEN
200:                   DO 20 J = 1,N
201:                       DO 10 I = 1,J
202:                           C(I,J) = ZERO
203:    10                 CONTINUE
204:    20             CONTINUE
205:               ELSE
206:                   DO 40 J = 1,N
207:                       DO 30 I = 1,J
208:                           C(I,J) = BETA*C(I,J)
209:    30                 CONTINUE
210:    40             CONTINUE
211:               END IF
212:           ELSE
213:               IF (BETA.EQ.ZERO) THEN
214:                   DO 60 J = 1,N
215:                       DO 50 I = J,N
216:                           C(I,J) = ZERO
217:    50                 CONTINUE
218:    60             CONTINUE
219:               ELSE
220:                   DO 80 J = 1,N
221:                       DO 70 I = J,N
222:                           C(I,J) = BETA*C(I,J)
223:    70                 CONTINUE
224:    80             CONTINUE
225:               END IF
226:           END IF
227:           RETURN
228:       END IF
229: *
230: *     Start the operations.
231: *
232:       IF (LSAME(TRANS,'N')) THEN
233: *
234: *        Form  C := alpha*A*B' + alpha*B*A' + C.
235: *
236:           IF (UPPER) THEN
237:               DO 130 J = 1,N
238:                   IF (BETA.EQ.ZERO) THEN
239:                       DO 90 I = 1,J
240:                           C(I,J) = ZERO
241:    90                 CONTINUE
242:                   ELSE IF (BETA.NE.ONE) THEN
243:                       DO 100 I = 1,J
244:                           C(I,J) = BETA*C(I,J)
245:   100                 CONTINUE
246:                   END IF
247:                   DO 120 L = 1,K
248:                       IF ((A(J,L).NE.ZERO) .OR. (B(J,L).NE.ZERO)) THEN
249:                           TEMP1 = ALPHA*B(J,L)
250:                           TEMP2 = ALPHA*A(J,L)
251:                           DO 110 I = 1,J
252:                               C(I,J) = C(I,J) + A(I,L)*TEMP1 +
253:      +                                 B(I,L)*TEMP2
254:   110                     CONTINUE
255:                       END IF
256:   120             CONTINUE
257:   130         CONTINUE
258:           ELSE
259:               DO 180 J = 1,N
260:                   IF (BETA.EQ.ZERO) THEN
261:                       DO 140 I = J,N
262:                           C(I,J) = ZERO
263:   140                 CONTINUE
264:                   ELSE IF (BETA.NE.ONE) THEN
265:                       DO 150 I = J,N
266:                           C(I,J) = BETA*C(I,J)
267:   150                 CONTINUE
268:                   END IF
269:                   DO 170 L = 1,K
270:                       IF ((A(J,L).NE.ZERO) .OR. (B(J,L).NE.ZERO)) THEN
271:                           TEMP1 = ALPHA*B(J,L)
272:                           TEMP2 = ALPHA*A(J,L)
273:                           DO 160 I = J,N
274:                               C(I,J) = C(I,J) + A(I,L)*TEMP1 +
275:      +                                 B(I,L)*TEMP2
276:   160                     CONTINUE
277:                       END IF
278:   170             CONTINUE
279:   180         CONTINUE
280:           END IF
281:       ELSE
282: *
283: *        Form  C := alpha*A'*B + alpha*B'*A + C.
284: *
285:           IF (UPPER) THEN
286:               DO 210 J = 1,N
287:                   DO 200 I = 1,J
288:                       TEMP1 = ZERO
289:                       TEMP2 = ZERO
290:                       DO 190 L = 1,K
291:                           TEMP1 = TEMP1 + A(L,I)*B(L,J)
292:                           TEMP2 = TEMP2 + B(L,I)*A(L,J)
293:   190                 CONTINUE
294:                       IF (BETA.EQ.ZERO) THEN
295:                           C(I,J) = ALPHA*TEMP1 + ALPHA*TEMP2
296:                       ELSE
297:                           C(I,J) = BETA*C(I,J) + ALPHA*TEMP1 +
298:      +                             ALPHA*TEMP2
299:                       END IF
300:   200             CONTINUE
301:   210         CONTINUE
302:           ELSE
303:               DO 240 J = 1,N
304:                   DO 230 I = J,N
305:                       TEMP1 = ZERO
306:                       TEMP2 = ZERO
307:                       DO 220 L = 1,K
308:                           TEMP1 = TEMP1 + A(L,I)*B(L,J)
309:                           TEMP2 = TEMP2 + B(L,I)*A(L,J)
310:   220                 CONTINUE
311:                       IF (BETA.EQ.ZERO) THEN
312:                           C(I,J) = ALPHA*TEMP1 + ALPHA*TEMP2
313:                       ELSE
314:                           C(I,J) = BETA*C(I,J) + ALPHA*TEMP1 +
315:      +                             ALPHA*TEMP2
316:                       END IF
317:   230             CONTINUE
318:   240         CONTINUE
319:           END IF
320:       END IF
321: *
322:       RETURN
323: *
324: *     End of SSYR2K.
325: *
326:       END
327: