3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZPTTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zpttrs.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zpttrs.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpttrs.f">
21 * SUBROUTINE ZPTTRS( UPLO, N, NRHS, D, E, B, LDB, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDB, N, NRHS
27 * .. Array Arguments ..
28 * DOUBLE PRECISION D( * )
29 * COMPLEX*16 B( LDB, * ), E( * )
38 *> ZPTTRS solves a tridiagonal system of the form
40 *> using the factorization A = U**H *D* U or A = L*D*L**H computed by ZPTTRF.
41 *> D is a diagonal matrix specified in the vector D, U (or L) is a unit
42 *> bidiagonal matrix whose superdiagonal (subdiagonal) is specified in
43 *> the vector E, and X and B are N by NRHS matrices.
51 *> UPLO is CHARACTER*1
52 *> Specifies the form of the factorization and whether the
53 *> vector E is the superdiagonal of the upper bidiagonal factor
54 *> U or the subdiagonal of the lower bidiagonal factor L.
55 *> = 'U': A = U**H *D*U, E is the superdiagonal of U
56 *> = 'L': A = L*D*L**H, E is the subdiagonal of L
62 *> The order of the tridiagonal matrix A. N >= 0.
68 *> The number of right hand sides, i.e., the number of columns
69 *> of the matrix B. NRHS >= 0.
74 *> D is DOUBLE PRECISION array, dimension (N)
75 *> The n diagonal elements of the diagonal matrix D from the
76 *> factorization A = U**H *D*U or A = L*D*L**H.
81 *> E is COMPLEX*16 array, dimension (N-1)
82 *> If UPLO = 'U', the (n-1) superdiagonal elements of the unit
83 *> bidiagonal factor U from the factorization A = U**H*D*U.
84 *> If UPLO = 'L', the (n-1) subdiagonal elements of the unit
85 *> bidiagonal factor L from the factorization A = L*D*L**H.
90 *> B is COMPLEX*16 array, dimension (LDB,NRHS)
91 *> On entry, the right hand side vectors B for the system of
93 *> On exit, the solution vectors, X.
99 *> The leading dimension of the array B. LDB >= max(1,N).
105 *> = 0: successful exit
106 *> < 0: if INFO = -k, the k-th argument had an illegal value
112 *> \author Univ. of Tennessee
113 *> \author Univ. of California Berkeley
114 *> \author Univ. of Colorado Denver
119 *> \ingroup complex16PTcomputational
121 * =====================================================================
122 SUBROUTINE ZPTTRS( UPLO, N, NRHS, D, E, B, LDB, INFO )
124 * -- LAPACK computational routine (version 3.6.1) --
125 * -- LAPACK is a software package provided by Univ. of Tennessee, --
126 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129 * .. Scalar Arguments ..
131 INTEGER INFO, LDB, N, NRHS
133 * .. Array Arguments ..
134 DOUBLE PRECISION D( * )
135 COMPLEX*16 B( LDB, * ), E( * )
138 * =====================================================================
140 * .. Local Scalars ..
142 INTEGER IUPLO, J, JB, NB
144 * .. External Functions ..
148 * .. External Subroutines ..
149 EXTERNAL XERBLA, ZPTTS2
151 * .. Intrinsic Functions ..
154 * .. Executable Statements ..
156 * Test the input arguments.
159 UPPER = ( UPLO.EQ.'U' .OR. UPLO.EQ.'u' )
160 IF( .NOT.UPPER .AND. .NOT.( UPLO.EQ.'L' .OR. UPLO.EQ.'l' ) ) THEN
162 ELSE IF( N.LT.0 ) THEN
164 ELSE IF( NRHS.LT.0 ) THEN
166 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
170 CALL XERBLA( 'ZPTTRS', -INFO )
174 * Quick return if possible
176 IF( N.EQ.0 .OR. NRHS.EQ.0 )
179 * Determine the number of right-hand sides to solve at a time.
184 NB = MAX( 1, ILAENV( 1, 'ZPTTRS', UPLO, N, NRHS, -1, -1 ) )
195 IF( NB.GE.NRHS ) THEN
196 CALL ZPTTS2( IUPLO, N, NRHS, D, E, B, LDB )
198 DO 10 J = 1, NRHS, NB
199 JB = MIN( NRHS-J+1, NB )
200 CALL ZPTTS2( IUPLO, N, JB, D, E, B( 1, J ), LDB )