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

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

Contents


_TBMV,_TBSV(3F)						       _TBMV,_TBSV(3F)


NAME    [Toc]    [Back]

     dtbmv, stbmv, ztbmv, ctbmv, dtbsv,	stbsv, ztbsv, ctbsv - BLAS Level Two
     Matrix-Vector Product  and	 Solution of System of Equations.


FORTRAN	77 SYNOPSIS
     subroutine	dtbmv( uplo, trans, diag, n, k,	a, lda,	x, incx	)
     subroutine	dtbsv( uplo, trans, diag, n, k,	a, lda,	x, incx	)
	   character*1	      uplo, trans, diag
	   integer	      n, k, lda, incx
	   double precision   a( lda,*), x(*)

     subroutine	stbmv( uplo, trans, diag, n, k,	a, lda,	x, incx	)
     subroutine	stbsv( uplo, trans, diag, n, k,	a, lda,	x, incx	)
	   character*1	      uplo, trans, diag
	   integer	      n, k, lda, incx
	   real		      a( lda,*), x(*)

     subroutine	ztbmv( uplo, trans, diag, n, k,	a, lda,	x, incx	)
     subroutine	ztbsv( uplo, trans, diag, n, k,	a, lda,	x, incx	)
	   character*1	      uplo, trans, diag
	   integer	      n, k, lda, incx
	   double complex     a( lda,*), x(*)

     subroutine	ctbmv( uplo, trans, diag, n, a,	k, lda,	x, incx	)
     subroutine	ctbsv( uplo, trans, diag, n, a,	k, lda,	x, incx	)
	   character*1	      uplo, trans, diag
	   integer	      n, k, lda, incx
	   complex	      a( lda,*), x(*)

C SYNOPSIS    [Toc]    [Back]

     void dtbmv( uplo, trans, diag, n, k, a, lda, x, incx )
     void dtbsv( uplo, trans, diag, n, k, a, lda, x, incx )
	   MatrixTriangle	 uplo;
	   MatrixTranspose	 trans;
	   MatrixUnitTriangular	 diag;
	   Integer		 n, k, lda, incx;
	   double		 (*a)[lda*k], (*x)[ n ];

     void stbmv( uplo, trans, diag, n, k, a, lda, x, incx )
     void stbsv( uplo, trans, diag, n, k, a, lda, x, incx )
	   MatrixTriangle	 uplo;
	   MatrixTranspose	 trans;
	   MatrixUnitTriangular	 diag;
	   Integer		 n, k, lda, incx;
	   float		 (*a)[lda*k], (*x)[ n ];

     void ztbmv( uplo, trans, diag, n, k, a, lda, x, incx )
     void ztbsv( uplo, trans, diag, n, k, a, lda, x, incx )
	   MatrixTriangle	 uplo;
	   MatrixTranspose	 trans;



									Page 1






_TBMV,_TBSV(3F)						       _TBMV,_TBSV(3F)



	   MatrixUnitTriangular	 diag;
	   Integer		 n, k, lda, incx;
	   Zomplex		 (*a)[lda*k], (*x)[ n ];

     void ctbmv( uplo, trans, diag, n, k, a, lda, x, incx )
     void ctbsv( uplo, trans, diag, n, k, a, lda, x, incx )
	   MatrixTriangle	 uplo;
	   MatrixTranspose	 trans;
	   MatrixUnitTriangular	 diag;
	   Integer		 n, k, lda, incx;
	   Complex		 (*a)[lda*k], (*x)[ n ];


DESCRIPTION    [Toc]    [Back]

     dtbmv, stbmv, ztbmv and ctbmv perform one of the matrix-vector operations

	   x :=	A*x,   or   x := A'*x,	 or   x	:= conjg( A' )*x,

     where x is	an n element vector and	A is an	n by n unit, or	non-unit,
     upper or lower triangular band matrix, with ( k + 1 ) diagonals.

     dtbsv, stbsv, ztbsv and ctbsv solve one of	the systems of equations

	   A*x = b,   or   A'*x	= b,   or   conjg( A' )*x = b,

     where b and x are n element vectors and A is an n by n unit, or non-unit,
     upper or lower triangular band matrix, with ( k + 1 ) diagonals.  No test
     for singularity or	near-singularity is included in	these routines.	Such
     tests must	be performed before calling these routines.

PARAMETERS    [Toc]    [Back]

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

		  FORTRAN
		  uplo = 'U' or	'u'	   A is	an upper triangular matrix.
		  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.

     trans   On	entry, trans specifies the operation to	be

		  FORTRAN
		  trans	= 'N' or 'n'	   x :=	A*x /  A*x = b.
		  trans	= 'T' or 't'	   x :=	A'*x / A'*x = b.
		  trans	= 'C' or 'c'	   x :=	conjg( A' )*x  /



									Page 2






_TBMV,_TBSV(3F)						       _TBMV,_TBSV(3F)



						conjg( A' )*x =	b.

		  C
		  trans	= NoTranspose		x := A*x /  A*x	= b.
		  trans	= Transpose		x := A'*x / A'*x = b.
		  trans	= ConjugateTranspose	x := conjg( A' )*x  /
						    conjg( A' )*x = b.

	     For real value matrices, trans='C'	and trans='T' has the same
	     meaning.

	     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.

     n	     On	entry, n specifies the order of	the matrix A. n	must be	at
	     least zero.
	     Unchanged on exit.

     k	     On	entry, with uplo = 'U' or 'u' or UpperTriangle , k specifies
	     the number	of super-diagonals of the matrix A.

	     On	entry with uplo	= 'L' or 'l' or	LowerTriangle ,	k specifies
	     the number	of sub-diagonals of the	matrix A.

	     k must satisfy  0 .le. k.

	     Unchanged on exit.

     a	     An	array containing the matrix A.

	     FORTRAN
	     Array of dimension	( lda, n ).

	     C
	     A pointer to an array of size lda*n containing the	matrix A.
	     See note below about array	storage	convention for C.

	     Before entry with uplo = 'U' or 'u' or UpperTriangle , the



									Page 3






_TBMV,_TBSV(3F)						       _TBMV,_TBSV(3F)



	     leading ( k + 1 ) by n part of the	array a	must contain the upper
	     triangular	band part of the matrix	of coefficients, supplied
	     column by column, with the	leading	diagonal of the	matrix in row
	     ( k + 1 ) of the array, the first super-diagonal starting at
	     position 2	in row k, and so on. The top left k by k triangle of
	     the array a is not	referenced.  The following Fortran program
	     segment will transfer an upper triangular band matrix from
	     conventional full matrix storage to band storage:

			       DO 20, J	= 1, N
				  M = K	+ 1 - J
				  DO 10, I = MAX( 1, J - K ), J
				     A(	M + I, J ) = matrix( I,	J )
			    10	  CONTINUE
			    20 CONTINUE

	     Before entry with uplo = 'L' or 'l'or LowerTraingle , the leading
	     ( k + 1 ) by n part of the	array a	must contain the lower
	     triangular	band part of the matrix	of coefficients, supplied
	     column by column, with the	leading	diagonal of the	matrix in row
	     1 of the array, the first sub-diagonal starting at	position 1 in
	     row 2, and	so on. The bottom right	k by k triangle	of the array a
	     is	not referenced.	The following Fortran program segment will
	     transfer a	lower triangular band matrix from conventional full
	     matrix storage to band storage:

			       DO 20, J	= 1, N
				  M = 1	- J
				  DO 10, I = J,	MIN( N,	J + K )
				     A(	M + I, J ) = matrix( I,	J )
			    10	  CONTINUE
			    20 CONTINUE

	     Note that when diag = 'U' or 'u' or , the elements	of a
	     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.	 lda must be at	least max( 1, n	).
	     Unchanged on exit.

     x	     Array of size at least ( 1	+ ( n -	1 )*abs( incx )	). Before
	     entry, the	incremented array x must contain the vector x. On
	     exit, x is	overwritten with the transformed/solution vector x.

     incx    On	entry, incx specifies the increment for	the elements of	x.
	     incx must not be zero.
	     Unchanged on exit.





									Page 4






_TBMV,_TBSV(3F)						       _TBMV,_TBSV(3F)



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.


									PPPPaaaaggggeeee 5555
[ Back ]
 Similar pages
Name OS Title
rot IRIX BLAS level ONE rotation subroutines
spmv IRIX BLAS Level Two (Symmetric/Hermitian)
sbmv IRIX BLAS Level Two (Symmetric/Hermitian)
symv IRIX BLAS Level Two (Symmetric/Hermitian)Matrix
nrm2 IRIX BLAS level ONE Euclidean norm functions.
gemm IRIX BLAS level three Matrix Product FORTRAN 77 SYNOPSIS subroutine dgemm( transa,transb,m,n,k,alpha,a,lda,b,ldb,be
ger IRIX BLAS Level Two Rank 1 Operation FORTRAN 77 SYNOPSIS subroutine dger( m, n, alpha, x, incx, y, incy, a, lda ) i
syr2k IRIX BLAS level three Symmetric Rank 2K Update. FORTRAN 77 SYNOPSIS subroutine dsyr2k(uplo,trans,n,k,alpha,a,lda,b,
syrk IRIX BLAS level three Symmetric Rank K Update. FORTRAN 77 SYNOPSIS subroutine dsyrk( uplo, trans, n, k, alpha, a, l
her2k IRIX BLAS level three Hermitian Rank 2K Update FORTRAN 77 SYNOPSIS subroutine zher2k( uplo,trans,n,k,alpha,a,lda,b,
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service