File:
[local] /
rpl /
lapack /
blas /
dtbsv.f
Revision
1.11:
download - view:
text,
annotated -
select for diffs -
revision graph
Mon Jan 27 09:28:13 2014 UTC (11 years, 3 months ago) by
bertrand
Branches:
MAIN
CVS tags:
rpl-4_1_24,
rpl-4_1_23,
rpl-4_1_22,
rpl-4_1_21,
rpl-4_1_20,
rpl-4_1_19,
rpl-4_1_18,
rpl-4_1_17,
HEAD
Cohérence.
1: *> \brief \b DTBSV
2: *
3: * =========== DOCUMENTATION ===========
4: *
5: * Online html documentation available at
6: * http://www.netlib.org/lapack/explore-html/
7: *
8: * Definition:
9: * ===========
10: *
11: * SUBROUTINE DTBSV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
12: *
13: * .. Scalar Arguments ..
14: * INTEGER INCX,K,LDA,N
15: * CHARACTER DIAG,TRANS,UPLO
16: * ..
17: * .. Array Arguments ..
18: * DOUBLE PRECISION A(LDA,*),X(*)
19: * ..
20: *
21: *
22: *> \par Purpose:
23: * =============
24: *>
25: *> \verbatim
26: *>
27: *> DTBSV solves one of the systems of equations
28: *>
29: *> A*x = b, or A**T*x = b,
30: *>
31: *> where b and x are n element vectors and A is an n by n unit, or
32: *> non-unit, upper or lower triangular band matrix, with ( k + 1 )
33: *> diagonals.
34: *>
35: *> No test for singularity or near-singularity is included in this
36: *> routine. Such tests must be performed before calling this routine.
37: *> \endverbatim
38: *
39: * Arguments:
40: * ==========
41: *
42: *> \param[in] UPLO
43: *> \verbatim
44: *> UPLO is CHARACTER*1
45: *> On entry, UPLO specifies whether the matrix is an upper or
46: *> lower triangular matrix as follows:
47: *>
48: *> UPLO = 'U' or 'u' A is an upper triangular matrix.
49: *>
50: *> UPLO = 'L' or 'l' A is a lower triangular matrix.
51: *> \endverbatim
52: *>
53: *> \param[in] TRANS
54: *> \verbatim
55: *> TRANS is CHARACTER*1
56: *> On entry, TRANS specifies the equations to be solved as
57: *> follows:
58: *>
59: *> TRANS = 'N' or 'n' A*x = b.
60: *>
61: *> TRANS = 'T' or 't' A**T*x = b.
62: *>
63: *> TRANS = 'C' or 'c' A**T*x = b.
64: *> \endverbatim
65: *>
66: *> \param[in] DIAG
67: *> \verbatim
68: *> DIAG is CHARACTER*1
69: *> On entry, DIAG specifies whether or not A is unit
70: *> triangular as follows:
71: *>
72: *> DIAG = 'U' or 'u' A is assumed to be unit triangular.
73: *>
74: *> DIAG = 'N' or 'n' A is not assumed to be unit
75: *> triangular.
76: *> \endverbatim
77: *>
78: *> \param[in] N
79: *> \verbatim
80: *> N is INTEGER
81: *> On entry, N specifies the order of the matrix A.
82: *> N must be at least zero.
83: *> \endverbatim
84: *>
85: *> \param[in] K
86: *> \verbatim
87: *> K is INTEGER
88: *> On entry with UPLO = 'U' or 'u', K specifies the number of
89: *> super-diagonals of the matrix A.
90: *> On entry with UPLO = 'L' or 'l', K specifies the number of
91: *> sub-diagonals of the matrix A.
92: *> K must satisfy 0 .le. K.
93: *> \endverbatim
94: *>
95: *> \param[in] A
96: *> \verbatim
97: *> A is DOUBLE PRECISION array of DIMENSION ( LDA, n ).
98: *> Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
99: *> by n part of the array A must contain the upper triangular
100: *> band part of the matrix of coefficients, supplied column by
101: *> column, with the leading diagonal of the matrix in row
102: *> ( k + 1 ) of the array, the first super-diagonal starting at
103: *> position 2 in row k, and so on. The top left k by k triangle
104: *> of the array A is not referenced.
105: *> The following program segment will transfer an upper
106: *> triangular band matrix from conventional full matrix storage
107: *> to band storage:
108: *>
109: *> DO 20, J = 1, N
110: *> M = K + 1 - J
111: *> DO 10, I = MAX( 1, J - K ), J
112: *> A( M + I, J ) = matrix( I, J )
113: *> 10 CONTINUE
114: *> 20 CONTINUE
115: *>
116: *> Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
117: *> by n part of the array A must contain the lower triangular
118: *> band part of the matrix of coefficients, supplied column by
119: *> column, with the leading diagonal of the matrix in row 1 of
120: *> the array, the first sub-diagonal starting at position 1 in
121: *> row 2, and so on. The bottom right k by k triangle of the
122: *> array A is not referenced.
123: *> The following program segment will transfer a lower
124: *> triangular band matrix from conventional full matrix storage
125: *> to band storage:
126: *>
127: *> DO 20, J = 1, N
128: *> M = 1 - J
129: *> DO 10, I = J, MIN( N, J + K )
130: *> A( M + I, J ) = matrix( I, J )
131: *> 10 CONTINUE
132: *> 20 CONTINUE
133: *>
134: *> Note that when DIAG = 'U' or 'u' the elements of the array A
135: *> corresponding to the diagonal elements of the matrix are not
136: *> referenced, but are assumed to be unity.
137: *> \endverbatim
138: *>
139: *> \param[in] LDA
140: *> \verbatim
141: *> LDA is INTEGER
142: *> On entry, LDA specifies the first dimension of A as declared
143: *> in the calling (sub) program. LDA must be at least
144: *> ( k + 1 ).
145: *> \endverbatim
146: *>
147: *> \param[in,out] X
148: *> \verbatim
149: *> X is DOUBLE PRECISION array of dimension at least
150: *> ( 1 + ( n - 1 )*abs( INCX ) ).
151: *> Before entry, the incremented array X must contain the n
152: *> element right-hand side vector b. On exit, X is overwritten
153: *> with the solution vector x.
154: *> \endverbatim
155: *>
156: *> \param[in] INCX
157: *> \verbatim
158: *> INCX is INTEGER
159: *> On entry, INCX specifies the increment for the elements of
160: *> X. INCX must not be zero.
161: *> \endverbatim
162: *
163: * Authors:
164: * ========
165: *
166: *> \author Univ. of Tennessee
167: *> \author Univ. of California Berkeley
168: *> \author Univ. of Colorado Denver
169: *> \author NAG Ltd.
170: *
171: *> \date November 2011
172: *
173: *> \ingroup double_blas_level2
174: *
175: *> \par Further Details:
176: * =====================
177: *>
178: *> \verbatim
179: *>
180: *> Level 2 Blas routine.
181: *>
182: *> -- Written on 22-October-1986.
183: *> Jack Dongarra, Argonne National Lab.
184: *> Jeremy Du Croz, Nag Central Office.
185: *> Sven Hammarling, Nag Central Office.
186: *> Richard Hanson, Sandia National Labs.
187: *> \endverbatim
188: *>
189: * =====================================================================
190: SUBROUTINE DTBSV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
191: *
192: * -- Reference BLAS level2 routine (version 3.4.0) --
193: * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
194: * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
195: * November 2011
196: *
197: * .. Scalar Arguments ..
198: INTEGER INCX,K,LDA,N
199: CHARACTER DIAG,TRANS,UPLO
200: * ..
201: * .. Array Arguments ..
202: DOUBLE PRECISION A(LDA,*),X(*)
203: * ..
204: *
205: * =====================================================================
206: *
207: * .. Parameters ..
208: DOUBLE PRECISION ZERO
209: PARAMETER (ZERO=0.0D+0)
210: * ..
211: * .. Local Scalars ..
212: DOUBLE PRECISION TEMP
213: INTEGER I,INFO,IX,J,JX,KPLUS1,KX,L
214: LOGICAL NOUNIT
215: * ..
216: * .. External Functions ..
217: LOGICAL LSAME
218: EXTERNAL LSAME
219: * ..
220: * .. External Subroutines ..
221: EXTERNAL XERBLA
222: * ..
223: * .. Intrinsic Functions ..
224: INTRINSIC MAX,MIN
225: * ..
226: *
227: * Test the input parameters.
228: *
229: INFO = 0
230: IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
231: INFO = 1
232: ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
233: + .NOT.LSAME(TRANS,'C')) THEN
234: INFO = 2
235: ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
236: INFO = 3
237: ELSE IF (N.LT.0) THEN
238: INFO = 4
239: ELSE IF (K.LT.0) THEN
240: INFO = 5
241: ELSE IF (LDA.LT. (K+1)) THEN
242: INFO = 7
243: ELSE IF (INCX.EQ.0) THEN
244: INFO = 9
245: END IF
246: IF (INFO.NE.0) THEN
247: CALL XERBLA('DTBSV ',INFO)
248: RETURN
249: END IF
250: *
251: * Quick return if possible.
252: *
253: IF (N.EQ.0) RETURN
254: *
255: NOUNIT = LSAME(DIAG,'N')
256: *
257: * Set up the start point in X if the increment is not unity. This
258: * will be ( N - 1 )*INCX too small for descending loops.
259: *
260: IF (INCX.LE.0) THEN
261: KX = 1 - (N-1)*INCX
262: ELSE IF (INCX.NE.1) THEN
263: KX = 1
264: END IF
265: *
266: * Start the operations. In this version the elements of A are
267: * accessed by sequentially with one pass through A.
268: *
269: IF (LSAME(TRANS,'N')) THEN
270: *
271: * Form x := inv( A )*x.
272: *
273: IF (LSAME(UPLO,'U')) THEN
274: KPLUS1 = K + 1
275: IF (INCX.EQ.1) THEN
276: DO 20 J = N,1,-1
277: IF (X(J).NE.ZERO) THEN
278: L = KPLUS1 - J
279: IF (NOUNIT) X(J) = X(J)/A(KPLUS1,J)
280: TEMP = X(J)
281: DO 10 I = J - 1,MAX(1,J-K),-1
282: X(I) = X(I) - TEMP*A(L+I,J)
283: 10 CONTINUE
284: END IF
285: 20 CONTINUE
286: ELSE
287: KX = KX + (N-1)*INCX
288: JX = KX
289: DO 40 J = N,1,-1
290: KX = KX - INCX
291: IF (X(JX).NE.ZERO) THEN
292: IX = KX
293: L = KPLUS1 - J
294: IF (NOUNIT) X(JX) = X(JX)/A(KPLUS1,J)
295: TEMP = X(JX)
296: DO 30 I = J - 1,MAX(1,J-K),-1
297: X(IX) = X(IX) - TEMP*A(L+I,J)
298: IX = IX - INCX
299: 30 CONTINUE
300: END IF
301: JX = JX - INCX
302: 40 CONTINUE
303: END IF
304: ELSE
305: IF (INCX.EQ.1) THEN
306: DO 60 J = 1,N
307: IF (X(J).NE.ZERO) THEN
308: L = 1 - J
309: IF (NOUNIT) X(J) = X(J)/A(1,J)
310: TEMP = X(J)
311: DO 50 I = J + 1,MIN(N,J+K)
312: X(I) = X(I) - TEMP*A(L+I,J)
313: 50 CONTINUE
314: END IF
315: 60 CONTINUE
316: ELSE
317: JX = KX
318: DO 80 J = 1,N
319: KX = KX + INCX
320: IF (X(JX).NE.ZERO) THEN
321: IX = KX
322: L = 1 - J
323: IF (NOUNIT) X(JX) = X(JX)/A(1,J)
324: TEMP = X(JX)
325: DO 70 I = J + 1,MIN(N,J+K)
326: X(IX) = X(IX) - TEMP*A(L+I,J)
327: IX = IX + INCX
328: 70 CONTINUE
329: END IF
330: JX = JX + INCX
331: 80 CONTINUE
332: END IF
333: END IF
334: ELSE
335: *
336: * Form x := inv( A**T)*x.
337: *
338: IF (LSAME(UPLO,'U')) THEN
339: KPLUS1 = K + 1
340: IF (INCX.EQ.1) THEN
341: DO 100 J = 1,N
342: TEMP = X(J)
343: L = KPLUS1 - J
344: DO 90 I = MAX(1,J-K),J - 1
345: TEMP = TEMP - A(L+I,J)*X(I)
346: 90 CONTINUE
347: IF (NOUNIT) TEMP = TEMP/A(KPLUS1,J)
348: X(J) = TEMP
349: 100 CONTINUE
350: ELSE
351: JX = KX
352: DO 120 J = 1,N
353: TEMP = X(JX)
354: IX = KX
355: L = KPLUS1 - J
356: DO 110 I = MAX(1,J-K),J - 1
357: TEMP = TEMP - A(L+I,J)*X(IX)
358: IX = IX + INCX
359: 110 CONTINUE
360: IF (NOUNIT) TEMP = TEMP/A(KPLUS1,J)
361: X(JX) = TEMP
362: JX = JX + INCX
363: IF (J.GT.K) KX = KX + INCX
364: 120 CONTINUE
365: END IF
366: ELSE
367: IF (INCX.EQ.1) THEN
368: DO 140 J = N,1,-1
369: TEMP = X(J)
370: L = 1 - J
371: DO 130 I = MIN(N,J+K),J + 1,-1
372: TEMP = TEMP - A(L+I,J)*X(I)
373: 130 CONTINUE
374: IF (NOUNIT) TEMP = TEMP/A(1,J)
375: X(J) = TEMP
376: 140 CONTINUE
377: ELSE
378: KX = KX + (N-1)*INCX
379: JX = KX
380: DO 160 J = N,1,-1
381: TEMP = X(JX)
382: IX = KX
383: L = 1 - J
384: DO 150 I = MIN(N,J+K),J + 1,-1
385: TEMP = TEMP - A(L+I,J)*X(IX)
386: IX = IX - INCX
387: 150 CONTINUE
388: IF (NOUNIT) TEMP = TEMP/A(1,J)
389: X(JX) = TEMP
390: JX = JX - INCX
391: IF ((N-J).GE.K) KX = KX - INCX
392: 160 CONTINUE
393: END IF
394: END IF
395: END IF
396: *
397: RETURN
398: *
399: * End of DTBSV .
400: *
401: END
CVSweb interface <joel.bertrand@systella.fr>