1 *> \brief \b DGTTS2 solves a system of linear equations with a tridiagonal matrix using the LU factorization computed by sgttrf.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DGTTS2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgtts2.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgtts2.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgtts2.f">
21 * SUBROUTINE DGTTS2( ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB )
23 * .. Scalar Arguments ..
24 * INTEGER ITRANS, LDB, N, NRHS
26 * .. Array Arguments ..
28 * DOUBLE PRECISION B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
37 *> DGTTS2 solves one of the systems of equations
38 *> A*X = B or A**T*X = B,
39 *> with a tridiagonal matrix A using the LU factorization computed
49 *> Specifies the form of the system of equations.
50 *> = 0: A * X = B (No transpose)
51 *> = 1: A**T* X = B (Transpose)
52 *> = 2: A**T* X = B (Conjugate transpose = Transpose)
58 *> The order of the matrix A.
64 *> The number of right hand sides, i.e., the number of columns
65 *> of the matrix B. NRHS >= 0.
70 *> DL is DOUBLE PRECISION array, dimension (N-1)
71 *> The (n-1) multipliers that define the matrix L from the
72 *> LU factorization of A.
77 *> D is DOUBLE PRECISION array, dimension (N)
78 *> The n diagonal elements of the upper triangular matrix U from
79 *> the LU factorization of A.
84 *> DU is DOUBLE PRECISION array, dimension (N-1)
85 *> The (n-1) elements of the first super-diagonal of U.
90 *> DU2 is DOUBLE PRECISION array, dimension (N-2)
91 *> The (n-2) elements of the second super-diagonal of U.
96 *> IPIV is INTEGER array, dimension (N)
97 *> The pivot indices; for 1 <= i <= n, row i of the matrix was
98 *> interchanged with row IPIV(i). IPIV(i) will always be either
99 *> i or i+1; IPIV(i) = i indicates a row interchange was not
105 *> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
106 *> On entry, the matrix of right hand side vectors B.
107 *> On exit, B is overwritten by the solution vectors X.
113 *> The leading dimension of the array B. LDB >= max(1,N).
119 *> \author Univ. of Tennessee
120 *> \author Univ. of California Berkeley
121 *> \author Univ. of Colorado Denver
124 *> \date September 2012
126 *> \ingroup doubleGTcomputational
128 * =====================================================================
129 SUBROUTINE DGTTS2( ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB )
131 * -- LAPACK computational routine (version 3.4.2) --
132 * -- LAPACK is a software package provided by Univ. of Tennessee, --
133 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136 * .. Scalar Arguments ..
137 INTEGER ITRANS, LDB, N, NRHS
139 * .. Array Arguments ..
141 DOUBLE PRECISION B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
144 * =====================================================================
146 * .. Local Scalars ..
148 DOUBLE PRECISION TEMP
150 * .. Executable Statements ..
152 * Quick return if possible
154 IF( N.EQ.0 .OR. NRHS.EQ.0 )
157 IF( ITRANS.EQ.0 ) THEN
159 * Solve A*X = B using the LU factorization of A,
160 * overwriting each right hand side vector with its solution.
170 TEMP = B( I+1-IP+I, J ) - DL( I )*B( IP, J )
171 B( I, J ) = B( IP, J )
177 B( N, J ) = B( N, J ) / D( N )
179 $ B( N-1, J ) = ( B( N-1, J )-DU( N-1 )*B( N, J ) ) /
181 DO 30 I = N - 2, 1, -1
182 B( I, J ) = ( B( I, J )-DU( I )*B( I+1, J )-DU2( I )*
183 $ B( I+2, J ) ) / D( I )
195 IF( IPIV( I ).EQ.I ) THEN
196 B( I+1, J ) = B( I+1, J ) - DL( I )*B( I, J )
199 B( I, J ) = B( I+1, J )
200 B( I+1, J ) = TEMP - DL( I )*B( I, J )
206 B( N, J ) = B( N, J ) / D( N )
208 $ B( N-1, J ) = ( B( N-1, J )-DU( N-1 )*B( N, J ) ) /
210 DO 50 I = N - 2, 1, -1
211 B( I, J ) = ( B( I, J )-DU( I )*B( I+1, J )-DU2( I )*
212 $ B( I+2, J ) ) / D( I )
218 * Solve A**T * X = B.
226 B( 1, J ) = B( 1, J ) / D( 1 )
228 $ B( 2, J ) = ( B( 2, J )-DU( 1 )*B( 1, J ) ) / D( 2 )
230 B( I, J ) = ( B( I, J )-DU( I-1 )*B( I-1, J )-DU2( I-2 )*
231 $ B( I-2, J ) ) / D( I )
236 DO 90 I = N - 1, 1, -1
238 TEMP = B( I, J ) - DL( I )*B( I+1, J )
239 B( I, J ) = B( IP, J )
252 B( 1, J ) = B( 1, J ) / D( 1 )
254 $ B( 2, J ) = ( B( 2, J )-DU( 1 )*B( 1, J ) ) / D( 2 )
256 B( I, J ) = ( B( I, J )-DU( I-1 )*B( I-1, J )-
257 $ DU2( I-2 )*B( I-2, J ) ) / D( I )
259 DO 110 I = N - 1, 1, -1
260 IF( IPIV( I ).EQ.I ) THEN
261 B( I, J ) = B( I, J ) - DL( I )*B( I+1, J )
264 B( I+1, J ) = B( I, J ) - DL( I )*TEMP