version 1.6, 2010/12/21 13:51:25
|
version 1.14, 2018/05/29 06:55:14
|
Line 1
|
Line 1
|
|
*> \brief \b DTBSV |
|
* |
|
* =========== DOCUMENTATION =========== |
|
* |
|
* Online html documentation available at |
|
* http://www.netlib.org/lapack/explore-html/ |
|
* |
|
* Definition: |
|
* =========== |
|
* |
|
* SUBROUTINE DTBSV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX) |
|
* |
|
* .. Scalar Arguments .. |
|
* INTEGER INCX,K,LDA,N |
|
* CHARACTER DIAG,TRANS,UPLO |
|
* .. |
|
* .. Array Arguments .. |
|
* DOUBLE PRECISION A(LDA,*),X(*) |
|
* .. |
|
* |
|
* |
|
*> \par Purpose: |
|
* ============= |
|
*> |
|
*> \verbatim |
|
*> |
|
*> DTBSV solves one of the systems of equations |
|
*> |
|
*> A*x = b, or A**T*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 |
|
*> routine. Such tests must be performed before calling this routine. |
|
*> \endverbatim |
|
* |
|
* Arguments: |
|
* ========== |
|
* |
|
*> \param[in] UPLO |
|
*> \verbatim |
|
*> UPLO is CHARACTER*1 |
|
*> 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. |
|
*> \endverbatim |
|
*> |
|
*> \param[in] TRANS |
|
*> \verbatim |
|
*> TRANS is CHARACTER*1 |
|
*> On entry, TRANS specifies the equations to be solved as |
|
*> follows: |
|
*> |
|
*> TRANS = 'N' or 'n' A*x = b. |
|
*> |
|
*> TRANS = 'T' or 't' A**T*x = b. |
|
*> |
|
*> TRANS = 'C' or 'c' A**T*x = b. |
|
*> \endverbatim |
|
*> |
|
*> \param[in] DIAG |
|
*> \verbatim |
|
*> 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. |
|
*> \endverbatim |
|
*> |
|
*> \param[in] N |
|
*> \verbatim |
|
*> N is INTEGER |
|
*> On entry, N specifies the order of the matrix A. |
|
*> N must be at least zero. |
|
*> \endverbatim |
|
*> |
|
*> \param[in] K |
|
*> \verbatim |
|
*> K is INTEGER |
|
*> 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 must satisfy 0 .le. K. |
|
*> \endverbatim |
|
*> |
|
*> \param[in] A |
|
*> \verbatim |
|
*> A is DOUBLE PRECISION array, dimension ( LDA, N ) |
|
*> 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 |
|
*> 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 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', 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 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' the elements of the array A |
|
*> corresponding to the diagonal elements of the matrix are not |
|
*> referenced, but are assumed to be unity. |
|
*> \endverbatim |
|
*> |
|
*> \param[in] LDA |
|
*> \verbatim |
|
*> LDA is INTEGER |
|
*> On entry, LDA specifies the first dimension of A as declared |
|
*> in the calling (sub) program. LDA must be at least |
|
*> ( k + 1 ). |
|
*> \endverbatim |
|
*> |
|
*> \param[in,out] X |
|
*> \verbatim |
|
*> X is DOUBLE PRECISION array, dimension at least |
|
*> ( 1 + ( n - 1 )*abs( INCX ) ). |
|
*> Before entry, the incremented array X must contain the n |
|
*> element right-hand side vector b. On exit, X is overwritten |
|
*> with the solution vector x. |
|
*> \endverbatim |
|
*> |
|
*> \param[in] INCX |
|
*> \verbatim |
|
*> INCX is INTEGER |
|
*> On entry, INCX specifies the increment for the elements of |
|
*> X. INCX must not be zero. |
|
*> \endverbatim |
|
* |
|
* Authors: |
|
* ======== |
|
* |
|
*> \author Univ. of Tennessee |
|
*> \author Univ. of California Berkeley |
|
*> \author Univ. of Colorado Denver |
|
*> \author NAG Ltd. |
|
* |
|
*> \date December 2016 |
|
* |
|
*> \ingroup double_blas_level2 |
|
* |
|
*> \par Further Details: |
|
* ===================== |
|
*> |
|
*> \verbatim |
|
*> |
|
*> Level 2 Blas routine. |
|
*> |
|
*> -- Written on 22-October-1986. |
|
*> Jack Dongarra, Argonne National Lab. |
|
*> Jeremy Du Croz, Nag Central Office. |
|
*> Sven Hammarling, Nag Central Office. |
|
*> Richard Hanson, Sandia National Labs. |
|
*> \endverbatim |
|
*> |
|
* ===================================================================== |
SUBROUTINE DTBSV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX) |
SUBROUTINE DTBSV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX) |
|
* |
|
* -- Reference BLAS level2 routine (version 3.7.0) -- |
|
* -- Reference BLAS is a software package provided by Univ. of Tennessee, -- |
|
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- |
|
* December 2016 |
|
* |
* .. Scalar Arguments .. |
* .. Scalar Arguments .. |
INTEGER INCX,K,LDA,N |
INTEGER INCX,K,LDA,N |
CHARACTER DIAG,TRANS,UPLO |
CHARACTER DIAG,TRANS,UPLO |
Line 7
|
Line 202
|
DOUBLE PRECISION A(LDA,*),X(*) |
DOUBLE PRECISION A(LDA,*),X(*) |
* .. |
* .. |
* |
* |
* 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 |
|
* routine. Such tests must be performed before calling this routine. |
|
* |
|
* Arguments |
|
* ========== |
|
* |
|
* UPLO - CHARACTER*1. |
|
* 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. |
|
* |
|
* TRANS - CHARACTER*1. |
|
* On entry, TRANS specifies the equations to be solved as |
|
* follows: |
|
* |
|
* TRANS = 'N' or 'n' A*x = b. |
|
* |
|
* TRANS = 'T' or 't' A'*x = b. |
|
* |
|
* TRANS = 'C' or 'c' A'*x = b. |
|
* |
|
* Unchanged on exit. |
|
* |
|
* DIAG - 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. |
|
* |
|
* Unchanged on exit. |
|
* |
|
* N - INTEGER. |
|
* On entry, N specifies the order of the matrix A. |
|
* N must be at least zero. |
|
* Unchanged on exit. |
|
* |
|
* K - INTEGER. |
|
* 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 must satisfy 0 .le. K. |
|
* Unchanged on exit. |
|
* |
|
* A - DOUBLE PRECISION array of DIMENSION ( LDA, n ). |
|
* 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 |
|
* 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 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', 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 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' 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 - INTEGER. |
|
* On entry, LDA specifies the first dimension of A as declared |
|
* in the calling (sub) program. LDA must be at least |
|
* ( k + 1 ). |
|
* Unchanged on exit. |
|
* |
|
* X - DOUBLE PRECISION array of dimension at least |
|
* ( 1 + ( n - 1 )*abs( INCX ) ). |
|
* Before entry, the incremented array X must contain the n |
|
* element right-hand side vector b. On exit, X is overwritten |
|
* with the solution vector x. |
|
* |
|
* INCX - INTEGER. |
|
* On entry, INCX specifies the increment for the elements of |
|
* X. INCX must not be zero. |
|
* Unchanged on exit. |
|
* |
|
* Further Details |
|
* =============== |
|
* |
|
* Level 2 Blas routine. |
|
* |
|
* -- Written on 22-October-1986. |
|
* Jack Dongarra, Argonne National Lab. |
|
* Jeremy Du Croz, Nag Central Office. |
|
* Sven Hammarling, Nag Central Office. |
|
* Richard Hanson, Sandia National Labs. |
|
* |
|
* ===================================================================== |
* ===================================================================== |
* |
* |
* .. Parameters .. |
* .. Parameters .. |
Line 271
|
Line 333
|
END IF |
END IF |
ELSE |
ELSE |
* |
* |
* Form x := inv( A')*x. |
* Form x := inv( A**T)*x. |
* |
* |
IF (LSAME(UPLO,'U')) THEN |
IF (LSAME(UPLO,'U')) THEN |
KPLUS1 = K + 1 |
KPLUS1 = K + 1 |