1 *> \brief <b> SPTSV computes the solution to system of linear equations A * X = B for PT matrices</b>
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SPTSV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sptsv.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sptsv.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sptsv.f">
21 * SUBROUTINE SPTSV( 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 *> SPTSV computes the solution to a real system of linear equations
37 *> A*X = B, where A is an N-by-N symmetric positive definite tridiagonal
38 *> matrix, and X and B are N-by-NRHS matrices.
40 *> A is factored as A = L*D*L**T, and the factored form of A is then
41 *> used to solve the system of equations.
50 *> The order of the 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 *> On entry, the n diagonal elements of the tridiagonal matrix
64 *> A. On exit, the n diagonal elements of the diagonal matrix
65 *> D from the factorization A = L*D*L**T.
70 *> E is REAL array, dimension (N-1)
71 *> On entry, the (n-1) subdiagonal elements of the tridiagonal
72 *> matrix A. On exit, the (n-1) subdiagonal elements of the
73 *> unit bidiagonal factor L from the L*D*L**T factorization of
74 *> A. (E can also be regarded as the superdiagonal of the unit
75 *> bidiagonal factor U from the U**T*D*U factorization of A.)
80 *> B is REAL array, dimension (LDB,NRHS)
81 *> On entry, the N-by-NRHS right hand side matrix B.
82 *> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
88 *> The leading dimension of the array B. LDB >= max(1,N).
94 *> = 0: successful exit
95 *> < 0: if INFO = -i, the i-th argument had an illegal value
96 *> > 0: if INFO = i, the leading minor of order i is not
97 *> positive definite, and the solution has not been
98 *> computed. The factorization has not been completed
105 *> \author Univ. of Tennessee
106 *> \author Univ. of California Berkeley
107 *> \author Univ. of Colorado Denver
110 *> \date September 2012
112 *> \ingroup realPTsolve
114 * =====================================================================
115 SUBROUTINE SPTSV( N, NRHS, D, E, B, LDB, INFO )
117 * -- LAPACK driver routine (version 3.4.2) --
118 * -- LAPACK is a software package provided by Univ. of Tennessee, --
119 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
122 * .. Scalar Arguments ..
123 INTEGER INFO, LDB, N, NRHS
125 * .. Array Arguments ..
126 REAL B( LDB, * ), D( * ), E( * )
129 * =====================================================================
131 * .. External Subroutines ..
132 EXTERNAL SPTTRF, SPTTRS, XERBLA
134 * .. Intrinsic Functions ..
137 * .. Executable Statements ..
139 * Test the input parameters.
144 ELSE IF( NRHS.LT.0 ) THEN
146 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
150 CALL XERBLA( 'SPTSV ', -INFO )
154 * Compute the L*D*L**T (or U**T*D*U) factorization of A.
156 CALL SPTTRF( N, D, E, INFO )
159 * Solve the system A*X = B, overwriting B with X.
161 CALL SPTTRS( N, NRHS, D, E, B, LDB, INFO )