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