3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DGTTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgttrs.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgttrs.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgttrs.f">
21 * SUBROUTINE DGTTRS( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB,
24 * .. Scalar Arguments ..
26 * INTEGER INFO, LDB, N, NRHS
28 * .. Array Arguments ..
30 * DOUBLE PRECISION B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
39 *> DGTTRS solves one of the systems of equations
40 *> A*X = B or A**T*X = B,
41 *> with a tridiagonal matrix A using the LU factorization computed
50 *> TRANS is CHARACTER*1
51 *> Specifies the form of the system of equations.
52 *> = 'N': A * X = B (No transpose)
53 *> = 'T': A**T* X = B (Transpose)
54 *> = 'C': A**T* X = B (Conjugate transpose = Transpose)
60 *> The order of the matrix A.
66 *> The number of right hand sides, i.e., the number of columns
67 *> of the matrix B. NRHS >= 0.
72 *> DL is DOUBLE PRECISION array, dimension (N-1)
73 *> The (n-1) multipliers that define the matrix L from the
74 *> LU factorization of A.
79 *> D is DOUBLE PRECISION array, dimension (N)
80 *> The n diagonal elements of the upper triangular matrix U from
81 *> the LU factorization of A.
86 *> DU is DOUBLE PRECISION array, dimension (N-1)
87 *> The (n-1) elements of the first super-diagonal of U.
92 *> DU2 is DOUBLE PRECISION array, dimension (N-2)
93 *> The (n-2) elements of the second super-diagonal of U.
98 *> IPIV is INTEGER array, dimension (N)
99 *> The pivot indices; for 1 <= i <= n, row i of the matrix was
100 *> interchanged with row IPIV(i). IPIV(i) will always be either
101 *> i or i+1; IPIV(i) = i indicates a row interchange was not
107 *> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
108 *> On entry, the matrix of right hand side vectors B.
109 *> On exit, B is overwritten by the solution vectors X.
115 *> The leading dimension of the array B. LDB >= max(1,N).
121 *> = 0: successful exit
122 *> < 0: if INFO = -i, the i-th argument had an illegal value
128 *> \author Univ. of Tennessee
129 *> \author Univ. of California Berkeley
130 *> \author Univ. of Colorado Denver
133 *> \date September 2012
135 *> \ingroup doubleGTcomputational
137 * =====================================================================
138 SUBROUTINE DGTTRS( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB,
141 * -- LAPACK computational routine (version 3.4.2) --
142 * -- LAPACK is a software package provided by Univ. of Tennessee, --
143 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146 * .. Scalar Arguments ..
148 INTEGER INFO, LDB, N, NRHS
150 * .. Array Arguments ..
152 DOUBLE PRECISION B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
155 * =====================================================================
157 * .. Local Scalars ..
159 INTEGER ITRANS, J, JB, NB
161 * .. External Functions ..
165 * .. External Subroutines ..
166 EXTERNAL DGTTS2, XERBLA
168 * .. Intrinsic Functions ..
171 * .. Executable Statements ..
174 NOTRAN = ( TRANS.EQ.'N' .OR. TRANS.EQ.'n' )
175 IF( .NOT.NOTRAN .AND. .NOT.( TRANS.EQ.'T' .OR. TRANS.EQ.
176 $ 't' ) .AND. .NOT.( TRANS.EQ.'C' .OR. TRANS.EQ.'c' ) ) THEN
178 ELSE IF( N.LT.0 ) THEN
180 ELSE IF( NRHS.LT.0 ) THEN
182 ELSE IF( LDB.LT.MAX( N, 1 ) ) THEN
186 CALL XERBLA( 'DGTTRS', -INFO )
190 * Quick return if possible
192 IF( N.EQ.0 .OR. NRHS.EQ.0 )
203 * Determine the number of right-hand sides to solve at a time.
208 NB = MAX( 1, ILAENV( 1, 'DGTTRS', TRANS, N, NRHS, -1, -1 ) )
211 IF( NB.GE.NRHS ) THEN
212 CALL DGTTS2( ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB )
214 DO 10 J = 1, NRHS, NB
215 JB = MIN( NRHS-J+1, NB )
216 CALL DGTTS2( ITRANS, N, JB, DL, D, DU, DU2, IPIV, B( 1, J ),