001:       SUBROUTINE DTBSV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
002: *     .. Scalar Arguments ..
003:       INTEGER INCX,K,LDA,N
004:       CHARACTER DIAG,TRANS,UPLO
005: *     ..
006: *     .. Array Arguments ..
007:       DOUBLE PRECISION A(LDA,*),X(*)
008: *     ..
009: *
010: *  Purpose
011: *  =======
012: *
013: *  DTBSV  solves one of the systems of equations
014: *
015: *     A*x = b,   or   A'*x = b,
016: *
017: *  where b and x are n element vectors and A is an n by n unit, or
018: *  non-unit, upper or lower triangular band matrix, with ( k + 1 )
019: *  diagonals.
020: *
021: *  No test for singularity or near-singularity is included in this
022: *  routine. Such tests must be performed before calling this routine.
023: *
024: *  Arguments
025: *  ==========
026: *
027: *  UPLO   - CHARACTER*1.
028: *           On entry, UPLO specifies whether the matrix is an upper or
029: *           lower triangular matrix as follows:
030: *
031: *              UPLO = 'U' or 'u'   A is an upper triangular matrix.
032: *
033: *              UPLO = 'L' or 'l'   A is a lower triangular matrix.
034: *
035: *           Unchanged on exit.
036: *
037: *  TRANS  - CHARACTER*1.
038: *           On entry, TRANS specifies the equations to be solved as
039: *           follows:
040: *
041: *              TRANS = 'N' or 'n'   A*x = b.
042: *
043: *              TRANS = 'T' or 't'   A'*x = b.
044: *
045: *              TRANS = 'C' or 'c'   A'*x = b.
046: *
047: *           Unchanged on exit.
048: *
049: *  DIAG   - CHARACTER*1.
050: *           On entry, DIAG specifies whether or not A is unit
051: *           triangular as follows:
052: *
053: *              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
054: *
055: *              DIAG = 'N' or 'n'   A is not assumed to be unit
056: *                                  triangular.
057: *
058: *           Unchanged on exit.
059: *
060: *  N      - INTEGER.
061: *           On entry, N specifies the order of the matrix A.
062: *           N must be at least zero.
063: *           Unchanged on exit.
064: *
065: *  K      - INTEGER.
066: *           On entry with UPLO = 'U' or 'u', K specifies the number of
067: *           super-diagonals of the matrix A.
068: *           On entry with UPLO = 'L' or 'l', K specifies the number of
069: *           sub-diagonals of the matrix A.
070: *           K must satisfy  0 .le. K.
071: *           Unchanged on exit.
072: *
073: *  A      - DOUBLE PRECISION array of DIMENSION ( LDA, n ).
074: *           Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
075: *           by n part of the array A must contain the upper triangular
076: *           band part of the matrix of coefficients, supplied column by
077: *           column, with the leading diagonal of the matrix in row
078: *           ( k + 1 ) of the array, the first super-diagonal starting at
079: *           position 2 in row k, and so on. The top left k by k triangle
080: *           of the array A is not referenced.
081: *           The following program segment will transfer an upper
082: *           triangular band matrix from conventional full matrix storage
083: *           to band storage:
084: *
085: *                 DO 20, J = 1, N
086: *                    M = K + 1 - J
087: *                    DO 10, I = MAX( 1, J - K ), J
088: *                       A( M + I, J ) = matrix( I, J )
089: *              10    CONTINUE
090: *              20 CONTINUE
091: *
092: *           Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
093: *           by n part of the array A must contain the lower triangular
094: *           band part of the matrix of coefficients, supplied column by
095: *           column, with the leading diagonal of the matrix in row 1 of
096: *           the array, the first sub-diagonal starting at position 1 in
097: *           row 2, and so on. The bottom right k by k triangle of the
098: *           array A is not referenced.
099: *           The following program segment will transfer a lower
100: *           triangular band matrix from conventional full matrix storage
101: *           to band storage:
102: *
103: *                 DO 20, J = 1, N
104: *                    M = 1 - J
105: *                    DO 10, I = J, MIN( N, J + K )
106: *                       A( M + I, J ) = matrix( I, J )
107: *              10    CONTINUE
108: *              20 CONTINUE
109: *
110: *           Note that when DIAG = 'U' or 'u' the elements of the array A
111: *           corresponding to the diagonal elements of the matrix are not
112: *           referenced, but are assumed to be unity.
113: *           Unchanged on exit.
114: *
115: *  LDA    - INTEGER.
116: *           On entry, LDA specifies the first dimension of A as declared
117: *           in the calling (sub) program. LDA must be at least
118: *           ( k + 1 ).
119: *           Unchanged on exit.
120: *
121: *  X      - DOUBLE PRECISION array of dimension at least
122: *           ( 1 + ( n - 1 )*abs( INCX ) ).
123: *           Before entry, the incremented array X must contain the n
124: *           element right-hand side vector b. On exit, X is overwritten
125: *           with the solution vector x.
126: *
127: *  INCX   - INTEGER.
128: *           On entry, INCX specifies the increment for the elements of
129: *           X. INCX must not be zero.
130: *           Unchanged on exit.
131: *
132: *  Further Details
133: *  ===============
134: *
135: *  Level 2 Blas routine.
136: *
137: *  -- Written on 22-October-1986.
138: *     Jack Dongarra, Argonne National Lab.
139: *     Jeremy Du Croz, Nag Central Office.
140: *     Sven Hammarling, Nag Central Office.
141: *     Richard Hanson, Sandia National Labs.
142: *
143: *  =====================================================================
144: *
145: *     .. Parameters ..
146:       DOUBLE PRECISION ZERO
147:       PARAMETER (ZERO=0.0D+0)
148: *     ..
149: *     .. Local Scalars ..
150:       DOUBLE PRECISION TEMP
151:       INTEGER I,INFO,IX,J,JX,KPLUS1,KX,L
152:       LOGICAL NOUNIT
153: *     ..
154: *     .. External Functions ..
155:       LOGICAL LSAME
156:       EXTERNAL LSAME
157: *     ..
158: *     .. External Subroutines ..
159:       EXTERNAL XERBLA
160: *     ..
161: *     .. Intrinsic Functions ..
162:       INTRINSIC MAX,MIN
163: *     ..
164: *
165: *     Test the input parameters.
166: *
167:       INFO = 0
168:       IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
169:           INFO = 1
170:       ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
171:      +         .NOT.LSAME(TRANS,'C')) THEN
172:           INFO = 2
173:       ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
174:           INFO = 3
175:       ELSE IF (N.LT.0) THEN
176:           INFO = 4
177:       ELSE IF (K.LT.0) THEN
178:           INFO = 5
179:       ELSE IF (LDA.LT. (K+1)) THEN
180:           INFO = 7
181:       ELSE IF (INCX.EQ.0) THEN
182:           INFO = 9
183:       END IF
184:       IF (INFO.NE.0) THEN
185:           CALL XERBLA('DTBSV ',INFO)
186:           RETURN
187:       END IF
188: *
189: *     Quick return if possible.
190: *
191:       IF (N.EQ.0) RETURN
192: *
193:       NOUNIT = LSAME(DIAG,'N')
194: *
195: *     Set up the start point in X if the increment is not unity. This
196: *     will be  ( N - 1 )*INCX  too small for descending loops.
197: *
198:       IF (INCX.LE.0) THEN
199:           KX = 1 - (N-1)*INCX
200:       ELSE IF (INCX.NE.1) THEN
201:           KX = 1
202:       END IF
203: *
204: *     Start the operations. In this version the elements of A are
205: *     accessed by sequentially with one pass through A.
206: *
207:       IF (LSAME(TRANS,'N')) THEN
208: *
209: *        Form  x := inv( A )*x.
210: *
211:           IF (LSAME(UPLO,'U')) THEN
212:               KPLUS1 = K + 1
213:               IF (INCX.EQ.1) THEN
214:                   DO 20 J = N,1,-1
215:                       IF (X(J).NE.ZERO) THEN
216:                           L = KPLUS1 - J
217:                           IF (NOUNIT) X(J) = X(J)/A(KPLUS1,J)
218:                           TEMP = X(J)
219:                           DO 10 I = J - 1,MAX(1,J-K),-1
220:                               X(I) = X(I) - TEMP*A(L+I,J)
221:    10                     CONTINUE
222:                       END IF
223:    20             CONTINUE
224:               ELSE
225:                   KX = KX + (N-1)*INCX
226:                   JX = KX
227:                   DO 40 J = N,1,-1
228:                       KX = KX - INCX
229:                       IF (X(JX).NE.ZERO) THEN
230:                           IX = KX
231:                           L = KPLUS1 - J
232:                           IF (NOUNIT) X(JX) = X(JX)/A(KPLUS1,J)
233:                           TEMP = X(JX)
234:                           DO 30 I = J - 1,MAX(1,J-K),-1
235:                               X(IX) = X(IX) - TEMP*A(L+I,J)
236:                               IX = IX - INCX
237:    30                     CONTINUE
238:                       END IF
239:                       JX = JX - INCX
240:    40             CONTINUE
241:               END IF
242:           ELSE
243:               IF (INCX.EQ.1) THEN
244:                   DO 60 J = 1,N
245:                       IF (X(J).NE.ZERO) THEN
246:                           L = 1 - J
247:                           IF (NOUNIT) X(J) = X(J)/A(1,J)
248:                           TEMP = X(J)
249:                           DO 50 I = J + 1,MIN(N,J+K)
250:                               X(I) = X(I) - TEMP*A(L+I,J)
251:    50                     CONTINUE
252:                       END IF
253:    60             CONTINUE
254:               ELSE
255:                   JX = KX
256:                   DO 80 J = 1,N
257:                       KX = KX + INCX
258:                       IF (X(JX).NE.ZERO) THEN
259:                           IX = KX
260:                           L = 1 - J
261:                           IF (NOUNIT) X(JX) = X(JX)/A(1,J)
262:                           TEMP = X(JX)
263:                           DO 70 I = J + 1,MIN(N,J+K)
264:                               X(IX) = X(IX) - TEMP*A(L+I,J)
265:                               IX = IX + INCX
266:    70                     CONTINUE
267:                       END IF
268:                       JX = JX + INCX
269:    80             CONTINUE
270:               END IF
271:           END IF
272:       ELSE
273: *
274: *        Form  x := inv( A')*x.
275: *
276:           IF (LSAME(UPLO,'U')) THEN
277:               KPLUS1 = K + 1
278:               IF (INCX.EQ.1) THEN
279:                   DO 100 J = 1,N
280:                       TEMP = X(J)
281:                       L = KPLUS1 - J
282:                       DO 90 I = MAX(1,J-K),J - 1
283:                           TEMP = TEMP - A(L+I,J)*X(I)
284:    90                 CONTINUE
285:                       IF (NOUNIT) TEMP = TEMP/A(KPLUS1,J)
286:                       X(J) = TEMP
287:   100             CONTINUE
288:               ELSE
289:                   JX = KX
290:                   DO 120 J = 1,N
291:                       TEMP = X(JX)
292:                       IX = KX
293:                       L = KPLUS1 - J
294:                       DO 110 I = MAX(1,J-K),J - 1
295:                           TEMP = TEMP - A(L+I,J)*X(IX)
296:                           IX = IX + INCX
297:   110                 CONTINUE
298:                       IF (NOUNIT) TEMP = TEMP/A(KPLUS1,J)
299:                       X(JX) = TEMP
300:                       JX = JX + INCX
301:                       IF (J.GT.K) KX = KX + INCX
302:   120             CONTINUE
303:               END IF
304:           ELSE
305:               IF (INCX.EQ.1) THEN
306:                   DO 140 J = N,1,-1
307:                       TEMP = X(J)
308:                       L = 1 - J
309:                       DO 130 I = MIN(N,J+K),J + 1,-1
310:                           TEMP = TEMP - A(L+I,J)*X(I)
311:   130                 CONTINUE
312:                       IF (NOUNIT) TEMP = TEMP/A(1,J)
313:                       X(J) = TEMP
314:   140             CONTINUE
315:               ELSE
316:                   KX = KX + (N-1)*INCX
317:                   JX = KX
318:                   DO 160 J = N,1,-1
319:                       TEMP = X(JX)
320:                       IX = KX
321:                       L = 1 - J
322:                       DO 150 I = MIN(N,J+K),J + 1,-1
323:                           TEMP = TEMP - A(L+I,J)*X(IX)
324:                           IX = IX - INCX
325:   150                 CONTINUE
326:                       IF (NOUNIT) TEMP = TEMP/A(1,J)
327:                       X(JX) = TEMP
328:                       JX = JX - INCX
329:                       IF ((N-J).GE.K) KX = KX - INCX
330:   160             CONTINUE
331:               END IF
332:           END IF
333:       END IF
334: *
335:       RETURN
336: *
337: *     End of DTBSV .
338: *
339:       END
340: