LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
csyrk.f
Go to the documentation of this file.
1 *> \brief \b CSYRK
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 CSYRK(UPLO,TRANS,N,K,ALPHA,A,LDA,BETA,C,LDC)
12 *
13 * .. Scalar Arguments ..
14 * COMPLEX ALPHA,BETA
15 * INTEGER K,LDA,LDC,N
16 * CHARACTER TRANS,UPLO
17 * ..
18 * .. Array Arguments ..
19 * COMPLEX A(LDA,*),C(LDC,*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> CSYRK 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 *> \endverbatim
68 *>
69 *> \param[in] N
70 *> \verbatim
71 *> N is INTEGER
72 *> On entry, N specifies the order of the matrix C. N must be
73 *> at least zero.
74 *> \endverbatim
75 *>
76 *> \param[in] K
77 *> \verbatim
78 *> K is INTEGER
79 *> On entry with TRANS = 'N' or 'n', K specifies the number
80 *> of columns of the matrix A, and on entry with
81 *> TRANS = 'T' or 't', K specifies the number of rows of the
82 *> matrix A. K must be at least zero.
83 *> \endverbatim
84 *>
85 *> \param[in] ALPHA
86 *> \verbatim
87 *> ALPHA is COMPLEX
88 *> On entry, ALPHA specifies the scalar alpha.
89 *> \endverbatim
90 *>
91 *> \param[in] A
92 *> \verbatim
93 *> A is COMPLEX array of DIMENSION ( LDA, ka ), where ka is
94 *> k when TRANS = 'N' or 'n', and is n otherwise.
95 *> Before entry with TRANS = 'N' or 'n', the leading n by k
96 *> part of the array A must contain the matrix A, otherwise
97 *> the leading k by n part of the array A must contain the
98 *> matrix A.
99 *> \endverbatim
100 *>
101 *> \param[in] LDA
102 *> \verbatim
103 *> LDA is INTEGER
104 *> On entry, LDA specifies the first dimension of A as declared
105 *> in the calling (sub) program. When TRANS = 'N' or 'n'
106 *> then LDA must be at least max( 1, n ), otherwise LDA must
107 *> be at least max( 1, k ).
108 *> \endverbatim
109 *>
110 *> \param[in] BETA
111 *> \verbatim
112 *> BETA is COMPLEX
113 *> On entry, BETA specifies the scalar beta.
114 *> \endverbatim
115 *>
116 *> \param[in,out] C
117 *> \verbatim
118 *> C is COMPLEX array of DIMENSION ( LDC, n ).
119 *> Before entry with UPLO = 'U' or 'u', the leading n by n
120 *> upper triangular part of the array C must contain the upper
121 *> triangular part of the symmetric matrix and the strictly
122 *> lower triangular part of C is not referenced. On exit, the
123 *> upper triangular part of the array C is overwritten by the
124 *> upper triangular part of the updated matrix.
125 *> Before entry with UPLO = 'L' or 'l', the leading n by n
126 *> lower triangular part of the array C must contain the lower
127 *> triangular part of the symmetric matrix and the strictly
128 *> upper triangular part of C is not referenced. On exit, the
129 *> lower triangular part of the array C is overwritten by the
130 *> lower triangular part of the updated matrix.
131 *> \endverbatim
132 *>
133 *> \param[in] LDC
134 *> \verbatim
135 *> LDC is INTEGER
136 *> On entry, LDC specifies the first dimension of C as declared
137 *> in the calling (sub) program. LDC must be at least
138 *> max( 1, n ).
139 *> \endverbatim
140 *
141 * Authors:
142 * ========
143 *
144 *> \author Univ. of Tennessee
145 *> \author Univ. of California Berkeley
146 *> \author Univ. of Colorado Denver
147 *> \author NAG Ltd.
148 *
149 *> \date November 2011
150 *
151 *> \ingroup complex_blas_level3
152 *
153 *> \par Further Details:
154 * =====================
155 *>
156 *> \verbatim
157 *>
158 *> Level 3 Blas routine.
159 *>
160 *> -- Written on 8-February-1989.
161 *> Jack Dongarra, Argonne National Laboratory.
162 *> Iain Duff, AERE Harwell.
163 *> Jeremy Du Croz, Numerical Algorithms Group Ltd.
164 *> Sven Hammarling, Numerical Algorithms Group Ltd.
165 *> \endverbatim
166 *>
167 * =====================================================================
168  SUBROUTINE csyrk(UPLO,TRANS,N,K,ALPHA,A,LDA,BETA,C,LDC)
169 *
170 * -- Reference BLAS level3 routine (version 3.4.0) --
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 * November 2011
174 *
175 * .. Scalar Arguments ..
176  COMPLEX alpha,beta
177  INTEGER k,lda,ldc,n
178  CHARACTER trans,uplo
179 * ..
180 * .. Array Arguments ..
181  COMPLEX a(lda,*),c(ldc,*)
182 * ..
183 *
184 * =====================================================================
185 *
186 * .. External Functions ..
187  LOGICAL lsame
188  EXTERNAL lsame
189 * ..
190 * .. External Subroutines ..
191  EXTERNAL xerbla
192 * ..
193 * .. Intrinsic Functions ..
194  INTRINSIC max
195 * ..
196 * .. Local Scalars ..
197  COMPLEX temp
198  INTEGER i,info,j,l,nrowa
199  LOGICAL upper
200 * ..
201 * .. Parameters ..
202  COMPLEX one
203  parameter(one= (1.0e+0,0.0e+0))
204  COMPLEX zero
205  parameter(zero= (0.0e+0,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'))) THEN
222  info = 2
223  ELSE IF (n.LT.0) THEN
224  info = 3
225  ELSE IF (k.LT.0) THEN
226  info = 4
227  ELSE IF (lda.LT.max(1,nrowa)) THEN
228  info = 7
229  ELSE IF (ldc.LT.max(1,n)) THEN
230  info = 10
231  END IF
232  IF (info.NE.0) THEN
233  CALL xerbla('CSYRK ',info)
234  return
235  END IF
236 *
237 * Quick return if possible.
238 *
239  IF ((n.EQ.0) .OR. (((alpha.EQ.zero).OR.
240  + (k.EQ.0)).AND. (beta.EQ.one))) return
241 *
242 * And when alpha.eq.zero.
243 *
244  IF (alpha.EQ.zero) THEN
245  IF (upper) THEN
246  IF (beta.EQ.zero) THEN
247  DO 20 j = 1,n
248  DO 10 i = 1,j
249  c(i,j) = zero
250  10 continue
251  20 continue
252  ELSE
253  DO 40 j = 1,n
254  DO 30 i = 1,j
255  c(i,j) = beta*c(i,j)
256  30 continue
257  40 continue
258  END IF
259  ELSE
260  IF (beta.EQ.zero) THEN
261  DO 60 j = 1,n
262  DO 50 i = j,n
263  c(i,j) = zero
264  50 continue
265  60 continue
266  ELSE
267  DO 80 j = 1,n
268  DO 70 i = j,n
269  c(i,j) = beta*c(i,j)
270  70 continue
271  80 continue
272  END IF
273  END IF
274  return
275  END IF
276 *
277 * Start the operations.
278 *
279  IF (lsame(trans,'N')) THEN
280 *
281 * Form C := alpha*A*A**T + beta*C.
282 *
283  IF (upper) THEN
284  DO 130 j = 1,n
285  IF (beta.EQ.zero) THEN
286  DO 90 i = 1,j
287  c(i,j) = zero
288  90 continue
289  ELSE IF (beta.NE.one) THEN
290  DO 100 i = 1,j
291  c(i,j) = beta*c(i,j)
292  100 continue
293  END IF
294  DO 120 l = 1,k
295  IF (a(j,l).NE.zero) THEN
296  temp = alpha*a(j,l)
297  DO 110 i = 1,j
298  c(i,j) = c(i,j) + temp*a(i,l)
299  110 continue
300  END IF
301  120 continue
302  130 continue
303  ELSE
304  DO 180 j = 1,n
305  IF (beta.EQ.zero) THEN
306  DO 140 i = j,n
307  c(i,j) = zero
308  140 continue
309  ELSE IF (beta.NE.one) THEN
310  DO 150 i = j,n
311  c(i,j) = beta*c(i,j)
312  150 continue
313  END IF
314  DO 170 l = 1,k
315  IF (a(j,l).NE.zero) THEN
316  temp = alpha*a(j,l)
317  DO 160 i = j,n
318  c(i,j) = c(i,j) + temp*a(i,l)
319  160 continue
320  END IF
321  170 continue
322  180 continue
323  END IF
324  ELSE
325 *
326 * Form C := alpha*A**T*A + beta*C.
327 *
328  IF (upper) THEN
329  DO 210 j = 1,n
330  DO 200 i = 1,j
331  temp = zero
332  DO 190 l = 1,k
333  temp = temp + a(l,i)*a(l,j)
334  190 continue
335  IF (beta.EQ.zero) THEN
336  c(i,j) = alpha*temp
337  ELSE
338  c(i,j) = alpha*temp + beta*c(i,j)
339  END IF
340  200 continue
341  210 continue
342  ELSE
343  DO 240 j = 1,n
344  DO 230 i = j,n
345  temp = zero
346  DO 220 l = 1,k
347  temp = temp + a(l,i)*a(l,j)
348  220 continue
349  IF (beta.EQ.zero) THEN
350  c(i,j) = alpha*temp
351  ELSE
352  c(i,j) = alpha*temp + beta*c(i,j)
353  END IF
354  230 continue
355  240 continue
356  END IF
357  END IF
358 *
359  return
360 *
361 * End of CSYRK .
362 *
363  END