LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zpttrs.f
Go to the documentation of this file.
1*> \brief \b ZPTTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZPTTRS + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zpttrs.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zpttrs.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpttrs.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE ZPTTRS( UPLO, N, NRHS, D, E, B, LDB, INFO )
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER INFO, LDB, N, NRHS
26* ..
27* .. Array Arguments ..
28* DOUBLE PRECISION D( * )
29* COMPLEX*16 B( LDB, * ), E( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> ZPTTRS solves a tridiagonal system of the form
39*> A * X = B
40*> using the factorization A = U**H *D* U or A = L*D*L**H computed by ZPTTRF.
41*> D is a diagonal matrix specified in the vector D, U (or L) is a unit
42*> bidiagonal matrix whose superdiagonal (subdiagonal) is specified in
43*> the vector E, and X and B are N by NRHS matrices.
44*> \endverbatim
45*
46* Arguments:
47* ==========
48*
49*> \param[in] UPLO
50*> \verbatim
51*> UPLO is CHARACTER*1
52*> Specifies the form of the factorization and whether the
53*> vector E is the superdiagonal of the upper bidiagonal factor
54*> U or the subdiagonal of the lower bidiagonal factor L.
55*> = 'U': A = U**H *D*U, E is the superdiagonal of U
56*> = 'L': A = L*D*L**H, E is the subdiagonal of L
57*> \endverbatim
58*>
59*> \param[in] N
60*> \verbatim
61*> N is INTEGER
62*> The order of the tridiagonal matrix A. N >= 0.
63*> \endverbatim
64*>
65*> \param[in] NRHS
66*> \verbatim
67*> NRHS is INTEGER
68*> The number of right hand sides, i.e., the number of columns
69*> of the matrix B. NRHS >= 0.
70*> \endverbatim
71*>
72*> \param[in] D
73*> \verbatim
74*> D is DOUBLE PRECISION array, dimension (N)
75*> The n diagonal elements of the diagonal matrix D from the
76*> factorization A = U**H *D*U or A = L*D*L**H.
77*> \endverbatim
78*>
79*> \param[in] E
80*> \verbatim
81*> E is COMPLEX*16 array, dimension (N-1)
82*> If UPLO = 'U', the (n-1) superdiagonal elements of the unit
83*> bidiagonal factor U from the factorization A = U**H*D*U.
84*> If UPLO = 'L', the (n-1) subdiagonal elements of the unit
85*> bidiagonal factor L from the factorization A = L*D*L**H.
86*> \endverbatim
87*>
88*> \param[in,out] B
89*> \verbatim
90*> B is COMPLEX*16 array, dimension (LDB,NRHS)
91*> On entry, the right hand side vectors B for the system of
92*> linear equations.
93*> On exit, the solution vectors, 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 = -k, the k-th argument had an illegal value
107*> \endverbatim
108*
109* Authors:
110* ========
111*
112*> \author Univ. of Tennessee
113*> \author Univ. of California Berkeley
114*> \author Univ. of Colorado Denver
115*> \author NAG Ltd.
116*
117*> \ingroup pttrs
118*
119* =====================================================================
120 SUBROUTINE zpttrs( UPLO, N, NRHS, D, E, B, LDB, INFO )
121*
122* -- LAPACK computational routine --
123* -- LAPACK is a software package provided by Univ. of Tennessee, --
124* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
125*
126* .. Scalar Arguments ..
127 CHARACTER UPLO
128 INTEGER INFO, LDB, N, NRHS
129* ..
130* .. Array Arguments ..
131 DOUBLE PRECISION D( * )
132 COMPLEX*16 B( LDB, * ), E( * )
133* ..
134*
135* =====================================================================
136*
137* .. Local Scalars ..
138 LOGICAL UPPER
139 INTEGER IUPLO, J, JB, NB
140* ..
141* .. External Functions ..
142 INTEGER ILAENV
143 EXTERNAL ilaenv
144* ..
145* .. External Subroutines ..
146 EXTERNAL xerbla, zptts2
147* ..
148* .. Intrinsic Functions ..
149 INTRINSIC max, min
150* ..
151* .. Executable Statements ..
152*
153* Test the input arguments.
154*
155 info = 0
156 upper = ( uplo.EQ.'U' .OR. uplo.EQ.'u' )
157 IF( .NOT.upper .AND. .NOT.( uplo.EQ.'L' .OR. uplo.EQ.'l' ) ) THEN
158 info = -1
159 ELSE IF( n.LT.0 ) THEN
160 info = -2
161 ELSE IF( nrhs.LT.0 ) THEN
162 info = -3
163 ELSE IF( ldb.LT.max( 1, n ) ) THEN
164 info = -7
165 END IF
166 IF( info.NE.0 ) THEN
167 CALL xerbla( 'ZPTTRS', -info )
168 RETURN
169 END IF
170*
171* Quick return if possible
172*
173 IF( n.EQ.0 .OR. nrhs.EQ.0 )
174 $ RETURN
175*
176* Determine the number of right-hand sides to solve at a time.
177*
178 IF( nrhs.EQ.1 ) THEN
179 nb = 1
180 ELSE
181 nb = max( 1, ilaenv( 1, 'ZPTTRS', uplo, n, nrhs, -1, -1 ) )
182 END IF
183*
184* Decode UPLO
185*
186 IF( upper ) THEN
187 iuplo = 1
188 ELSE
189 iuplo = 0
190 END IF
191*
192 IF( nb.GE.nrhs ) THEN
193 CALL zptts2( iuplo, n, nrhs, d, e, b, ldb )
194 ELSE
195 DO 10 j = 1, nrhs, nb
196 jb = min( nrhs-j+1, nb )
197 CALL zptts2( iuplo, n, jb, d, e, b( 1, j ), ldb )
198 10 CONTINUE
199 END IF
200*
201 RETURN
202*
203* End of ZPTTRS
204*
205 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zpttrs(uplo, n, nrhs, d, e, b, ldb, info)
ZPTTRS
Definition zpttrs.f:121
subroutine zptts2(iuplo, n, nrhs, d, e, b, ldb)
ZPTTS2 solves a tridiagonal system of the form AX=B using the L D LH factorization computed by spttrf...
Definition zptts2.f:113