LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ztrtrs()

subroutine ztrtrs ( character uplo,
character trans,
character diag,
integer n,
integer nrhs,
complex*16, dimension( lda, * ) a,
integer lda,
complex*16, dimension( ldb, * ) b,
integer ldb,
integer info )

ZTRTRS

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

Purpose:
!>
!> ZTRTRS solves a triangular system of the form
!>
!>    A * X = B,  A**T * X = B,  or  A**H * X = B,
!>
!> where A is a triangular matrix of order N, and B is an N-by-NRHS matrix.
!>
!> This subroutine verifies that A is nonsingular, but callers should note that only exact
!> singularity is detected. It is conceivable for one or more diagonal elements of A to be
!> subnormally tiny numbers without this subroutine signalling an error.
!>
!> If a possible loss of numerical precision due to near-singular matrices is a concern, the
!> caller should verify that A is nonsingular within some tolerance before calling this subroutine.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  A is upper triangular;
!>          = 'L':  A is lower triangular.
!> 
[in]TRANS
!>          TRANS is CHARACTER*1
!>          Specifies the form of the system of equations:
!>          = 'N':  A * X = B     (No transpose)
!>          = 'T':  A**T * X = B  (Transpose)
!>          = 'C':  A**H * X = B  (Conjugate transpose)
!> 
[in]DIAG
!>          DIAG is CHARACTER*1
!>          = 'N':  A is non-unit triangular;
!>          = 'U':  A is unit triangular.
!> 
[in]N
!>          N is INTEGER
!>          The order of the 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]A
!>          A is COMPLEX*16 array, dimension (LDA,N)
!>          The triangular matrix A.  If UPLO = 'U', the leading N-by-N
!>          upper triangular part of the array A contains the upper
!>          triangular matrix, and the strictly lower triangular part of
!>          A is not referenced.  If UPLO = 'L', the leading N-by-N lower
!>          triangular part of the array A contains the lower triangular
!>          matrix, and the strictly upper triangular part of A is not
!>          referenced.  If DIAG = 'U', the diagonal elements of A are
!>          also not referenced and are assumed to be 1.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in,out]B
!>          B is COMPLEX*16 array, dimension (LDB,NRHS)
!>          On entry, the right hand side matrix B.
!>          On exit, if INFO = 0, the solution matrix 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 = -i, the i-th argument had an illegal value
!>          > 0:  if INFO = i, the i-th diagonal element of A is exactly zero,
!>               indicating that the matrix is singular and the solutions
!>               X have not been computed.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 142 of file ztrtrs.f.

144*
145* -- LAPACK computational routine --
146* -- LAPACK is a software package provided by Univ. of Tennessee, --
147* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148*
149* .. Scalar Arguments ..
150 CHARACTER DIAG, TRANS, UPLO
151 INTEGER INFO, LDA, LDB, N, NRHS
152* ..
153* .. Array Arguments ..
154 COMPLEX*16 A( LDA, * ), B( LDB, * )
155* ..
156*
157* =====================================================================
158*
159* .. Parameters ..
160 COMPLEX*16 ZERO, ONE
161 parameter( zero = ( 0.0d+0, 0.0d+0 ),
162 $ one = ( 1.0d+0, 0.0d+0 ) )
163* ..
164* .. Local Scalars ..
165 LOGICAL NOUNIT
166* ..
167* .. External Functions ..
168 LOGICAL LSAME
169 EXTERNAL lsame
170* ..
171* .. External Subroutines ..
172 EXTERNAL xerbla, ztrsm
173* ..
174* .. Intrinsic Functions ..
175 INTRINSIC max
176* ..
177* .. Executable Statements ..
178*
179* Test the input parameters.
180*
181 info = 0
182 nounit = lsame( diag, 'N' )
183 IF( .NOT.lsame( uplo, 'U' ) .AND.
184 $ .NOT.lsame( uplo, 'L' ) ) THEN
185 info = -1
186 ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.
187 $ lsame( trans, 'T' ) .AND.
188 $ .NOT.lsame( trans, 'C' ) ) THEN
189 info = -2
190 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
191 info = -3
192 ELSE IF( n.LT.0 ) THEN
193 info = -4
194 ELSE IF( nrhs.LT.0 ) THEN
195 info = -5
196 ELSE IF( lda.LT.max( 1, n ) ) THEN
197 info = -7
198 ELSE IF( ldb.LT.max( 1, n ) ) THEN
199 info = -9
200 END IF
201 IF( info.NE.0 ) THEN
202 CALL xerbla( 'ZTRTRS', -info )
203 RETURN
204 END IF
205*
206* Quick return if possible
207*
208 IF( n.EQ.0 )
209 $ RETURN
210*
211* Check for singularity.
212*
213 IF( nounit ) THEN
214 DO 10 info = 1, n
215 IF( a( info, info ).EQ.zero )
216 $ RETURN
217 10 CONTINUE
218 END IF
219 info = 0
220*
221* Solve A * x = b, A**T * x = b, or A**H * x = b.
222*
223 CALL ztrsm( 'Left', uplo, trans, diag, n, nrhs, one, a, lda, b,
224 $ ldb )
225*
226 RETURN
227*
228* End of ZTRTRS
229*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine ztrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
ZTRSM
Definition ztrsm.f:180
Here is the call graph for this function:
Here is the caller graph for this function: