dtbsv man page on OpenIndiana

Man page or keyword search:  
man Server   20441 pages
apropos Keyword Search (all sections)
Output format
OpenIndiana logo
[printable version]

dtbsv(3P)		    Sun Performance Library		     dtbsv(3P)

NAME
       dtbsv - solve one of the systems of equations A*x = b, or A'*x = b

SYNOPSIS
       SUBROUTINE DTBSV(UPLO, TRANSA, DIAG, N, K, A, LDA, Y, INCY)

       CHARACTER * 1 UPLO, TRANSA, DIAG
       INTEGER N, K, LDA, INCY
       DOUBLE PRECISION A(LDA,*), Y(*)

       SUBROUTINE DTBSV_64(UPLO, TRANSA, DIAG, N, K, A, LDA, Y, INCY)

       CHARACTER * 1 UPLO, TRANSA, DIAG
       INTEGER*8 N, K, LDA, INCY
       DOUBLE PRECISION A(LDA,*), Y(*)

   F95 INTERFACE
       SUBROUTINE TBSV(UPLO, [TRANSA], DIAG, [N], K, A, [LDA], Y, [INCY])

       CHARACTER(LEN=1) :: UPLO, TRANSA, DIAG
       INTEGER :: N, K, LDA, INCY
       REAL(8), DIMENSION(:) :: Y
       REAL(8), DIMENSION(:,:) :: A

       SUBROUTINE TBSV_64(UPLO, [TRANSA], DIAG, [N], K, A, [LDA], Y,
	      [INCY])

       CHARACTER(LEN=1) :: UPLO, TRANSA, DIAG
       INTEGER(8) :: N, K, LDA, INCY
       REAL(8), DIMENSION(:) :: Y
       REAL(8), DIMENSION(:,:) :: A

   C INTERFACE
       #include <sunperf.h>

       void  dtbsv(char uplo, char transa, char diag, int n, int k, double *a,
		 int lda, double *y, int incy);

       void dtbsv_64(char uplo, char transa, char diag, long n, long k, double
		 *a, long lda, double *y, long incy);

PURPOSE
       dtbsv  solves  one  of  the  systems of equations A*x = b, or 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 this rou‐
       tine. Such tests must be performed before calling this routine.

ARGUMENTS
       UPLO (input)
		 On entry, UPLO specifies whether the matrix 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.

		 Unchanged on exit.

       TRANSA (input)
		 On entry, TRANSA specifies the equations to be solved as fol‐
		 lows:

		 TRANSA = 'N' or 'n'   A*x = b.

		 TRANSA = 'T' or 't'   A'*x = b.

		 TRANSA = 'C' or 'c'   A'*x = b.

		 Unchanged on exit.

		 TRANSA is defaulted to 'N' for F95 INTERFACE.

       DIAG (input)
		 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.

		 Unchanged on exit.

       N (input)
		 On  entry,  N	specifies  the order of the matrix A.  N >= 0.
		 Unchanged on exit.

       K (input)
		 On entry with UPLO = 'U' or 'u', K specifies  the  number  of
		 super-diagonals of the matrix A.  On entry with UPLO = 'L' or
		 'l', K specifies the number of sub-diagonals of the matrix A.
		 K >= 0.  Unchanged on exit.

       A (input)
		 Before entry with UPLO = 'U' or 'u', the 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 col‐
		 umn, 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 program segment
		 will transfer an upper triangular band	 matrix	 from  conven‐
		 tional 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', 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 col‐
		 umn, 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 program segment will trans‐
		 fer 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' the elements of the array A
		 corresponding to the diagonal elements of the matrix are  not
		 referenced, but are assumed to be unity.  Unchanged on exit.

       LDA (input)
		 On  entry, LDA specifies the first dimension of A as declared
		 in the calling (sub) program.	LDA >= ( k + 1	).   Unchanged
		 on exit.

       Y (input/output)
		 ( 1 + ( n - 1 )*abs( INCY ) ).	 Before entry, the incremented
		 array Y must contain the n element right-hand side vector  b.
		 On exit, Y is overwritten with the solution vector x.

       INCY (input)
		 On entry, INCY specifies the increment for the elements of Y.
		 INCY <> 0.  Unchanged on exit.

				  6 Mar 2009			     dtbsv(3P)
[top]

List of man pages available for OpenIndiana

Copyright (c) for man pages and the logo by the respective OS vendor.

For those who want to learn more, the polarhome community provides shell access and support.

[legal] [privacy] [GNU] [policy] [cookies] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.
Based on Fawad Halim's script.
....................................................................
Vote for polarhome
Free Shell Accounts :: the biggest list on the net