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