001:       SUBROUTINE STBTRS( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB, B,
002:      $                   LDB, INFO )
003: *
004: *  -- LAPACK routine (version 3.2) --
005: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
006: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
007: *     November 2006
008: *
009: *     .. Scalar Arguments ..
010:       CHARACTER          DIAG, TRANS, UPLO
011:       INTEGER            INFO, KD, LDAB, LDB, N, NRHS
012: *     ..
013: *     .. Array Arguments ..
014:       REAL               AB( LDAB, * ), B( LDB, * )
015: *     ..
016: *
017: *  Purpose
018: *  =======
019: *
020: *  STBTRS solves a triangular system of the form
021: *
022: *     A * X = B  or  A**T * X = B,
023: *
024: *  where A is a triangular band matrix of order N, and B is an
025: *  N-by NRHS matrix.  A check is made to verify that A is nonsingular.
026: *
027: *  Arguments
028: *  =========
029: *
030: *  UPLO    (input) CHARACTER*1
031: *          = 'U':  A is upper triangular;
032: *          = 'L':  A is lower triangular.
033: *
034: *  TRANS   (input) CHARACTER*1
035: *          Specifies the form the system of equations:
036: *          = 'N':  A * X = B  (No transpose)
037: *          = 'T':  A**T * X = B  (Transpose)
038: *          = 'C':  A**H * X = B  (Conjugate transpose = Transpose)
039: *
040: *  DIAG    (input) CHARACTER*1
041: *          = 'N':  A is non-unit triangular;
042: *          = 'U':  A is unit triangular.
043: *
044: *  N       (input) INTEGER
045: *          The order of the matrix A.  N >= 0.
046: *
047: *  KD      (input) INTEGER
048: *          The number of superdiagonals or subdiagonals of the
049: *          triangular band matrix A.  KD >= 0.
050: *
051: *  NRHS    (input) INTEGER
052: *          The number of right hand sides, i.e., the number of columns
053: *          of the matrix B.  NRHS >= 0.
054: *
055: *  AB      (input) REAL array, dimension (LDAB,N)
056: *          The upper or lower triangular band matrix A, stored in the
057: *          first kd+1 rows of AB.  The j-th column of A is stored
058: *          in the j-th column of the array AB as follows:
059: *          if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
060: *          if UPLO = 'L', AB(1+i-j,j)    = A(i,j) for j<=i<=min(n,j+kd).
061: *          If DIAG = 'U', the diagonal elements of A are not referenced
062: *          and are assumed to be 1.
063: *
064: *  LDAB    (input) INTEGER
065: *          The leading dimension of the array AB.  LDAB >= KD+1.
066: *
067: *  B       (input/output) REAL array, dimension (LDB,NRHS)
068: *          On entry, the right hand side matrix B.
069: *          On exit, if INFO = 0, the solution matrix X.
070: *
071: *  LDB     (input) INTEGER
072: *          The leading dimension of the array B.  LDB >= max(1,N).
073: *
074: *  INFO    (output) INTEGER
075: *          = 0:  successful exit
076: *          < 0:  if INFO = -i, the i-th argument had an illegal value
077: *          > 0:  if INFO = i, the i-th diagonal element of A is zero,
078: *                indicating that the matrix is singular and the
079: *                solutions X have not been computed.
080: *
081: *  =====================================================================
082: *
083: *     .. Parameters ..
084:       REAL               ZERO
085:       PARAMETER          ( ZERO = 0.0E+0 )
086: *     ..
087: *     .. Local Scalars ..
088:       LOGICAL            NOUNIT, UPPER
089:       INTEGER            J
090: *     ..
091: *     .. External Functions ..
092:       LOGICAL            LSAME
093:       EXTERNAL           LSAME
094: *     ..
095: *     .. External Subroutines ..
096:       EXTERNAL           STBSV, XERBLA
097: *     ..
098: *     .. Intrinsic Functions ..
099:       INTRINSIC          MAX
100: *     ..
101: *     .. Executable Statements ..
102: *
103: *     Test the input parameters.
104: *
105:       INFO = 0
106:       NOUNIT = LSAME( DIAG, 'N' )
107:       UPPER = LSAME( UPLO, 'U' )
108:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
109:          INFO = -1
110:       ELSE IF( .NOT.LSAME( TRANS, 'N' ) .AND. .NOT.
111:      $         LSAME( TRANS, 'T' ) .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
112:          INFO = -2
113:       ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
114:          INFO = -3
115:       ELSE IF( N.LT.0 ) THEN
116:          INFO = -4
117:       ELSE IF( KD.LT.0 ) THEN
118:          INFO = -5
119:       ELSE IF( NRHS.LT.0 ) THEN
120:          INFO = -6
121:       ELSE IF( LDAB.LT.KD+1 ) THEN
122:          INFO = -8
123:       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
124:          INFO = -10
125:       END IF
126:       IF( INFO.NE.0 ) THEN
127:          CALL XERBLA( 'STBTRS', -INFO )
128:          RETURN
129:       END IF
130: *
131: *     Quick return if possible
132: *
133:       IF( N.EQ.0 )
134:      $   RETURN
135: *
136: *     Check for singularity.
137: *
138:       IF( NOUNIT ) THEN
139:          IF( UPPER ) THEN
140:             DO 10 INFO = 1, N
141:                IF( AB( KD+1, INFO ).EQ.ZERO )
142:      $            RETURN
143:    10       CONTINUE
144:          ELSE
145:             DO 20 INFO = 1, N
146:                IF( AB( 1, INFO ).EQ.ZERO )
147:      $            RETURN
148:    20       CONTINUE
149:          END IF
150:       END IF
151:       INFO = 0
152: *
153: *     Solve A * X = B  or  A' * X = B.
154: *
155:       DO 30 J = 1, NRHS
156:          CALL STBSV( UPLO, TRANS, DIAG, N, KD, AB, LDAB, B( 1, J ), 1 )
157:    30 CONTINUE
158: *
159:       RETURN
160: *
161: *     End of STBTRS
162: *
163:       END
164: