LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ zpttrs()

subroutine zpttrs ( character uplo,
integer n,
integer nrhs,
double precision, dimension( * ) d,
complex*16, dimension( * ) e,
complex*16, dimension( ldb, * ) b,
integer ldb,
integer info )

ZPTTRS

Download ZPTTRS + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!> !> ZPTTRS solves a tridiagonal system of the form !> A * X = B !> using the factorization A = U**H *D* U or A = L*D*L**H computed by ZPTTRF. !> D is a diagonal matrix specified in the vector D, U (or L) is a unit !> bidiagonal matrix whose superdiagonal (subdiagonal) is specified in !> the vector E, and X and B are N by NRHS matrices. !>
Parameters
[in]UPLO
!> UPLO is CHARACTER*1 !> Specifies the form of the factorization and whether the !> vector E is the superdiagonal of the upper bidiagonal factor !> U or the subdiagonal of the lower bidiagonal factor L. !> = 'U': A = U**H *D*U, E is the superdiagonal of U !> = 'L': A = L*D*L**H, E is the subdiagonal of L !>
[in]N
!> N is INTEGER !> The order of the tridiagonal matrix A. N >= 0. !>
[in]NRHS
!> NRHS is INTEGER !> The number of right hand sides, i.e., the number of columns !> of the matrix B. NRHS >= 0. !>
[in]D
!> D is DOUBLE PRECISION array, dimension (N) !> The n diagonal elements of the diagonal matrix D from the !> factorization A = U**H *D*U or A = L*D*L**H. !>
[in]E
!> E is COMPLEX*16 array, dimension (N-1) !> If UPLO = 'U', the (n-1) superdiagonal elements of the unit !> bidiagonal factor U from the factorization A = U**H*D*U. !> If UPLO = 'L', the (n-1) subdiagonal elements of the unit !> bidiagonal factor L from the factorization A = L*D*L**H. !>
[in,out]B
!> B is COMPLEX*16 array, dimension (LDB,NRHS) !> On entry, the right hand side vectors B for the system of !> linear equations. !> On exit, the solution vectors, X. !>
[in]LDB
!> LDB is INTEGER !> The leading dimension of the array B. LDB >= max(1,N). !>
[out]INFO
!> INFO is INTEGER !> = 0: successful exit !> < 0: if INFO = -k, the k-th argument had an illegal value !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 118 of file zpttrs.f.

119*
120* -- LAPACK computational routine --
121* -- LAPACK is a software package provided by Univ. of Tennessee, --
122* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123*
124* .. Scalar Arguments ..
125 CHARACTER UPLO
126 INTEGER INFO, LDB, N, NRHS
127* ..
128* .. Array Arguments ..
129 DOUBLE PRECISION D( * )
130 COMPLEX*16 B( LDB, * ), E( * )
131* ..
132*
133* =====================================================================
134*
135* .. Local Scalars ..
136 LOGICAL UPPER
137 INTEGER IUPLO, J, JB, NB
138* ..
139* .. External Functions ..
140 INTEGER ILAENV
141 EXTERNAL ilaenv
142* ..
143* .. External Subroutines ..
144 EXTERNAL xerbla, zptts2
145* ..
146* .. Intrinsic Functions ..
147 INTRINSIC max, min
148* ..
149* .. Executable Statements ..
150*
151* Test the input arguments.
152*
153 info = 0
154 upper = ( uplo.EQ.'U' .OR. uplo.EQ.'u' )
155 IF( .NOT.upper .AND. .NOT.( uplo.EQ.'L' .OR. uplo.EQ.'l' ) ) THEN
156 info = -1
157 ELSE IF( n.LT.0 ) THEN
158 info = -2
159 ELSE IF( nrhs.LT.0 ) THEN
160 info = -3
161 ELSE IF( ldb.LT.max( 1, n ) ) THEN
162 info = -7
163 END IF
164 IF( info.NE.0 ) THEN
165 CALL xerbla( 'ZPTTRS', -info )
166 RETURN
167 END IF
168*
169* Quick return if possible
170*
171 IF( n.EQ.0 .OR. nrhs.EQ.0 )
172 $ RETURN
173*
174* Determine the number of right-hand sides to solve at a time.
175*
176 IF( nrhs.EQ.1 ) THEN
177 nb = 1
178 ELSE
179 nb = max( 1, ilaenv( 1, 'ZPTTRS', uplo, n, nrhs, -1, -1 ) )
180 END IF
181*
182* Decode UPLO
183*
184 IF( upper ) THEN
185 iuplo = 1
186 ELSE
187 iuplo = 0
188 END IF
189*
190 IF( nb.GE.nrhs ) THEN
191 CALL zptts2( iuplo, n, nrhs, d, e, b, ldb )
192 ELSE
193 DO 10 j = 1, nrhs, nb
194 jb = min( nrhs-j+1, nb )
195 CALL zptts2( iuplo, n, jb, d, e, b( 1, j ), ldb )
196 10 CONTINUE
197 END IF
198*
199 RETURN
200*
201* End of ZPTTRS
202*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:160
subroutine zptts2(iuplo, n, nrhs, d, e, b, ldb)
ZPTTS2 solves a tridiagonal system of the form AX=B using the L D LH factorization computed by spttrf...
Definition zptts2.f:111
Here is the call graph for this function:
Here is the caller graph for this function: