LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ssyrk()

subroutine ssyrk ( character  uplo,
character  trans,
integer  n,
integer  k,
real  alpha,
real, dimension(lda,*)  a,
integer  lda,
real  beta,
real, dimension(ldc,*)  c,
integer  ldc 
)

SSYRK

Purpose:
 SSYRK  performs one of the symmetric rank k operations

    C := alpha*A*A**T + beta*C,

 or

    C := alpha*A**T*A + beta*C,

 where  alpha and beta  are scalars, C is an  n by n  symmetric matrix
 and  A  is an  n by k  matrix in the first case and a  k by n  matrix
 in the second case.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On  entry,   UPLO  specifies  whether  the  upper  or  lower
           triangular  part  of the  array  C  is to be  referenced  as
           follows:

              UPLO = 'U' or 'u'   Only the  upper triangular part of  C
                                  is to be referenced.

              UPLO = 'L' or 'l'   Only the  lower triangular part of  C
                                  is to be referenced.
[in]TRANS
          TRANS is CHARACTER*1
           On entry,  TRANS  specifies the operation to be performed as
           follows:

              TRANS = 'N' or 'n'   C := alpha*A*A**T + beta*C.

              TRANS = 'T' or 't'   C := alpha*A**T*A + beta*C.

              TRANS = 'C' or 'c'   C := alpha*A**T*A + beta*C.
[in]N
          N is INTEGER
           On entry,  N specifies the order of the matrix C.  N must be
           at least zero.
[in]K
          K is INTEGER
           On entry with  TRANS = 'N' or 'n',  K  specifies  the number
           of  columns   of  the   matrix   A,   and  on   entry   with
           TRANS = 'T' or 't' or 'C' or 'c',  K  specifies  the  number
           of rows of the matrix  A.  K must be at least zero.
[in]ALPHA
          ALPHA is REAL
           On entry, ALPHA specifies the scalar alpha.
[in]A
          A is REAL array, dimension ( LDA, ka ), where ka is
           k  when  TRANS = 'N' or 'n',  and is  n  otherwise.
           Before entry with  TRANS = 'N' or 'n',  the  leading  n by k
           part of the array  A  must contain the matrix  A,  otherwise
           the leading  k by n  part of the array  A  must contain  the
           matrix A.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in  the  calling  (sub)  program.   When  TRANS = 'N' or 'n'
           then  LDA must be at least  max( 1, n ), otherwise  LDA must
           be at least  max( 1, k ).
[in]BETA
          BETA is REAL
           On entry, BETA specifies the scalar beta.
[in,out]C
          C is REAL array, dimension ( LDC, N )
           Before entry  with  UPLO = 'U' or 'u',  the leading  n by n
           upper triangular part of the array C must contain the upper
           triangular part  of the  symmetric matrix  and the strictly
           lower triangular part of C is not referenced.  On exit, the
           upper triangular part of the array  C is overwritten by the
           upper triangular part of the updated matrix.
           Before entry  with  UPLO = 'L' or 'l',  the leading  n by n
           lower triangular part of the array C must contain the lower
           triangular part  of the  symmetric matrix  and the strictly
           upper triangular part of C is not referenced.  On exit, the
           lower triangular part of the array  C is overwritten by the
           lower triangular part of the updated matrix.
[in]LDC
          LDC is INTEGER
           On entry, LDC specifies the first dimension of C as declared
           in  the  calling  (sub)  program.   LDC  must  be  at  least
           max( 1, n ).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Level 3 Blas routine.

  -- Written on 8-February-1989.
     Jack Dongarra, Argonne National Laboratory.
     Iain Duff, AERE Harwell.
     Jeremy Du Croz, Numerical Algorithms Group Ltd.
     Sven Hammarling, Numerical Algorithms Group Ltd.

Definition at line 168 of file ssyrk.f.

169*
170* -- Reference BLAS level3 routine --
171* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
172* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
173*
174* .. Scalar Arguments ..
175 REAL ALPHA,BETA
176 INTEGER K,LDA,LDC,N
177 CHARACTER TRANS,UPLO
178* ..
179* .. Array Arguments ..
180 REAL A(LDA,*),C(LDC,*)
181* ..
182*
183* =====================================================================
184*
185* .. External Functions ..
186 LOGICAL LSAME
187 EXTERNAL lsame
188* ..
189* .. External Subroutines ..
190 EXTERNAL xerbla
191* ..
192* .. Intrinsic Functions ..
193 INTRINSIC max
194* ..
195* .. Local Scalars ..
196 REAL TEMP
197 INTEGER I,INFO,J,L,NROWA
198 LOGICAL UPPER
199* ..
200* .. Parameters ..
201 REAL ONE,ZERO
202 parameter(one=1.0e+0,zero=0.0e+0)
203* ..
204*
205* Test the input parameters.
206*
207 IF (lsame(trans,'N')) THEN
208 nrowa = n
209 ELSE
210 nrowa = k
211 END IF
212 upper = lsame(uplo,'U')
213*
214 info = 0
215 IF ((.NOT.upper) .AND. (.NOT.lsame(uplo,'L'))) THEN
216 info = 1
217 ELSE IF ((.NOT.lsame(trans,'N')) .AND.
218 + (.NOT.lsame(trans,'T')) .AND.
219 + (.NOT.lsame(trans,'C'))) THEN
220 info = 2
221 ELSE IF (n.LT.0) THEN
222 info = 3
223 ELSE IF (k.LT.0) THEN
224 info = 4
225 ELSE IF (lda.LT.max(1,nrowa)) THEN
226 info = 7
227 ELSE IF (ldc.LT.max(1,n)) THEN
228 info = 10
229 END IF
230 IF (info.NE.0) THEN
231 CALL xerbla('SSYRK ',info)
232 RETURN
233 END IF
234*
235* Quick return if possible.
236*
237 IF ((n.EQ.0) .OR. (((alpha.EQ.zero).OR.
238 + (k.EQ.0)).AND. (beta.EQ.one))) RETURN
239*
240* And when alpha.eq.zero.
241*
242 IF (alpha.EQ.zero) THEN
243 IF (upper) THEN
244 IF (beta.EQ.zero) THEN
245 DO 20 j = 1,n
246 DO 10 i = 1,j
247 c(i,j) = zero
248 10 CONTINUE
249 20 CONTINUE
250 ELSE
251 DO 40 j = 1,n
252 DO 30 i = 1,j
253 c(i,j) = beta*c(i,j)
254 30 CONTINUE
255 40 CONTINUE
256 END IF
257 ELSE
258 IF (beta.EQ.zero) THEN
259 DO 60 j = 1,n
260 DO 50 i = j,n
261 c(i,j) = zero
262 50 CONTINUE
263 60 CONTINUE
264 ELSE
265 DO 80 j = 1,n
266 DO 70 i = j,n
267 c(i,j) = beta*c(i,j)
268 70 CONTINUE
269 80 CONTINUE
270 END IF
271 END IF
272 RETURN
273 END IF
274*
275* Start the operations.
276*
277 IF (lsame(trans,'N')) THEN
278*
279* Form C := alpha*A*A**T + beta*C.
280*
281 IF (upper) THEN
282 DO 130 j = 1,n
283 IF (beta.EQ.zero) THEN
284 DO 90 i = 1,j
285 c(i,j) = zero
286 90 CONTINUE
287 ELSE IF (beta.NE.one) THEN
288 DO 100 i = 1,j
289 c(i,j) = beta*c(i,j)
290 100 CONTINUE
291 END IF
292 DO 120 l = 1,k
293 IF (a(j,l).NE.zero) THEN
294 temp = alpha*a(j,l)
295 DO 110 i = 1,j
296 c(i,j) = c(i,j) + temp*a(i,l)
297 110 CONTINUE
298 END IF
299 120 CONTINUE
300 130 CONTINUE
301 ELSE
302 DO 180 j = 1,n
303 IF (beta.EQ.zero) THEN
304 DO 140 i = j,n
305 c(i,j) = zero
306 140 CONTINUE
307 ELSE IF (beta.NE.one) THEN
308 DO 150 i = j,n
309 c(i,j) = beta*c(i,j)
310 150 CONTINUE
311 END IF
312 DO 170 l = 1,k
313 IF (a(j,l).NE.zero) THEN
314 temp = alpha*a(j,l)
315 DO 160 i = j,n
316 c(i,j) = c(i,j) + temp*a(i,l)
317 160 CONTINUE
318 END IF
319 170 CONTINUE
320 180 CONTINUE
321 END IF
322 ELSE
323*
324* Form C := alpha*A**T*A + beta*C.
325*
326 IF (upper) THEN
327 DO 210 j = 1,n
328 DO 200 i = 1,j
329 temp = zero
330 DO 190 l = 1,k
331 temp = temp + a(l,i)*a(l,j)
332 190 CONTINUE
333 IF (beta.EQ.zero) THEN
334 c(i,j) = alpha*temp
335 ELSE
336 c(i,j) = alpha*temp + beta*c(i,j)
337 END IF
338 200 CONTINUE
339 210 CONTINUE
340 ELSE
341 DO 240 j = 1,n
342 DO 230 i = j,n
343 temp = zero
344 DO 220 l = 1,k
345 temp = temp + a(l,i)*a(l,j)
346 220 CONTINUE
347 IF (beta.EQ.zero) THEN
348 c(i,j) = alpha*temp
349 ELSE
350 c(i,j) = alpha*temp + beta*c(i,j)
351 END IF
352 230 CONTINUE
353 240 CONTINUE
354 END IF
355 END IF
356*
357 RETURN
358*
359* End of SSYRK
360*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: