LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ctrmm()

subroutine ctrmm ( character  side,
character  uplo,
character  transa,
character  diag,
integer  m,
integer  n,
complex  alpha,
complex, dimension(lda,*)  a,
integer  lda,
complex, dimension(ldb,*)  b,
integer  ldb 
)

CTRMM

Purpose:
 CTRMM  performs one of the matrix-matrix operations

    B := alpha*op( A )*B,   or   B := alpha*B*op( A )

 where  alpha  is a scalar,  B  is an m by n matrix,  A  is a unit, or
 non-unit,  upper or lower triangular matrix  and  op( A )  is one  of

    op( A ) = A   or   op( A ) = A**T   or   op( A ) = A**H.
Parameters
[in]SIDE
          SIDE is CHARACTER*1
           On entry,  SIDE specifies whether  op( A ) multiplies B from
           the left or right as follows:

              SIDE = 'L' or 'l'   B := alpha*op( A )*B.

              SIDE = 'R' or 'r'   B := alpha*B*op( A ).
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the matrix A is an upper or
           lower triangular matrix as follows:

              UPLO = 'U' or 'u'   A is an upper triangular matrix.

              UPLO = 'L' or 'l'   A is a lower triangular matrix.
[in]TRANSA
          TRANSA is CHARACTER*1
           On entry, TRANSA specifies the form of op( A ) to be used in
           the matrix multiplication as follows:

              TRANSA = 'N' or 'n'   op( A ) = A.

              TRANSA = 'T' or 't'   op( A ) = A**T.

              TRANSA = 'C' or 'c'   op( A ) = A**H.
[in]DIAG
          DIAG is CHARACTER*1
           On entry, DIAG specifies whether or not A is unit triangular
           as follows:

              DIAG = 'U' or 'u'   A is assumed to be unit triangular.

              DIAG = 'N' or 'n'   A is not assumed to be unit
                                  triangular.
[in]M
          M is INTEGER
           On entry, M specifies the number of rows of B. M must be at
           least zero.
[in]N
          N is INTEGER
           On entry, N specifies the number of columns of B.  N must be
           at least zero.
[in]ALPHA
          ALPHA is COMPLEX
           On entry,  ALPHA specifies the scalar  alpha. When  alpha is
           zero then  A is not referenced and  B need not be set before
           entry.
[in]A
          A is COMPLEX array, dimension ( LDA, k ), where k is m
           when  SIDE = 'L' or 'l'  and is  n  when  SIDE = 'R' or 'r'.
           Before entry  with  UPLO = 'U' or 'u',  the  leading  k by k
           upper triangular part of the array  A must contain the upper
           triangular matrix  and the strictly lower triangular part of
           A is not referenced.
           Before entry  with  UPLO = 'L' or 'l',  the  leading  k by k
           lower triangular part of the array  A must contain the lower
           triangular matrix  and the strictly upper triangular part of
           A is not referenced.
           Note that when  DIAG = 'U' or 'u',  the diagonal elements of
           A  are not referenced either,  but are assumed to be  unity.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program.  When  SIDE = 'L' or 'l'  then
           LDA  must be at least  max( 1, m ),  when  SIDE = 'R' or 'r'
           then LDA must be at least max( 1, n ).
[in,out]B
          B is COMPLEX array, dimension ( LDB, N ).
           Before entry,  the leading  m by n part of the array  B must
           contain the matrix  B,  and  on exit  is overwritten  by the
           transformed matrix.
[in]LDB
          LDB is INTEGER
           On entry, LDB specifies the first dimension of B as declared
           in  the  calling  (sub)  program.   LDB  must  be  at  least
           max( 1, m ).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Level 3 Blas routine.

  -- Written on 8-February-1989.
     Jack Dongarra, Argonne National Laboratory.
     Iain Duff, AERE Harwell.
     Jeremy Du Croz, Numerical Algorithms Group Ltd.
     Sven Hammarling, Numerical Algorithms Group Ltd.

Definition at line 176 of file ctrmm.f.

177*
178* -- Reference BLAS level3 routine --
179* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
180* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
181*
182* .. Scalar Arguments ..
183 COMPLEX ALPHA
184 INTEGER LDA,LDB,M,N
185 CHARACTER DIAG,SIDE,TRANSA,UPLO
186* ..
187* .. Array Arguments ..
188 COMPLEX A(LDA,*),B(LDB,*)
189* ..
190*
191* =====================================================================
192*
193* .. External Functions ..
194 LOGICAL LSAME
195 EXTERNAL lsame
196* ..
197* .. External Subroutines ..
198 EXTERNAL xerbla
199* ..
200* .. Intrinsic Functions ..
201 INTRINSIC conjg,max
202* ..
203* .. Local Scalars ..
204 COMPLEX TEMP
205 INTEGER I,INFO,J,K,NROWA
206 LOGICAL LSIDE,NOCONJ,NOUNIT,UPPER
207* ..
208* .. Parameters ..
209 COMPLEX ONE
210 parameter(one= (1.0e+0,0.0e+0))
211 COMPLEX ZERO
212 parameter(zero= (0.0e+0,0.0e+0))
213* ..
214*
215* Test the input parameters.
216*
217 lside = lsame(side,'L')
218 IF (lside) THEN
219 nrowa = m
220 ELSE
221 nrowa = n
222 END IF
223 noconj = lsame(transa,'T')
224 nounit = lsame(diag,'N')
225 upper = lsame(uplo,'U')
226*
227 info = 0
228 IF ((.NOT.lside) .AND. (.NOT.lsame(side,'R'))) THEN
229 info = 1
230 ELSE IF ((.NOT.upper) .AND. (.NOT.lsame(uplo,'L'))) THEN
231 info = 2
232 ELSE IF ((.NOT.lsame(transa,'N')) .AND.
233 + (.NOT.lsame(transa,'T')) .AND.
234 + (.NOT.lsame(transa,'C'))) THEN
235 info = 3
236 ELSE IF ((.NOT.lsame(diag,'U')) .AND.
237 + (.NOT.lsame(diag,'N'))) THEN
238 info = 4
239 ELSE IF (m.LT.0) THEN
240 info = 5
241 ELSE IF (n.LT.0) THEN
242 info = 6
243 ELSE IF (lda.LT.max(1,nrowa)) THEN
244 info = 9
245 ELSE IF (ldb.LT.max(1,m)) THEN
246 info = 11
247 END IF
248 IF (info.NE.0) THEN
249 CALL xerbla('CTRMM ',info)
250 RETURN
251 END IF
252*
253* Quick return if possible.
254*
255 IF (m.EQ.0 .OR. n.EQ.0) RETURN
256*
257* And when alpha.eq.zero.
258*
259 IF (alpha.EQ.zero) THEN
260 DO 20 j = 1,n
261 DO 10 i = 1,m
262 b(i,j) = zero
263 10 CONTINUE
264 20 CONTINUE
265 RETURN
266 END IF
267*
268* Start the operations.
269*
270 IF (lside) THEN
271 IF (lsame(transa,'N')) THEN
272*
273* Form B := alpha*A*B.
274*
275 IF (upper) THEN
276 DO 50 j = 1,n
277 DO 40 k = 1,m
278 IF (b(k,j).NE.zero) THEN
279 temp = alpha*b(k,j)
280 DO 30 i = 1,k - 1
281 b(i,j) = b(i,j) + temp*a(i,k)
282 30 CONTINUE
283 IF (nounit) temp = temp*a(k,k)
284 b(k,j) = temp
285 END IF
286 40 CONTINUE
287 50 CONTINUE
288 ELSE
289 DO 80 j = 1,n
290 DO 70 k = m,1,-1
291 IF (b(k,j).NE.zero) THEN
292 temp = alpha*b(k,j)
293 b(k,j) = temp
294 IF (nounit) b(k,j) = b(k,j)*a(k,k)
295 DO 60 i = k + 1,m
296 b(i,j) = b(i,j) + temp*a(i,k)
297 60 CONTINUE
298 END IF
299 70 CONTINUE
300 80 CONTINUE
301 END IF
302 ELSE
303*
304* Form B := alpha*A**T*B or B := alpha*A**H*B.
305*
306 IF (upper) THEN
307 DO 120 j = 1,n
308 DO 110 i = m,1,-1
309 temp = b(i,j)
310 IF (noconj) THEN
311 IF (nounit) temp = temp*a(i,i)
312 DO 90 k = 1,i - 1
313 temp = temp + a(k,i)*b(k,j)
314 90 CONTINUE
315 ELSE
316 IF (nounit) temp = temp*conjg(a(i,i))
317 DO 100 k = 1,i - 1
318 temp = temp + conjg(a(k,i))*b(k,j)
319 100 CONTINUE
320 END IF
321 b(i,j) = alpha*temp
322 110 CONTINUE
323 120 CONTINUE
324 ELSE
325 DO 160 j = 1,n
326 DO 150 i = 1,m
327 temp = b(i,j)
328 IF (noconj) THEN
329 IF (nounit) temp = temp*a(i,i)
330 DO 130 k = i + 1,m
331 temp = temp + a(k,i)*b(k,j)
332 130 CONTINUE
333 ELSE
334 IF (nounit) temp = temp*conjg(a(i,i))
335 DO 140 k = i + 1,m
336 temp = temp + conjg(a(k,i))*b(k,j)
337 140 CONTINUE
338 END IF
339 b(i,j) = alpha*temp
340 150 CONTINUE
341 160 CONTINUE
342 END IF
343 END IF
344 ELSE
345 IF (lsame(transa,'N')) THEN
346*
347* Form B := alpha*B*A.
348*
349 IF (upper) THEN
350 DO 200 j = n,1,-1
351 temp = alpha
352 IF (nounit) temp = temp*a(j,j)
353 DO 170 i = 1,m
354 b(i,j) = temp*b(i,j)
355 170 CONTINUE
356 DO 190 k = 1,j - 1
357 IF (a(k,j).NE.zero) THEN
358 temp = alpha*a(k,j)
359 DO 180 i = 1,m
360 b(i,j) = b(i,j) + temp*b(i,k)
361 180 CONTINUE
362 END IF
363 190 CONTINUE
364 200 CONTINUE
365 ELSE
366 DO 240 j = 1,n
367 temp = alpha
368 IF (nounit) temp = temp*a(j,j)
369 DO 210 i = 1,m
370 b(i,j) = temp*b(i,j)
371 210 CONTINUE
372 DO 230 k = j + 1,n
373 IF (a(k,j).NE.zero) THEN
374 temp = alpha*a(k,j)
375 DO 220 i = 1,m
376 b(i,j) = b(i,j) + temp*b(i,k)
377 220 CONTINUE
378 END IF
379 230 CONTINUE
380 240 CONTINUE
381 END IF
382 ELSE
383*
384* Form B := alpha*B*A**T or B := alpha*B*A**H.
385*
386 IF (upper) THEN
387 DO 280 k = 1,n
388 DO 260 j = 1,k - 1
389 IF (a(j,k).NE.zero) THEN
390 IF (noconj) THEN
391 temp = alpha*a(j,k)
392 ELSE
393 temp = alpha*conjg(a(j,k))
394 END IF
395 DO 250 i = 1,m
396 b(i,j) = b(i,j) + temp*b(i,k)
397 250 CONTINUE
398 END IF
399 260 CONTINUE
400 temp = alpha
401 IF (nounit) THEN
402 IF (noconj) THEN
403 temp = temp*a(k,k)
404 ELSE
405 temp = temp*conjg(a(k,k))
406 END IF
407 END IF
408 IF (temp.NE.one) THEN
409 DO 270 i = 1,m
410 b(i,k) = temp*b(i,k)
411 270 CONTINUE
412 END IF
413 280 CONTINUE
414 ELSE
415 DO 320 k = n,1,-1
416 DO 300 j = k + 1,n
417 IF (a(j,k).NE.zero) THEN
418 IF (noconj) THEN
419 temp = alpha*a(j,k)
420 ELSE
421 temp = alpha*conjg(a(j,k))
422 END IF
423 DO 290 i = 1,m
424 b(i,j) = b(i,j) + temp*b(i,k)
425 290 CONTINUE
426 END IF
427 300 CONTINUE
428 temp = alpha
429 IF (nounit) THEN
430 IF (noconj) THEN
431 temp = temp*a(k,k)
432 ELSE
433 temp = temp*conjg(a(k,k))
434 END IF
435 END IF
436 IF (temp.NE.one) THEN
437 DO 310 i = 1,m
438 b(i,k) = temp*b(i,k)
439 310 CONTINUE
440 END IF
441 320 CONTINUE
442 END IF
443 END IF
444 END IF
445*
446 RETURN
447*
448* End of CTRMM
449*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: