LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sptsv.f
Go to the documentation of this file.
1*> \brief <b> SPTSV computes the solution to system of linear equations A * X = B for PT matrices</b>
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SPTSV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sptsv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sptsv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sptsv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SPTSV( N, NRHS, D, E, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, LDB, N, NRHS
23* ..
24* .. Array Arguments ..
25* REAL B( LDB, * ), D( * ), E( * )
26* ..
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> SPTSV computes the solution to a real system of linear equations
35*> A*X = B, where A is an N-by-N symmetric positive definite tridiagonal
36*> matrix, and X and B are N-by-NRHS matrices.
37*>
38*> A is factored as A = L*D*L**T, and the factored form of A is then
39*> used to solve the system of equations.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] N
46*> \verbatim
47*> N is INTEGER
48*> The order of the matrix A. N >= 0.
49*> \endverbatim
50*>
51*> \param[in] NRHS
52*> \verbatim
53*> NRHS is INTEGER
54*> The number of right hand sides, i.e., the number of columns
55*> of the matrix B. NRHS >= 0.
56*> \endverbatim
57*>
58*> \param[in,out] D
59*> \verbatim
60*> D is REAL array, dimension (N)
61*> On entry, the n diagonal elements of the tridiagonal matrix
62*> A. On exit, the n diagonal elements of the diagonal matrix
63*> D from the factorization A = L*D*L**T.
64*> \endverbatim
65*>
66*> \param[in,out] E
67*> \verbatim
68*> E is REAL array, dimension (N-1)
69*> On entry, the (n-1) subdiagonal elements of the tridiagonal
70*> matrix A. On exit, the (n-1) subdiagonal elements of the
71*> unit bidiagonal factor L from the L*D*L**T factorization of
72*> A. (E can also be regarded as the superdiagonal of the unit
73*> bidiagonal factor U from the U**T*D*U factorization of A.)
74*> \endverbatim
75*>
76*> \param[in,out] B
77*> \verbatim
78*> B is REAL array, dimension (LDB,NRHS)
79*> On entry, the N-by-NRHS right hand side matrix B.
80*> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
81*> \endverbatim
82*>
83*> \param[in] LDB
84*> \verbatim
85*> LDB is INTEGER
86*> The leading dimension of the array B. LDB >= max(1,N).
87*> \endverbatim
88*>
89*> \param[out] INFO
90*> \verbatim
91*> INFO is INTEGER
92*> = 0: successful exit
93*> < 0: if INFO = -i, the i-th argument had an illegal value
94*> > 0: if INFO = i, the leading principal minor of order i
95*> is not positive, and the solution has not been
96*> computed. The factorization has not been completed
97*> unless i = N.
98*> \endverbatim
99*
100* Authors:
101* ========
102*
103*> \author Univ. of Tennessee
104*> \author Univ. of California Berkeley
105*> \author Univ. of Colorado Denver
106*> \author NAG Ltd.
107*
108*> \ingroup ptsv
109*
110* =====================================================================
111 SUBROUTINE sptsv( N, NRHS, D, E, B, LDB, INFO )
112*
113* -- LAPACK driver routine --
114* -- LAPACK is a software package provided by Univ. of Tennessee, --
115* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116*
117* .. Scalar Arguments ..
118 INTEGER INFO, LDB, N, NRHS
119* ..
120* .. Array Arguments ..
121 REAL B( LDB, * ), D( * ), E( * )
122* ..
123*
124* =====================================================================
125*
126* .. External Subroutines ..
127 EXTERNAL spttrf, spttrs, xerbla
128* ..
129* .. Intrinsic Functions ..
130 INTRINSIC max
131* ..
132* .. Executable Statements ..
133*
134* Test the input parameters.
135*
136 info = 0
137 IF( n.LT.0 ) THEN
138 info = -1
139 ELSE IF( nrhs.LT.0 ) THEN
140 info = -2
141 ELSE IF( ldb.LT.max( 1, n ) ) THEN
142 info = -6
143 END IF
144 IF( info.NE.0 ) THEN
145 CALL xerbla( 'SPTSV ', -info )
146 RETURN
147 END IF
148*
149* Compute the L*D*L**T (or U**T*D*U) factorization of A.
150*
151 CALL spttrf( n, d, e, info )
152 IF( info.EQ.0 ) THEN
153*
154* Solve the system A*X = B, overwriting B with X.
155*
156 CALL spttrs( n, nrhs, d, e, b, ldb, info )
157 END IF
158 RETURN
159*
160* End of SPTSV
161*
162 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sptsv(n, nrhs, d, e, b, ldb, info)
SPTSV computes the solution to system of linear equations A * X = B for PT matrices
Definition sptsv.f:112
subroutine spttrf(n, d, e, info)
SPTTRF
Definition spttrf.f:89
subroutine spttrs(n, nrhs, d, e, b, ldb, info)
SPTTRS
Definition spttrs.f:107