LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ssyrk.f
Go to the documentation of this file.
1 *> \brief \b SSYRK
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE SSYRK(UPLO,TRANS,N,K,ALPHA,A,LDA,BETA,C,LDC)
12 *
13 * .. Scalar Arguments ..
14 * REAL ALPHA,BETA
15 * INTEGER K,LDA,LDC,N
16 * CHARACTER TRANS,UPLO
17 * ..
18 * .. Array Arguments ..
19 * REAL A(LDA,*),C(LDC,*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> SSYRK performs one of the symmetric rank k operations
29 *>
30 *> C := alpha*A*A**T + beta*C,
31 *>
32 *> or
33 *>
34 *> C := alpha*A**T*A + beta*C,
35 *>
36 *> where alpha and beta are scalars, C is an n by n symmetric matrix
37 *> and A is an n by k matrix in the first case and a k by n matrix
38 *> in the second case.
39 *> \endverbatim
40 *
41 * Arguments:
42 * ==========
43 *
44 *> \param[in] UPLO
45 *> \verbatim
46 *> UPLO is CHARACTER*1
47 *> On entry, UPLO specifies whether the upper or lower
48 *> triangular part of the array C is to be referenced as
49 *> follows:
50 *>
51 *> UPLO = 'U' or 'u' Only the upper triangular part of C
52 *> is to be referenced.
53 *>
54 *> UPLO = 'L' or 'l' Only the lower triangular part of C
55 *> is to be referenced.
56 *> \endverbatim
57 *>
58 *> \param[in] TRANS
59 *> \verbatim
60 *> TRANS is CHARACTER*1
61 *> On entry, TRANS specifies the operation to be performed as
62 *> follows:
63 *>
64 *> TRANS = 'N' or 'n' C := alpha*A*A**T + beta*C.
65 *>
66 *> TRANS = 'T' or 't' C := alpha*A**T*A + beta*C.
67 *>
68 *> TRANS = 'C' or 'c' C := alpha*A**T*A + beta*C.
69 *> \endverbatim
70 *>
71 *> \param[in] N
72 *> \verbatim
73 *> N is INTEGER
74 *> On entry, N specifies the order of the matrix C. N must be
75 *> at least zero.
76 *> \endverbatim
77 *>
78 *> \param[in] K
79 *> \verbatim
80 *> K is INTEGER
81 *> On entry with TRANS = 'N' or 'n', K specifies the number
82 *> of columns of the matrix A, and on entry with
83 *> TRANS = 'T' or 't' or 'C' or 'c', K specifies the number
84 *> of rows of the matrix A. K must be at least zero.
85 *> \endverbatim
86 *>
87 *> \param[in] ALPHA
88 *> \verbatim
89 *> ALPHA is REAL
90 *> On entry, ALPHA specifies the scalar alpha.
91 *> \endverbatim
92 *>
93 *> \param[in] A
94 *> \verbatim
95 *> A is REAL array of DIMENSION ( LDA, ka ), where ka is
96 *> k when TRANS = 'N' or 'n', and is n otherwise.
97 *> Before entry with TRANS = 'N' or 'n', the leading n by k
98 *> part of the array A must contain the matrix A, otherwise
99 *> the leading k by n part of the array A must contain the
100 *> matrix A.
101 *> \endverbatim
102 *>
103 *> \param[in] LDA
104 *> \verbatim
105 *> LDA is INTEGER
106 *> On entry, LDA specifies the first dimension of A as declared
107 *> in the calling (sub) program. When TRANS = 'N' or 'n'
108 *> then LDA must be at least max( 1, n ), otherwise LDA must
109 *> be at least max( 1, k ).
110 *> \endverbatim
111 *>
112 *> \param[in] BETA
113 *> \verbatim
114 *> BETA is REAL
115 *> On entry, BETA specifies the scalar beta.
116 *> \endverbatim
117 *>
118 *> \param[in,out] C
119 *> \verbatim
120 *> C is REAL array of DIMENSION ( LDC, n ).
121 *> Before entry with UPLO = 'U' or 'u', the leading n by n
122 *> upper triangular part of the array C must contain the upper
123 *> triangular part of the symmetric matrix and the strictly
124 *> lower triangular part of C is not referenced. On exit, the
125 *> upper triangular part of the array C is overwritten by the
126 *> upper triangular part of the updated matrix.
127 *> Before entry with UPLO = 'L' or 'l', the leading n by n
128 *> lower triangular part of the array C must contain the lower
129 *> triangular part of the symmetric matrix and the strictly
130 *> upper triangular part of C is not referenced. On exit, the
131 *> lower triangular part of the array C is overwritten by the
132 *> lower triangular part of the updated matrix.
133 *> \endverbatim
134 *>
135 *> \param[in] LDC
136 *> \verbatim
137 *> LDC is INTEGER
138 *> On entry, LDC specifies the first dimension of C as declared
139 *> in the calling (sub) program. LDC must be at least
140 *> max( 1, n ).
141 *> \endverbatim
142 *
143 * Authors:
144 * ========
145 *
146 *> \author Univ. of Tennessee
147 *> \author Univ. of California Berkeley
148 *> \author Univ. of Colorado Denver
149 *> \author NAG Ltd.
150 *
151 *> \date November 2011
152 *
153 *> \ingroup single_blas_level3
154 *
155 *> \par Further Details:
156 * =====================
157 *>
158 *> \verbatim
159 *>
160 *> Level 3 Blas routine.
161 *>
162 *> -- Written on 8-February-1989.
163 *> Jack Dongarra, Argonne National Laboratory.
164 *> Iain Duff, AERE Harwell.
165 *> Jeremy Du Croz, Numerical Algorithms Group Ltd.
166 *> Sven Hammarling, Numerical Algorithms Group Ltd.
167 *> \endverbatim
168 *>
169 * =====================================================================
170  SUBROUTINE ssyrk(UPLO,TRANS,N,K,ALPHA,A,LDA,BETA,C,LDC)
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 *
364  END