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