LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 of 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 of 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.
Date
November 2011
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 171 of file ssyrk.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: