comparison libcruft/lapack/cgtsv.f @ 7789:82be108cc558

First attempt at single precision tyeps * * * corrections to qrupdate single precision routines * * * prefer demotion to single over promotion to double * * * Add single precision support to log2 function * * * Trivial PROJECT file update * * * Cache optimized hermitian/transpose methods * * * Add tests for tranpose/hermitian and ChangeLog entry for new transpose code
author David Bateman <dbateman@free.fr>
date Sun, 27 Apr 2008 22:34:17 +0200
parents
children
comparison
equal deleted inserted replaced
7788:45f5faba05a2 7789:82be108cc558
1 SUBROUTINE CGTSV( N, NRHS, DL, D, DU, B, LDB, INFO )
2 *
3 * -- LAPACK routine (version 3.1) --
4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5 * November 2006
6 *
7 * .. Scalar Arguments ..
8 INTEGER INFO, LDB, N, NRHS
9 * ..
10 * .. Array Arguments ..
11 COMPLEX B( LDB, * ), D( * ), DL( * ), DU( * )
12 * ..
13 *
14 * Purpose
15 * =======
16 *
17 * CGTSV solves the equation
18 *
19 * A*X = B,
20 *
21 * where A is an N-by-N tridiagonal matrix, by Gaussian elimination with
22 * partial pivoting.
23 *
24 * Note that the equation A'*X = B may be solved by interchanging the
25 * order of the arguments DU and DL.
26 *
27 * Arguments
28 * =========
29 *
30 * N (input) INTEGER
31 * The order of the matrix A. N >= 0.
32 *
33 * NRHS (input) INTEGER
34 * The number of right hand sides, i.e., the number of columns
35 * of the matrix B. NRHS >= 0.
36 *
37 * DL (input/output) COMPLEX array, dimension (N-1)
38 * On entry, DL must contain the (n-1) subdiagonal elements of
39 * A.
40 * On exit, DL is overwritten by the (n-2) elements of the
41 * second superdiagonal of the upper triangular matrix U from
42 * the LU factorization of A, in DL(1), ..., DL(n-2).
43 *
44 * D (input/output) COMPLEX array, dimension (N)
45 * On entry, D must contain the diagonal elements of A.
46 * On exit, D is overwritten by the n diagonal elements of U.
47 *
48 * DU (input/output) COMPLEX array, dimension (N-1)
49 * On entry, DU must contain the (n-1) superdiagonal elements
50 * of A.
51 * On exit, DU is overwritten by the (n-1) elements of the first
52 * superdiagonal of U.
53 *
54 * B (input/output) COMPLEX array, dimension (LDB,NRHS)
55 * On entry, the N-by-NRHS right hand side matrix B.
56 * On exit, if INFO = 0, the N-by-NRHS solution matrix X.
57 *
58 * LDB (input) INTEGER
59 * The leading dimension of the array B. LDB >= max(1,N).
60 *
61 * INFO (output) INTEGER
62 * = 0: successful exit
63 * < 0: if INFO = -i, the i-th argument had an illegal value
64 * > 0: if INFO = i, U(i,i) is exactly zero, and the solution
65 * has not been computed. The factorization has not been
66 * completed unless i = N.
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71 COMPLEX ZERO
72 PARAMETER ( ZERO = ( 0.0E+0, 0.0E+0 ) )
73 * ..
74 * .. Local Scalars ..
75 INTEGER J, K
76 COMPLEX MULT, TEMP, ZDUM
77 * ..
78 * .. Intrinsic Functions ..
79 INTRINSIC ABS, AIMAG, MAX, REAL
80 * ..
81 * .. External Subroutines ..
82 EXTERNAL XERBLA
83 * ..
84 * .. Statement Functions ..
85 REAL CABS1
86 * ..
87 * .. Statement Function definitions ..
88 CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
89 * ..
90 * .. Executable Statements ..
91 *
92 INFO = 0
93 IF( N.LT.0 ) THEN
94 INFO = -1
95 ELSE IF( NRHS.LT.0 ) THEN
96 INFO = -2
97 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
98 INFO = -7
99 END IF
100 IF( INFO.NE.0 ) THEN
101 CALL XERBLA( 'CGTSV ', -INFO )
102 RETURN
103 END IF
104 *
105 IF( N.EQ.0 )
106 $ RETURN
107 *
108 DO 30 K = 1, N - 1
109 IF( DL( K ).EQ.ZERO ) THEN
110 *
111 * Subdiagonal is zero, no elimination is required.
112 *
113 IF( D( K ).EQ.ZERO ) THEN
114 *
115 * Diagonal is zero: set INFO = K and return; a unique
116 * solution can not be found.
117 *
118 INFO = K
119 RETURN
120 END IF
121 ELSE IF( CABS1( D( K ) ).GE.CABS1( DL( K ) ) ) THEN
122 *
123 * No row interchange required
124 *
125 MULT = DL( K ) / D( K )
126 D( K+1 ) = D( K+1 ) - MULT*DU( K )
127 DO 10 J = 1, NRHS
128 B( K+1, J ) = B( K+1, J ) - MULT*B( K, J )
129 10 CONTINUE
130 IF( K.LT.( N-1 ) )
131 $ DL( K ) = ZERO
132 ELSE
133 *
134 * Interchange rows K and K+1
135 *
136 MULT = D( K ) / DL( K )
137 D( K ) = DL( K )
138 TEMP = D( K+1 )
139 D( K+1 ) = DU( K ) - MULT*TEMP
140 IF( K.LT.( N-1 ) ) THEN
141 DL( K ) = DU( K+1 )
142 DU( K+1 ) = -MULT*DL( K )
143 END IF
144 DU( K ) = TEMP
145 DO 20 J = 1, NRHS
146 TEMP = B( K, J )
147 B( K, J ) = B( K+1, J )
148 B( K+1, J ) = TEMP - MULT*B( K+1, J )
149 20 CONTINUE
150 END IF
151 30 CONTINUE
152 IF( D( N ).EQ.ZERO ) THEN
153 INFO = N
154 RETURN
155 END IF
156 *
157 * Back solve with the matrix U from the factorization.
158 *
159 DO 50 J = 1, NRHS
160 B( N, J ) = B( N, J ) / D( N )
161 IF( N.GT.1 )
162 $ B( N-1, J ) = ( B( N-1, J )-DU( N-1 )*B( N, J ) ) / D( N-1 )
163 DO 40 K = N - 2, 1, -1
164 B( K, J ) = ( B( K, J )-DU( K )*B( K+1, J )-DL( K )*
165 $ B( K+2, J ) ) / D( K )
166 40 CONTINUE
167 50 CONTINUE
168 *
169 RETURN
170 *
171 * End of CGTSV
172 *
173 END