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

◆ zgetrs()

subroutine zgetrs ( character trans,
integer n,
integer nrhs,
complex*16, dimension( lda, * ) a,
integer lda,
integer, dimension( * ) ipiv,
complex*16, dimension( ldb, * ) b,
integer ldb,
integer info )

ZGETRS

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

Purpose:
!>
!> ZGETRS solves a system of linear equations
!>    A * X = B,  A**T * X = B,  or  A**H * X = B
!> with a general N-by-N matrix A using the LU factorization computed
!> by ZGETRF.
!> 
Parameters
[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]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 factors L and U from the factorization A = P*L*U
!>          as computed by ZGETRF.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>          The pivot indices from ZGETRF; for 1<=i<=N, row i of the
!>          matrix was interchanged with row IPIV(i).
!> 
[in,out]B
!>          B is COMPLEX*16 array, dimension (LDB,NRHS)
!>          On entry, the right hand side matrix B.
!>          On exit, 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
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 118 of file zgetrs.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 TRANS
126 INTEGER INFO, LDA, LDB, N, NRHS
127* ..
128* .. Array Arguments ..
129 INTEGER IPIV( * )
130 COMPLEX*16 A( LDA, * ), B( LDB, * )
131* ..
132*
133* =====================================================================
134*
135* .. Parameters ..
136 COMPLEX*16 ONE
137 parameter( one = ( 1.0d+0, 0.0d+0 ) )
138* ..
139* .. Local Scalars ..
140 LOGICAL NOTRAN
141* ..
142* .. External Functions ..
143 LOGICAL LSAME
144 EXTERNAL lsame
145* ..
146* .. External Subroutines ..
147 EXTERNAL xerbla, zlaswp, ztrsm
148* ..
149* .. Intrinsic Functions ..
150 INTRINSIC max
151* ..
152* .. Executable Statements ..
153*
154* Test the input parameters.
155*
156 info = 0
157 notran = lsame( trans, 'N' )
158 IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) .AND. .NOT.
159 $ lsame( trans, 'C' ) ) THEN
160 info = -1
161 ELSE IF( n.LT.0 ) THEN
162 info = -2
163 ELSE IF( nrhs.LT.0 ) THEN
164 info = -3
165 ELSE IF( lda.LT.max( 1, n ) ) THEN
166 info = -5
167 ELSE IF( ldb.LT.max( 1, n ) ) THEN
168 info = -8
169 END IF
170 IF( info.NE.0 ) THEN
171 CALL xerbla( 'ZGETRS', -info )
172 RETURN
173 END IF
174*
175* Quick return if possible
176*
177 IF( n.EQ.0 .OR. nrhs.EQ.0 )
178 $ RETURN
179*
180 IF( notran ) THEN
181*
182* Solve A * X = B.
183*
184* Apply row interchanges to the right hand sides.
185*
186 CALL zlaswp( nrhs, b, ldb, 1, n, ipiv, 1 )
187*
188* Solve L*X = B, overwriting B with X.
189*
190 CALL ztrsm( 'Left', 'Lower', 'No transpose', 'Unit', n,
191 $ nrhs,
192 $ one, a, lda, b, ldb )
193*
194* Solve U*X = B, overwriting B with X.
195*
196 CALL ztrsm( 'Left', 'Upper', 'No transpose', 'Non-unit', n,
197 $ nrhs, one, a, lda, b, ldb )
198 ELSE
199*
200* Solve A**T * X = B or A**H * X = B.
201*
202* Solve U**T *X = B or U**H *X = B, overwriting B with X.
203*
204 CALL ztrsm( 'Left', 'Upper', trans, 'Non-unit', n, nrhs,
205 $ one,
206 $ a, lda, b, ldb )
207*
208* Solve L**T *X = B, or L**H *X = B overwriting B with X.
209*
210 CALL ztrsm( 'Left', 'Lower', trans, 'Unit', n, nrhs, one, a,
211 $ lda, b, ldb )
212*
213* Apply row interchanges to the solution vectors.
214*
215 CALL zlaswp( nrhs, b, ldb, 1, n, ipiv, -1 )
216 END IF
217*
218 RETURN
219*
220* End of ZGETRS
221*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zlaswp(n, a, lda, k1, k2, ipiv, incx)
ZLASWP performs a series of row interchanges on a general rectangular matrix.
Definition zlaswp.f:113
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: