LAPACK 3.12.1
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*> Download SPTTS2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sptts2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sptts2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sptts2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SPTTS2( N, NRHS, D, E, B, LDB )
20*
21* .. Scalar Arguments ..
22* INTEGER 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*> SPTTS2 solves a tridiagonal system of the form
35*> A * X = B
36*> using the L*D*L**T factorization of A computed by SPTTRF. D is a
37*> diagonal matrix specified in the vector D, L is a unit bidiagonal
38*> matrix whose subdiagonal is specified in the vector E, and X and B
39*> are N by NRHS matrices.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] N
46*> \verbatim
47*> N is INTEGER
48*> The order of the tridiagonal 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] D
59*> \verbatim
60*> D is REAL array, dimension (N)
61*> The n diagonal elements of the diagonal matrix D from the
62*> L*D*L**T factorization of A.
63*> \endverbatim
64*>
65*> \param[in] E
66*> \verbatim
67*> E is REAL array, dimension (N-1)
68*> The (n-1) subdiagonal elements of the unit bidiagonal factor
69*> L from the L*D*L**T factorization of A. E can also be regarded
70*> as the superdiagonal of the unit bidiagonal factor U from the
71*> factorization A = U**T*D*U.
72*> \endverbatim
73*>
74*> \param[in,out] B
75*> \verbatim
76*> B is REAL array, dimension (LDB,NRHS)
77*> On entry, the right hand side vectors B for the system of
78*> linear equations.
79*> On exit, the solution vectors, X.
80*> \endverbatim
81*>
82*> \param[in] LDB
83*> \verbatim
84*> LDB is INTEGER
85*> The leading dimension of the array B. LDB >= max(1,N).
86*> \endverbatim
87*
88* Authors:
89* ========
90*
91*> \author Univ. of Tennessee
92*> \author Univ. of California Berkeley
93*> \author Univ. of Colorado Denver
94*> \author NAG Ltd.
95*
96*> \ingroup ptts2
97*
98* =====================================================================
99 SUBROUTINE sptts2( N, NRHS, D, E, B, LDB )
100*
101* -- LAPACK computational routine --
102* -- LAPACK is a software package provided by Univ. of Tennessee, --
103* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
104*
105* .. Scalar Arguments ..
106 INTEGER LDB, N, NRHS
107* ..
108* .. Array Arguments ..
109 REAL B( LDB, * ), D( * ), E( * )
110* ..
111*
112* =====================================================================
113*
114* .. Local Scalars ..
115 INTEGER I, J
116* ..
117* .. External Subroutines ..
118 EXTERNAL sscal
119* ..
120* .. Executable Statements ..
121*
122* Quick return if possible
123*
124 IF( n.LE.1 ) THEN
125 IF( n.EQ.1 )
126 $ CALL sscal( nrhs, 1. / d( 1 ), b, ldb )
127 RETURN
128 END IF
129*
130* Solve A * X = B using the factorization A = L*D*L**T,
131* overwriting each right hand side vector with its solution.
132*
133 DO 30 j = 1, nrhs
134*
135* Solve L * x = b.
136*
137 DO 10 i = 2, n
138 b( i, j ) = b( i, j ) - b( i-1, j )*e( i-1 )
139 10 CONTINUE
140*
141* Solve D * L**T * x = b.
142*
143 b( n, j ) = b( n, j ) / d( n )
144 DO 20 i = n - 1, 1, -1
145 b( i, j ) = b( i, j ) / d( i ) - b( i+1, j )*e( i )
146 20 CONTINUE
147 30 CONTINUE
148*
149 RETURN
150*
151* End of SPTTS2
152*
153 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:100
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79