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