LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zgtsv.f
Go to the documentation of this file.
1*> \brief <b> ZGTSV computes the solution to system of linear equations A * X = B for GT matrices </b>
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZGTSV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgtsv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgtsv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgtsv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZGTSV( N, NRHS, DL, D, DU, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, LDB, N, NRHS
23* ..
24* .. Array Arguments ..
25* COMPLEX*16 B( LDB, * ), D( * ), DL( * ), DU( * )
26* ..
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> ZGTSV solves the equation
35*>
36*> A*X = B,
37*>
38*> where A is an N-by-N tridiagonal matrix, by Gaussian elimination with
39*> partial pivoting.
40*>
41*> Note that the equation A**T *X = B may be solved by interchanging the
42*> order of the arguments DU and DL.
43*> \endverbatim
44*
45* Arguments:
46* ==========
47*
48*> \param[in] N
49*> \verbatim
50*> N is INTEGER
51*> The order of the matrix A. N >= 0.
52*> \endverbatim
53*>
54*> \param[in] NRHS
55*> \verbatim
56*> NRHS is INTEGER
57*> The number of right hand sides, i.e., the number of columns
58*> of the matrix B. NRHS >= 0.
59*> \endverbatim
60*>
61*> \param[in,out] DL
62*> \verbatim
63*> DL is COMPLEX*16 array, dimension (N-1)
64*> On entry, DL must contain the (n-1) subdiagonal elements of
65*> A.
66*> On exit, DL is overwritten by the (n-2) elements of the
67*> second superdiagonal of the upper triangular matrix U from
68*> the LU factorization of A, in DL(1), ..., DL(n-2).
69*> \endverbatim
70*>
71*> \param[in,out] D
72*> \verbatim
73*> D is COMPLEX*16 array, dimension (N)
74*> On entry, D must contain the diagonal elements of A.
75*> On exit, D is overwritten by the n diagonal elements of U.
76*> \endverbatim
77*>
78*> \param[in,out] DU
79*> \verbatim
80*> DU is COMPLEX*16 array, dimension (N-1)
81*> On entry, DU must contain the (n-1) superdiagonal elements
82*> of A.
83*> On exit, DU is overwritten by the (n-1) elements of the first
84*> superdiagonal of U.
85*> \endverbatim
86*>
87*> \param[in,out] B
88*> \verbatim
89*> B is COMPLEX*16 array, dimension (LDB,NRHS)
90*> On entry, the N-by-NRHS right hand side matrix B.
91*> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
92*> \endverbatim
93*>
94*> \param[in] LDB
95*> \verbatim
96*> LDB is INTEGER
97*> The leading dimension of the array B. LDB >= max(1,N).
98*> \endverbatim
99*>
100*> \param[out] INFO
101*> \verbatim
102*> INFO is INTEGER
103*> = 0: successful exit
104*> < 0: if INFO = -i, the i-th argument had an illegal value
105*> > 0: if INFO = i, U(i,i) is exactly zero, and the solution
106*> has not been computed. The factorization has not been
107*> completed unless i = N.
108*> \endverbatim
109*
110* Authors:
111* ========
112*
113*> \author Univ. of Tennessee
114*> \author Univ. of California Berkeley
115*> \author Univ. of Colorado Denver
116*> \author NAG Ltd.
117*
118*> \ingroup gtsv
119*
120* =====================================================================
121 SUBROUTINE zgtsv( N, NRHS, DL, D, DU, B, LDB, INFO )
122*
123* -- LAPACK driver routine --
124* -- LAPACK is a software package provided by Univ. of Tennessee, --
125* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126*
127* .. Scalar Arguments ..
128 INTEGER INFO, LDB, N, NRHS
129* ..
130* .. Array Arguments ..
131 COMPLEX*16 B( LDB, * ), D( * ), DL( * ), DU( * )
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 COMPLEX*16 ZERO
138 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
139* ..
140* .. Local Scalars ..
141 INTEGER J, K
142 COMPLEX*16 MULT, TEMP, ZDUM
143* ..
144* .. Intrinsic Functions ..
145 INTRINSIC abs, dble, dimag, max
146* ..
147* .. External Subroutines ..
148 EXTERNAL xerbla
149* ..
150* .. Statement Functions ..
151 DOUBLE PRECISION CABS1
152* ..
153* .. Statement Function definitions ..
154 cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
155* ..
156* .. Executable Statements ..
157*
158 info = 0
159 IF( n.LT.0 ) THEN
160 info = -1
161 ELSE IF( nrhs.LT.0 ) THEN
162 info = -2
163 ELSE IF( ldb.LT.max( 1, n ) ) THEN
164 info = -7
165 END IF
166 IF( info.NE.0 ) THEN
167 CALL xerbla( 'ZGTSV ', -info )
168 RETURN
169 END IF
170*
171 IF( n.EQ.0 )
172 $ RETURN
173*
174 DO 30 k = 1, n - 1
175 IF( dl( k ).EQ.zero ) THEN
176*
177* Subdiagonal is zero, no elimination is required.
178*
179 IF( d( k ).EQ.zero ) THEN
180*
181* Diagonal is zero: set INFO = K and return; a unique
182* solution can not be found.
183*
184 info = k
185 RETURN
186 END IF
187 ELSE IF( cabs1( d( k ) ).GE.cabs1( dl( k ) ) ) THEN
188*
189* No row interchange required
190*
191 mult = dl( k ) / d( k )
192 d( k+1 ) = d( k+1 ) - mult*du( k )
193 DO 10 j = 1, nrhs
194 b( k+1, j ) = b( k+1, j ) - mult*b( k, j )
195 10 CONTINUE
196 IF( k.LT.( n-1 ) )
197 $ dl( k ) = zero
198 ELSE
199*
200* Interchange rows K and K+1
201*
202 mult = d( k ) / dl( k )
203 d( k ) = dl( k )
204 temp = d( k+1 )
205 d( k+1 ) = du( k ) - mult*temp
206 IF( k.LT.( n-1 ) ) THEN
207 dl( k ) = du( k+1 )
208 du( k+1 ) = -mult*dl( k )
209 END IF
210 du( k ) = temp
211 DO 20 j = 1, nrhs
212 temp = b( k, j )
213 b( k, j ) = b( k+1, j )
214 b( k+1, j ) = temp - mult*b( k+1, j )
215 20 CONTINUE
216 END IF
217 30 CONTINUE
218 IF( d( n ).EQ.zero ) THEN
219 info = n
220 RETURN
221 END IF
222*
223* Back solve with the matrix U from the factorization.
224*
225 DO 50 j = 1, nrhs
226 b( n, j ) = b( n, j ) / d( n )
227 IF( n.GT.1 )
228 $ b( n-1, j ) = ( b( n-1, j )-du( n-1 )*b( n, j ) ) / d( n-1 )
229 DO 40 k = n - 2, 1, -1
230 b( k, j ) = ( b( k, j )-du( k )*b( k+1, j )-dl( k )*
231 $ b( k+2, j ) ) / d( k )
232 40 CONTINUE
233 50 CONTINUE
234*
235 RETURN
236*
237* End of ZGTSV
238*
239 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgtsv(n, nrhs, dl, d, du, b, ldb, info)
ZGTSV computes the solution to system of linear equations A * X = B for GT matrices
Definition zgtsv.f:122