*nix Documentation Project
·  Home
 +   man pages
·  Linux HOWTOs
·  FreeBSD Tips
·  *niX Forums

  man pages->IRIX man pages -> libblas/trsm (3)              
Title
Content
Arch
Section
 

Contents


_TRSM(3F)							     _TRSM(3F)


NAME    [Toc]    [Back]

     dtrsm, strsm, ztrsm, ctrsm	- BLAS level three Solution of Systems of
     Equations


FORTRAN	77 SYNOPSIS
     subroutine	dtrsm( side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb )
	   character*1	      side,uplo,transa,diag
	   integer	      m, n, lda, ldb
	   double precision   alpha
	   double precision   a( lda,*), b(ldb,*)

     subroutine	strsm( side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb )
	   character*1	      side,uplo,transa,diag
	   integer	      m, n, lda, ldb
	   real		      alpha
	   real		      a( lda,*), b(ldb,*)

     subroutine	ztrsm( side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb )
	   character*1	      side,uplo,transa,diag
	   integer	      m, n, lda, ldb
	   double complex     alpha
	   double complex     a( lda,*), b(ldb,*)

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

C SYNOPSIS    [Toc]    [Back]

     void dtrsm( side, uplo, transa, diag, m, n, alpha,	a, lda,	b, ldb )
	   OperationSide	 side;
	   MatrixTriangle	 uplo;
	   MatrixTranspose	 transa;
	   MatrixUnitTriangular	 diag;
	   Integer		 m, n, tda, tdb;
	   double		 alpha;
	   double		 (*a)[lda*k], (*b)[lda*n];

     void strsm( side, uplo, transa, diag, m, n, alpha,	a, lda,	b, ldb )
	   OperationSide	 side;
	   MatrixTriangle	 uplo;
	   MatrixTranspose	 transa;
	   MatrixUnitTriangular	 diag;
	   Integer		 m, n, lda, ldb;
	   float		 alpha;
	   float		 (*a)[lda*k], (*b)[lda*n];

     void ztrsm( side, uplo, transa, diag, m, n, alpha,	a, lda,	b, ldb )
	   OperationSide	 side;



									Page 1






_TRSM(3F)							     _TRSM(3F)



	   MatrixTriangle	 uplo;
	   MatrixTranspose	 transa;
	   MatrixUnitTriangular	 diag;
	   Integer		 m, n, lda, ldb;
	   Zomplex		 alpha;
	   Zomplex		 (*a)[lda*k], (*b)[lda*n];

     void ctrsm( side, uplo, transa, diag, m, n, alpha,	a, lda,	b, ldb )
	   OperationSide	 side;
	   MatrixTriangle	 uplo;
	   MatrixTranspose	 transa;
	   MatrixUnitTriangular	 diag;
	   Integer		 m, n, lda, ldb;
	   Complex		 alpha;
	   Complex		 (*a)[lda*k], (*b)[lda*n];


DESCRIPTION    [Toc]    [Back]

     dtrsm, strsm, ztrsm and ctrsm solve one of	the matrix equations

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

     where alpha is a scalar, X	and B are m by n matrices, 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'   or	  op( A	) = conjg( A' ).

     The matrix	X is overwritten on B.

PARAMETERS    [Toc]    [Back]

     side    On	entry, side specifies whether op( A ) appears on the left or
	     right of X	as follows:


		     FORTRAN
		     side = 'L'	or 'l'	     op( A )*X = alpha*B.
		     side = 'R'	or 'r'	     X*op( A ) = alpha*B.

		     C
		     side = LeftSide	   op( A )*X = alpha*B.
		     side = RightSide	     X*op( A ) = alpha*B.

	     Unchanged on exit.

     uplo    On	entry, uplo specifies whether the matrix A is an upper or
	     lower triangular matrix as	follows:


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



									Page 2






_TRSM(3F)							     _TRSM(3F)



		     uplo = 'L'	or 'l'	     A is a lower triangular matrix.

		     C
		     uplo = UpperTriangle    A is an upper triangular matrix.
		     uplo = LowerTriangle    A is a lower triangular matrix.

	     Unchanged on exit.

     transa  On	entry, transa specifies	the form of op(	A ) to be used in the
	     matrix multiplication as follows:

		  FORTRAN
		  transa = 'N' or 'n'	   op( A ) = A.
		  transa = 'T' or 't'	   op( A ) = A'.
		  transa = 'C' or 'c'	   op( A ) = conjg( A' ).

		  C
		  transa = NoTranspose		op( A )	= A.
		  transa = Transpose		op( A )	= A'.
		  transa = ConjugateTranspose	op( A )	= conjg( A' ).

	     Unchanged on exit.

     diag    On	entry, diag specifies whether or not A is unit triangular as
	     follows:

		  FORTRAN
		  diag = 'U' or	'u'   A	is assumed to be unit
				      triangular.
		  diag = 'N' or	'n'   A	is not assumed to be unit
				      triangular.

		  C
		  diag = UnitTriangular	   A is	assumed	to be unit
					   triangular.
		  diag = NotUnitTriangular A is	not assumed to be unit
					   triangular.

	     Unchanged on exit.

     m	     On	entry, m specifies the number of rows of B. m must be at least
	     zero.
	     Unchanged on exit.

     n	     On	entry, n specifies the number of columns of B.	n must be at
	     least zero.
	     Unchanged on exit.

     alpha   On	entry, alpha specifies the scalar alpha. When alpha is zero
	     then a is not referenced and b need not be	set before entry.
	     Unchanged on exit.




									Page 3






_TRSM(3F)							     _TRSM(3F)



     a	     An	array containing the matrix A.

	     FORTRAN
	     Array of dimension	(lda, k).

	     C
	     A pointer to an array of size lda*k.
	     See note below about array	storage	convention for C.

	     k is m when side =	'L' or 'l' or LeftSide and is n	when side =
	     'R' or 'r'	or RightSide.

	     Before entry with uplo = 'U' or 'u' or , the elements
	     corresponding to the leading  k by	k upper	triangular elements of
	     the matrix	A must contain the upper triangular matrix and the
	     corresponding strictly lower triangular part of the matrix	A is
	     not referenced.

	     Before entry with uplo = 'L' or 'l' or , the elements
	     corresponding to the leading k by k lower triangular elements of
	     the matrix	A  must	contain	the lower triangular matrix and	the
	     corresponding strictly upper triangular part of the matrix	A is
	     not referenced.

	     Note that when diag = 'U' or 'u' or , the elements	corresponding
	     to	the diagonal elements of the matrix A are not referenced
	     either, but are assumed to	be unity.

	     Unchanged on exit.

     lda     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	).
	     Unchanged on exit.

     b	     An	array containing the matrix B.

	     FORTRAN
	     An	array of dimension ( ldb, n ).

	     C
	     A pointer to an array of size ldb*n.
	     See note below about array	storage	convention for C.

	     Before entry it should contain the	elements corresponding to the
	     m by n matrix B.  On exit it overwritten by the transformed
	     matrix.







									Page 4






_TRSM(3F)							     _TRSM(3F)



     ldb     On	entry, ldb specifies the first dimension of B as declared in
	     the calling (sub)program. ldb must	be at least max( 1, m ).
	     Unchanged on exit.


C ARRAY	STORAGE	CONVENTION
       The matrices  are assumed  to be	stored in a  one dimensional C array
       in an analogous fashion as a Fortran array (column major). Therefore,
       the element  A(i+1,j)  of matrix	A  is stored  immediately  after the
       element	A(i,j),	while  A(i,j+1)	is lda	elements apart from  A(i,j).
       The element A(i,j) of the matrix	can be accessed	directly by reference
       to  a[ (j-1)*lda	+ (i-1)	].

AUTHORS    [Toc]    [Back]

	  Jack Dongarra, Argonne National Laboratory.
	  Iain Duff, AERE Harwell.
	  Jeremy Du Croz, Numerical Algorithms Group Ltd.
	  Sven Hammarling, Numerical Algorithms	Group Ltd.

TUNING    [Toc]    [Back]

	  Optimized and	parallelized for SGI R3000, R4x00 and R8000 platforms.


									PPPPaaaaggggeeee 5555
[ Back ]
 Similar pages
Name OS Title
trmm IRIX BLAS level three Matrix Product FORTRAN 77 SYNOPSIS subroutine dtrmm( side, uplo, transa, diag, m, n, alpha, a
symm IRIX BLAS level three Symmetric Matrix Product FORTRAN 77 SYNOPSIS subroutine dsymm( side,uplo,m,n,alpha,a,lda,b,ld
hemm IRIX BLAS level three Hermitian Matrix Product FORTRAN 77 SYNOPSIS subroutine zhemm( side,uplo,m,n,alpha,a,lda,b,ld
gemm IRIX BLAS level three Matrix Product FORTRAN 77 SYNOPSIS subroutine dgemm( transa,transb,m,n,k,alpha,a,lda,b,ldb,be
syrk IRIX BLAS level three Symmetric Rank K Update. FORTRAN 77 SYNOPSIS subroutine dsyrk( uplo, trans, n, k, alpha, a, l
syr2k IRIX BLAS level three Symmetric Rank 2K Update. FORTRAN 77 SYNOPSIS subroutine dsyr2k(uplo,trans,n,k,alpha,a,lda,b,
her2k IRIX BLAS level three Hermitian Rank 2K Update FORTRAN 77 SYNOPSIS subroutine zher2k( uplo,trans,n,k,alpha,a,lda,b,
herk IRIX BLAS level three Hermitian Rank K Update FORTRAN 77 SYNOPSIS subroutine zherk(uplo,trans,n,k,alpha,a,lda,beta,
spr IRIX BLAS Level Two Symmetric Packed Matrix Rank 1 Update FORTRAN 77 SYNOPSIS subroutine dspr( uplo, n, alpha, x, i
syr2 IRIX BLAS Level Two (Symmetric/Hermitian)Matrix Rank 2 Update FORTRAN 77 SYNOPSIS subroutine dsyr2( uplo, n, alpha,
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service