3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SPTTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spttrs.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spttrs.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spttrs.f">
21 * SUBROUTINE SPTTRS( N, NRHS, D, E, B, LDB, INFO )
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDB, N, NRHS
26 * .. Array Arguments ..
27 * REAL B( LDB, * ), D( * ), E( * )
36 *> SPTTRS solves a tridiagonal system of the form
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.
50 *> The order of the tridiagonal matrix A. N >= 0.
56 *> The number of right hand sides, i.e., the number of columns
57 *> of the matrix B. NRHS >= 0.
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.
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.
78 *> B is REAL array, dimension (LDB,NRHS)
79 *> On entry, the right hand side vectors B for the system of
81 *> On exit, the solution vectors, X.
87 *> The leading dimension of the array B. LDB >= max(1,N).
93 *> = 0: successful exit
94 *> < 0: if INFO = -k, the k-th argument had an illegal value
100 *> \author Univ. of Tennessee
101 *> \author Univ. of California Berkeley
102 *> \author Univ. of Colorado Denver
105 *> \date September 2012
107 *> \ingroup realPTcomputational
109 * =====================================================================
110 SUBROUTINE SPTTRS( N, NRHS, D, E, B, LDB, INFO )
112 * -- LAPACK computational routine (version 3.4.2) --
113 * -- LAPACK is a software package provided by Univ. of Tennessee, --
114 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117 * .. Scalar Arguments ..
118 INTEGER INFO, LDB, N, NRHS
120 * .. Array Arguments ..
121 REAL B( LDB, * ), D( * ), E( * )
124 * =====================================================================
126 * .. Local Scalars ..
129 * .. External Functions ..
133 * .. External Subroutines ..
134 EXTERNAL SPTTS2, XERBLA
136 * .. Intrinsic Functions ..
139 * .. Executable Statements ..
141 * Test the input arguments.
146 ELSE IF( NRHS.LT.0 ) THEN
148 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
152 CALL XERBLA( 'SPTTRS', -INFO )
156 * Quick return if possible
158 IF( N.EQ.0 .OR. NRHS.EQ.0 )
161 * Determine the number of right-hand sides to solve at a time.
166 NB = MAX( 1, ILAENV( 1, 'SPTTRS', ' ', N, NRHS, -1, -1 ) )
169 IF( NB.GE.NRHS ) THEN
170 CALL SPTTS2( N, NRHS, D, E, B, LDB )
172 DO 10 J = 1, NRHS, NB
173 JB = MIN( NRHS-J+1, NB )
174 CALL SPTTS2( N, JB, D, E, B( 1, J ), LDB )