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

◆ ctrtrs()

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

CTRTRS

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

Purpose:
 CTRTRS 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.  A check is made to verify that A is nonsingular.
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 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 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 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 138 of file ctrtrs.f.

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