LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sptts2.f
Go to the documentation of this file.
1*> \brief \b SPTTS2 solves a tridiagonal system of the form AX=B using the L D LH factorization computed by spttrf.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SPTTS2 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sptts2.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sptts2.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sptts2.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE SPTTS2( N, NRHS, D, E, B, LDB )
22*
23* .. Scalar Arguments ..
24* INTEGER LDB, N, NRHS
25* ..
26* .. Array Arguments ..
27* REAL B( LDB, * ), D( * ), E( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> SPTTS2 solves a tridiagonal system of the form
37*> A * X = B
38*> using the L*D*L**T factorization of A computed by SPTTRF. 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 REAL 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 REAL 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 REAL 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* Authors:
91* ========
92*
93*> \author Univ. of Tennessee
94*> \author Univ. of California Berkeley
95*> \author Univ. of Colorado Denver
96*> \author NAG Ltd.
97*
98*> \ingroup ptts2
99*
100* =====================================================================
101 SUBROUTINE sptts2( N, NRHS, D, E, B, LDB )
102*
103* -- LAPACK computational routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 INTEGER LDB, N, NRHS
109* ..
110* .. Array Arguments ..
111 REAL B( LDB, * ), D( * ), E( * )
112* ..
113*
114* =====================================================================
115*
116* .. Local Scalars ..
117 INTEGER I, J
118* ..
119* .. External Subroutines ..
120 EXTERNAL sscal
121* ..
122* .. Executable Statements ..
123*
124* Quick return if possible
125*
126 IF( n.LE.1 ) THEN
127 IF( n.EQ.1 )
128 $ CALL sscal( nrhs, 1. / d( 1 ), b, ldb )
129 RETURN
130 END IF
131*
132* Solve A * X = B using the factorization A = L*D*L**T,
133* overwriting each right hand side vector with its solution.
134*
135 DO 30 j = 1, nrhs
136*
137* Solve L * x = b.
138*
139 DO 10 i = 2, n
140 b( i, j ) = b( i, j ) - b( i-1, j )*e( i-1 )
141 10 CONTINUE
142*
143* Solve D * L**T * x = b.
144*
145 b( n, j ) = b( n, j ) / d( n )
146 DO 20 i = n - 1, 1, -1
147 b( i, j ) = b( i, j ) / d( i ) - b( i+1, j )*e( i )
148 20 CONTINUE
149 30 CONTINUE
150*
151 RETURN
152*
153* End of SPTTS2
154*
155 END
subroutine sptts2(n, nrhs, d, e, b, ldb)
SPTTS2 solves a tridiagonal system of the form AX=B using the L D LH factorization computed by spttrf...
Definition sptts2.f:102
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79