KTH framework for Nek5000 toolboxes; testing version  0.0.1
dtbsv.f
Go to the documentation of this file.
1  SUBROUTINE dtbsv ( UPLO, TRANS, DIAG, N, K, A, LDA, X, INCX )
2 * .. Scalar Arguments ..
3  INTEGER INCX, K, LDA, N
4  CHARACTER*1 DIAG, TRANS, UPLO
5 * .. Array Arguments ..
6  DOUBLE PRECISION A( LDA, * ), X( * )
7 * ..
8 *
9 * Purpose
10 * =======
11 *
12 * DTBSV solves one of the systems of equations
13 *
14 * A*x = b, or A'*x = b,
15 *
16 * where b and x are n element vectors and A is an n by n unit, or
17 * non-unit, upper or lower triangular band matrix, with ( k + 1 )
18 * diagonals.
19 *
20 * No test for singularity or near-singularity is included in this
21 * routine. Such tests must be performed before calling this routine.
22 *
23 * Parameters
24 * ==========
25 *
26 * UPLO - CHARACTER*1.
27 * On entry, UPLO specifies whether the matrix is an upper or
28 * lower triangular matrix as follows:
29 *
30 * UPLO = 'U' or 'u' A is an upper triangular matrix.
31 *
32 * UPLO = 'L' or 'l' A is a lower triangular matrix.
33 *
34 * Unchanged on exit.
35 *
36 * TRANS - CHARACTER*1.
37 * On entry, TRANS specifies the equations to be solved as
38 * follows:
39 *
40 * TRANS = 'N' or 'n' A*x = b.
41 *
42 * TRANS = 'T' or 't' A'*x = b.
43 *
44 * TRANS = 'C' or 'c' A'*x = b.
45 *
46 * Unchanged on exit.
47 *
48 * DIAG - CHARACTER*1.
49 * On entry, DIAG specifies whether or not A is unit
50 * triangular as follows:
51 *
52 * DIAG = 'U' or 'u' A is assumed to be unit triangular.
53 *
54 * DIAG = 'N' or 'n' A is not assumed to be unit
55 * triangular.
56 *
57 * Unchanged on exit.
58 *
59 * N - INTEGER.
60 * On entry, N specifies the order of the matrix A.
61 * N must be at least zero.
62 * Unchanged on exit.
63 *
64 * K - INTEGER.
65 * On entry with UPLO = 'U' or 'u', K specifies the number of
66 * super-diagonals of the matrix A.
67 * On entry with UPLO = 'L' or 'l', K specifies the number of
68 * sub-diagonals of the matrix A.
69 * K must satisfy 0 .le. K.
70 * Unchanged on exit.
71 *
72 * A - DOUBLE PRECISION array of DIMENSION ( LDA, n ).
73 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
74 * by n part of the array A must contain the upper triangular
75 * band part of the matrix of coefficients, supplied column by
76 * column, with the leading diagonal of the matrix in row
77 * ( k + 1 ) of the array, the first super-diagonal starting at
78 * position 2 in row k, and so on. The top left k by k triangle
79 * of the array A is not referenced.
80 * The following program segment will transfer an upper
81 * triangular band matrix from conventional full matrix storage
82 * to band storage:
83 *
84 * DO 20, J = 1, N
85 * M = K + 1 - J
86 * DO 10, I = MAX( 1, J - K ), J
87 * A( M + I, J ) = matrix( I, J )
88 * 10 CONTINUE
89 * 20 CONTINUE
90 *
91 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
92 * by n part of the array A must contain the lower triangular
93 * band part of the matrix of coefficients, supplied column by
94 * column, with the leading diagonal of the matrix in row 1 of
95 * the array, the first sub-diagonal starting at position 1 in
96 * row 2, and so on. The bottom right k by k triangle of the
97 * array A is not referenced.
98 * The following program segment will transfer a lower
99 * triangular band matrix from conventional full matrix storage
100 * to band storage:
101 *
102 * DO 20, J = 1, N
103 * M = 1 - J
104 * DO 10, I = J, MIN( N, J + K )
105 * A( M + I, J ) = matrix( I, J )
106 * 10 CONTINUE
107 * 20 CONTINUE
108 *
109 * Note that when DIAG = 'U' or 'u' the elements of the array A
110 * corresponding to the diagonal elements of the matrix are not
111 * referenced, but are assumed to be unity.
112 * Unchanged on exit.
113 *
114 * LDA - INTEGER.
115 * On entry, LDA specifies the first dimension of A as declared
116 * in the calling (sub) program. LDA must be at least
117 * ( k + 1 ).
118 * Unchanged on exit.
119 *
120 * X - DOUBLE PRECISION array of dimension at least
121 * ( 1 + ( n - 1 )*abs( INCX ) ).
122 * Before entry, the incremented array X must contain the n
123 * element right-hand side vector b. On exit, X is overwritten
124 * with the solution vector x.
125 *
126 * INCX - INTEGER.
127 * On entry, INCX specifies the increment for the elements of
128 * X. INCX must not be zero.
129 * Unchanged on exit.
130 *
131 *
132 * Level 2 Blas routine.
133 *
134 * -- Written on 22-October-1986.
135 * Jack Dongarra, Argonne National Lab.
136 * Jeremy Du Croz, Nag Central Office.
137 * Sven Hammarling, Nag Central Office.
138 * Richard Hanson, Sandia National Labs.
139 *
140 *
141 * .. Parameters ..
142  DOUBLE PRECISION ZERO
143  parameter( zero = 0.0d+0 )
144 * .. Local Scalars ..
145  DOUBLE PRECISION TEMP
146  INTEGER I, INFO, IX, J, JX, KPLUS1, KX, L
147  LOGICAL NOUNIT
148 * .. External Functions ..
149  LOGICAL LSAME
150  EXTERNAL lsame
151 * .. External Subroutines ..
152  EXTERNAL xerbla
153 * .. Intrinsic Functions ..
154  INTRINSIC max, min
155 * ..
156 * .. Executable Statements ..
157 *
158 * Test the input parameters.
159 *
160  info = 0
161  IF ( .NOT.lsame( uplo , 'U' ).AND.
162  $ .NOT.lsame( uplo , 'L' ) )THEN
163  info = 1
164  ELSE IF( .NOT.lsame( trans, 'N' ).AND.
165  $ .NOT.lsame( trans, 'T' ).AND.
166  $ .NOT.lsame( trans, 'C' ) )THEN
167  info = 2
168  ELSE IF( .NOT.lsame( diag , 'U' ).AND.
169  $ .NOT.lsame( diag , 'N' ) )THEN
170  info = 3
171  ELSE IF( n.LT.0 )THEN
172  info = 4
173  ELSE IF( k.LT.0 )THEN
174  info = 5
175  ELSE IF( lda.LT.( k + 1 ) )THEN
176  info = 7
177  ELSE IF( incx.EQ.0 )THEN
178  info = 9
179  END IF
180  IF( info.NE.0 )THEN
181  CALL xerbla( 'DTBSV ', info )
182  RETURN
183  END IF
184 *
185 * Quick return if possible.
186 *
187  IF( n.EQ.0 )
188  $ RETURN
189 *
190  nounit = lsame( diag, 'N' )
191 *
192 * Set up the start point in X if the increment is not unity. This
193 * will be ( N - 1 )*INCX too small for descending loops.
194 *
195  IF( incx.LE.0 )THEN
196  kx = 1 - ( n - 1 )*incx
197  ELSE IF( incx.NE.1 )THEN
198  kx = 1
199  END IF
200 *
201 * Start the operations. In this version the elements of A are
202 * accessed by sequentially with one pass through A.
203 *
204  IF( lsame( trans, 'N' ) )THEN
205 *
206 * Form x := inv( A )*x.
207 *
208  IF( lsame( uplo, 'U' ) )THEN
209  kplus1 = k + 1
210  IF( incx.EQ.1 )THEN
211  DO 20, j = n, 1, -1
212  IF( x( j ).NE.zero )THEN
213  l = kplus1 - j
214  IF( nounit )
215  $ x( j ) = x( j )/a( kplus1, j )
216  temp = x( j )
217  DO 10, i = j - 1, max( 1, j - k ), -1
218  x( i ) = x( i ) - temp*a( l + i, j )
219  10 CONTINUE
220  END IF
221  20 CONTINUE
222  ELSE
223  kx = kx + ( n - 1 )*incx
224  jx = kx
225  DO 40, j = n, 1, -1
226  kx = kx - incx
227  IF( x( jx ).NE.zero )THEN
228  ix = kx
229  l = kplus1 - j
230  IF( nounit )
231  $ x( jx ) = x( jx )/a( kplus1, j )
232  temp = x( jx )
233  DO 30, i = j - 1, max( 1, j - k ), -1
234  x( ix ) = x( ix ) - temp*a( l + i, j )
235  ix = ix - incx
236  30 CONTINUE
237  END IF
238  jx = jx - incx
239  40 CONTINUE
240  END IF
241  ELSE
242  IF( incx.EQ.1 )THEN
243  DO 60, j = 1, n
244  IF( x( j ).NE.zero )THEN
245  l = 1 - j
246  IF( nounit )
247  $ 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 )
262  $ x( jx ) = x( jx )/a( 1, j )
263  temp = x( jx )
264  DO 70, i = j + 1, min( n, j + k )
265  x( ix ) = x( ix ) - temp*a( l + i, j )
266  ix = ix + incx
267  70 CONTINUE
268  END IF
269  jx = jx + incx
270  80 CONTINUE
271  END IF
272  END IF
273  ELSE
274 *
275 * Form x := inv( A')*x.
276 *
277  IF( lsame( uplo, 'U' ) )THEN
278  kplus1 = k + 1
279  IF( incx.EQ.1 )THEN
280  DO 100, j = 1, n
281  temp = x( j )
282  l = kplus1 - j
283  DO 90, i = max( 1, j - k ), j - 1
284  temp = temp - a( l + i, j )*x( i )
285  90 CONTINUE
286  IF( nounit )
287  $ temp = temp/a( kplus1, j )
288  x( j ) = temp
289  100 CONTINUE
290  ELSE
291  jx = kx
292  DO 120, j = 1, n
293  temp = x( jx )
294  ix = kx
295  l = kplus1 - j
296  DO 110, i = max( 1, j - k ), j - 1
297  temp = temp - a( l + i, j )*x( ix )
298  ix = ix + incx
299  110 CONTINUE
300  IF( nounit )
301  $ temp = temp/a( kplus1, j )
302  x( jx ) = temp
303  jx = jx + incx
304  IF( j.GT.k )
305  $ kx = kx + incx
306  120 CONTINUE
307  END IF
308  ELSE
309  IF( incx.EQ.1 )THEN
310  DO 140, j = n, 1, -1
311  temp = x( j )
312  l = 1 - j
313  DO 130, i = min( n, j + k ), j + 1, -1
314  temp = temp - a( l + i, j )*x( i )
315  130 CONTINUE
316  IF( nounit )
317  $ temp = temp/a( 1, j )
318  x( j ) = temp
319  140 CONTINUE
320  ELSE
321  kx = kx + ( n - 1 )*incx
322  jx = kx
323  DO 160, j = n, 1, -1
324  temp = x( jx )
325  ix = kx
326  l = 1 - j
327  DO 150, i = min( n, j + k ), j + 1, -1
328  temp = temp - a( l + i, j )*x( ix )
329  ix = ix - incx
330  150 CONTINUE
331  IF( nounit )
332  $ temp = temp/a( 1, j )
333  x( jx ) = temp
334  jx = jx - incx
335  IF( ( n - j ).GE.k )
336  $ kx = kx - incx
337  160 CONTINUE
338  END IF
339  END IF
340  END IF
341 *
342  RETURN
343 *
344 * End of DTBSV .
345 *
346  END
subroutine dtbsv(UPLO, TRANS, DIAG, N, K, A, LDA, X, INCX)
Definition: dtbsv.f:2
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2