LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ctrmm.f
Go to the documentation of this file.
1 *> \brief \b CTRMM
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 CTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
12 *
13 * .. Scalar Arguments ..
14 * COMPLEX ALPHA
15 * INTEGER LDA,LDB,M,N
16 * CHARACTER DIAG,SIDE,TRANSA,UPLO
17 * ..
18 * .. Array Arguments ..
19 * COMPLEX A(LDA,*),B(LDB,*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> CTRMM performs one of the matrix-matrix operations
29 *>
30 *> B := alpha*op( A )*B, or B := alpha*B*op( A )
31 *>
32 *> where alpha is a scalar, B is an m by n matrix, A is a unit, or
33 *> non-unit, upper or lower triangular matrix and op( A ) is one of
34 *>
35 *> op( A ) = A or op( A ) = A**T or op( A ) = A**H.
36 *> \endverbatim
37 *
38 * Arguments:
39 * ==========
40 *
41 *> \param[in] SIDE
42 *> \verbatim
43 *> SIDE is CHARACTER*1
44 *> On entry, SIDE specifies whether op( A ) multiplies B from
45 *> the left or right as follows:
46 *>
47 *> SIDE = 'L' or 'l' B := alpha*op( A )*B.
48 *>
49 *> SIDE = 'R' or 'r' B := alpha*B*op( A ).
50 *> \endverbatim
51 *>
52 *> \param[in] UPLO
53 *> \verbatim
54 *> UPLO is CHARACTER*1
55 *> On entry, UPLO specifies whether the matrix A is an upper or
56 *> lower triangular matrix as follows:
57 *>
58 *> UPLO = 'U' or 'u' A is an upper triangular matrix.
59 *>
60 *> UPLO = 'L' or 'l' A is a lower triangular matrix.
61 *> \endverbatim
62 *>
63 *> \param[in] TRANSA
64 *> \verbatim
65 *> TRANSA is CHARACTER*1
66 *> On entry, TRANSA specifies the form of op( A ) to be used in
67 *> the matrix multiplication as follows:
68 *>
69 *> TRANSA = 'N' or 'n' op( A ) = A.
70 *>
71 *> TRANSA = 'T' or 't' op( A ) = A**T.
72 *>
73 *> TRANSA = 'C' or 'c' op( A ) = A**H.
74 *> \endverbatim
75 *>
76 *> \param[in] DIAG
77 *> \verbatim
78 *> DIAG is CHARACTER*1
79 *> On entry, DIAG specifies whether or not A is unit triangular
80 *> as follows:
81 *>
82 *> DIAG = 'U' or 'u' A is assumed to be unit triangular.
83 *>
84 *> DIAG = 'N' or 'n' A is not assumed to be unit
85 *> triangular.
86 *> \endverbatim
87 *>
88 *> \param[in] M
89 *> \verbatim
90 *> M is INTEGER
91 *> On entry, M specifies the number of rows of B. M must be at
92 *> least zero.
93 *> \endverbatim
94 *>
95 *> \param[in] N
96 *> \verbatim
97 *> N is INTEGER
98 *> On entry, N specifies the number of columns of B. N must be
99 *> at least zero.
100 *> \endverbatim
101 *>
102 *> \param[in] ALPHA
103 *> \verbatim
104 *> ALPHA is COMPLEX
105 *> On entry, ALPHA specifies the scalar alpha. When alpha is
106 *> zero then A is not referenced and B need not be set before
107 *> entry.
108 *> \endverbatim
109 *>
110 *> \param[in] A
111 *> \verbatim
112 *> A is COMPLEX array of DIMENSION ( LDA, k ), where k is m
113 *> when SIDE = 'L' or 'l' and is n when SIDE = 'R' or 'r'.
114 *> Before entry with UPLO = 'U' or 'u', the leading k by k
115 *> upper triangular part of the array A must contain the upper
116 *> triangular matrix and the strictly lower triangular part of
117 *> A is not referenced.
118 *> Before entry with UPLO = 'L' or 'l', the leading k by k
119 *> lower triangular part of the array A must contain the lower
120 *> triangular matrix and the strictly upper triangular part of
121 *> A is not referenced.
122 *> Note that when DIAG = 'U' or 'u', the diagonal elements of
123 *> A are not referenced either, but are assumed to be unity.
124 *> \endverbatim
125 *>
126 *> \param[in] LDA
127 *> \verbatim
128 *> LDA is INTEGER
129 *> On entry, LDA specifies the first dimension of A as declared
130 *> in the calling (sub) program. When SIDE = 'L' or 'l' then
131 *> LDA must be at least max( 1, m ), when SIDE = 'R' or 'r'
132 *> then LDA must be at least max( 1, n ).
133 *> \endverbatim
134 *>
135 *> \param[in,out] B
136 *> \verbatim
137 *> B is COMPLEX array of DIMENSION ( LDB, n ).
138 *> Before entry, the leading m by n part of the array B must
139 *> contain the matrix B, and on exit is overwritten by the
140 *> transformed matrix.
141 *> \endverbatim
142 *>
143 *> \param[in] LDB
144 *> \verbatim
145 *> LDB is INTEGER
146 *> On entry, LDB specifies the first dimension of B as declared
147 *> in the calling (sub) program. LDB must be at least
148 *> max( 1, m ).
149 *> \endverbatim
150 *
151 * Authors:
152 * ========
153 *
154 *> \author Univ. of Tennessee
155 *> \author Univ. of California Berkeley
156 *> \author Univ. of Colorado Denver
157 *> \author NAG Ltd.
158 *
159 *> \date November 2011
160 *
161 *> \ingroup complex_blas_level3
162 *
163 *> \par Further Details:
164 * =====================
165 *>
166 *> \verbatim
167 *>
168 *> Level 3 Blas routine.
169 *>
170 *> -- Written on 8-February-1989.
171 *> Jack Dongarra, Argonne National Laboratory.
172 *> Iain Duff, AERE Harwell.
173 *> Jeremy Du Croz, Numerical Algorithms Group Ltd.
174 *> Sven Hammarling, Numerical Algorithms Group Ltd.
175 *> \endverbatim
176 *>
177 * =====================================================================
178  SUBROUTINE ctrmm(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB)
179 *
180 * -- Reference BLAS level3 routine (version 3.4.0) --
181 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
182 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
183 * November 2011
184 *
185 * .. Scalar Arguments ..
186  COMPLEX alpha
187  INTEGER lda,ldb,m,n
188  CHARACTER diag,side,transa,uplo
189 * ..
190 * .. Array Arguments ..
191  COMPLEX a(lda,*),b(ldb,*)
192 * ..
193 *
194 * =====================================================================
195 *
196 * .. External Functions ..
197  LOGICAL lsame
198  EXTERNAL lsame
199 * ..
200 * .. External Subroutines ..
201  EXTERNAL xerbla
202 * ..
203 * .. Intrinsic Functions ..
204  INTRINSIC conjg,max
205 * ..
206 * .. Local Scalars ..
207  COMPLEX temp
208  INTEGER i,info,j,k,nrowa
209  LOGICAL lside,noconj,nounit,upper
210 * ..
211 * .. Parameters ..
212  COMPLEX one
213  parameter(one= (1.0e+0,0.0e+0))
214  COMPLEX zero
215  parameter(zero= (0.0e+0,0.0e+0))
216 * ..
217 *
218 * Test the input parameters.
219 *
220  lside = lsame(side,'L')
221  IF (lside) THEN
222  nrowa = m
223  ELSE
224  nrowa = n
225  END IF
226  noconj = lsame(transa,'T')
227  nounit = lsame(diag,'N')
228  upper = lsame(uplo,'U')
229 *
230  info = 0
231  IF ((.NOT.lside) .AND. (.NOT.lsame(side,'R'))) THEN
232  info = 1
233  ELSE IF ((.NOT.upper) .AND. (.NOT.lsame(uplo,'L'))) THEN
234  info = 2
235  ELSE IF ((.NOT.lsame(transa,'N')) .AND.
236  + (.NOT.lsame(transa,'T')) .AND.
237  + (.NOT.lsame(transa,'C'))) THEN
238  info = 3
239  ELSE IF ((.NOT.lsame(diag,'U')) .AND. (.NOT.lsame(diag,'N'))) THEN
240  info = 4
241  ELSE IF (m.LT.0) THEN
242  info = 5
243  ELSE IF (n.LT.0) THEN
244  info = 6
245  ELSE IF (lda.LT.max(1,nrowa)) THEN
246  info = 9
247  ELSE IF (ldb.LT.max(1,m)) THEN
248  info = 11
249  END IF
250  IF (info.NE.0) THEN
251  CALL xerbla('CTRMM ',info)
252  return
253  END IF
254 *
255 * Quick return if possible.
256 *
257  IF (m.EQ.0 .OR. n.EQ.0) return
258 *
259 * And when alpha.eq.zero.
260 *
261  IF (alpha.EQ.zero) THEN
262  DO 20 j = 1,n
263  DO 10 i = 1,m
264  b(i,j) = zero
265  10 continue
266  20 continue
267  return
268  END IF
269 *
270 * Start the operations.
271 *
272  IF (lside) THEN
273  IF (lsame(transa,'N')) THEN
274 *
275 * Form B := alpha*A*B.
276 *
277  IF (upper) THEN
278  DO 50 j = 1,n
279  DO 40 k = 1,m
280  IF (b(k,j).NE.zero) THEN
281  temp = alpha*b(k,j)
282  DO 30 i = 1,k - 1
283  b(i,j) = b(i,j) + temp*a(i,k)
284  30 continue
285  IF (nounit) temp = temp*a(k,k)
286  b(k,j) = temp
287  END IF
288  40 continue
289  50 continue
290  ELSE
291  DO 80 j = 1,n
292  DO 70 k = m,1,-1
293  IF (b(k,j).NE.zero) THEN
294  temp = alpha*b(k,j)
295  b(k,j) = temp
296  IF (nounit) b(k,j) = b(k,j)*a(k,k)
297  DO 60 i = k + 1,m
298  b(i,j) = b(i,j) + temp*a(i,k)
299  60 continue
300  END IF
301  70 continue
302  80 continue
303  END IF
304  ELSE
305 *
306 * Form B := alpha*A**T*B or B := alpha*A**H*B.
307 *
308  IF (upper) THEN
309  DO 120 j = 1,n
310  DO 110 i = m,1,-1
311  temp = b(i,j)
312  IF (noconj) THEN
313  IF (nounit) temp = temp*a(i,i)
314  DO 90 k = 1,i - 1
315  temp = temp + a(k,i)*b(k,j)
316  90 continue
317  ELSE
318  IF (nounit) temp = temp*conjg(a(i,i))
319  DO 100 k = 1,i - 1
320  temp = temp + conjg(a(k,i))*b(k,j)
321  100 continue
322  END IF
323  b(i,j) = alpha*temp
324  110 continue
325  120 continue
326  ELSE
327  DO 160 j = 1,n
328  DO 150 i = 1,m
329  temp = b(i,j)
330  IF (noconj) THEN
331  IF (nounit) temp = temp*a(i,i)
332  DO 130 k = i + 1,m
333  temp = temp + a(k,i)*b(k,j)
334  130 continue
335  ELSE
336  IF (nounit) temp = temp*conjg(a(i,i))
337  DO 140 k = i + 1,m
338  temp = temp + conjg(a(k,i))*b(k,j)
339  140 continue
340  END IF
341  b(i,j) = alpha*temp
342  150 continue
343  160 continue
344  END IF
345  END IF
346  ELSE
347  IF (lsame(transa,'N')) THEN
348 *
349 * Form B := alpha*B*A.
350 *
351  IF (upper) THEN
352  DO 200 j = n,1,-1
353  temp = alpha
354  IF (nounit) temp = temp*a(j,j)
355  DO 170 i = 1,m
356  b(i,j) = temp*b(i,j)
357  170 continue
358  DO 190 k = 1,j - 1
359  IF (a(k,j).NE.zero) THEN
360  temp = alpha*a(k,j)
361  DO 180 i = 1,m
362  b(i,j) = b(i,j) + temp*b(i,k)
363  180 continue
364  END IF
365  190 continue
366  200 continue
367  ELSE
368  DO 240 j = 1,n
369  temp = alpha
370  IF (nounit) temp = temp*a(j,j)
371  DO 210 i = 1,m
372  b(i,j) = temp*b(i,j)
373  210 continue
374  DO 230 k = j + 1,n
375  IF (a(k,j).NE.zero) THEN
376  temp = alpha*a(k,j)
377  DO 220 i = 1,m
378  b(i,j) = b(i,j) + temp*b(i,k)
379  220 continue
380  END IF
381  230 continue
382  240 continue
383  END IF
384  ELSE
385 *
386 * Form B := alpha*B*A**T or B := alpha*B*A**H.
387 *
388  IF (upper) THEN
389  DO 280 k = 1,n
390  DO 260 j = 1,k - 1
391  IF (a(j,k).NE.zero) THEN
392  IF (noconj) THEN
393  temp = alpha*a(j,k)
394  ELSE
395  temp = alpha*conjg(a(j,k))
396  END IF
397  DO 250 i = 1,m
398  b(i,j) = b(i,j) + temp*b(i,k)
399  250 continue
400  END IF
401  260 continue
402  temp = alpha
403  IF (nounit) THEN
404  IF (noconj) THEN
405  temp = temp*a(k,k)
406  ELSE
407  temp = temp*conjg(a(k,k))
408  END IF
409  END IF
410  IF (temp.NE.one) THEN
411  DO 270 i = 1,m
412  b(i,k) = temp*b(i,k)
413  270 continue
414  END IF
415  280 continue
416  ELSE
417  DO 320 k = n,1,-1
418  DO 300 j = k + 1,n
419  IF (a(j,k).NE.zero) THEN
420  IF (noconj) THEN
421  temp = alpha*a(j,k)
422  ELSE
423  temp = alpha*conjg(a(j,k))
424  END IF
425  DO 290 i = 1,m
426  b(i,j) = b(i,j) + temp*b(i,k)
427  290 continue
428  END IF
429  300 continue
430  temp = alpha
431  IF (nounit) THEN
432  IF (noconj) THEN
433  temp = temp*a(k,k)
434  ELSE
435  temp = temp*conjg(a(k,k))
436  END IF
437  END IF
438  IF (temp.NE.one) THEN
439  DO 310 i = 1,m
440  b(i,k) = temp*b(i,k)
441  310 continue
442  END IF
443  320 continue
444  END IF
445  END IF
446  END IF
447 *
448  return
449 *
450 * End of CTRMM .
451 *
452  END