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