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

◆ dgetrs()

subroutine dgetrs ( character  trans,
integer  n,
integer  nrhs,
double precision, dimension( lda, * )  a,
integer  lda,
integer, dimension( * )  ipiv,
double precision, dimension( ldb, * )  b,
integer  ldb,
integer  info 
)

DGETRS

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

Purpose:
 DGETRS solves a system of linear equations
    A * X = B  or  A**T * X = B
 with a general N-by-N matrix A using the LU factorization computed
 by DGETRF.
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**T* X = B  (Conjugate transpose = 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 DOUBLE PRECISION array, dimension (LDA,N)
          The factors L and U from the factorization A = P*L*U
          as computed by DGETRF.
[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 DGETRF; for 1<=i<=N, row i of the
          matrix was interchanged with row IPIV(i).
[in,out]B
          B is DOUBLE PRECISION 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 120 of file dgetrs.f.

121*
122* -- LAPACK computational routine --
123* -- LAPACK is a software package provided by Univ. of Tennessee, --
124* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
125*
126* .. Scalar Arguments ..
127 CHARACTER TRANS
128 INTEGER INFO, LDA, LDB, N, NRHS
129* ..
130* .. Array Arguments ..
131 INTEGER IPIV( * )
132 DOUBLE PRECISION A( LDA, * ), B( LDB, * )
133* ..
134*
135* =====================================================================
136*
137* .. Parameters ..
138 DOUBLE PRECISION ONE
139 parameter( one = 1.0d+0 )
140* ..
141* .. Local Scalars ..
142 LOGICAL NOTRAN
143* ..
144* .. External Functions ..
145 LOGICAL LSAME
146 EXTERNAL lsame
147* ..
148* .. External Subroutines ..
149 EXTERNAL dlaswp, dtrsm, xerbla
150* ..
151* .. Intrinsic Functions ..
152 INTRINSIC max
153* ..
154* .. Executable Statements ..
155*
156* Test the input parameters.
157*
158 info = 0
159 notran = lsame( trans, 'N' )
160 IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) .AND. .NOT.
161 $ lsame( trans, 'C' ) ) THEN
162 info = -1
163 ELSE IF( n.LT.0 ) THEN
164 info = -2
165 ELSE IF( nrhs.LT.0 ) THEN
166 info = -3
167 ELSE IF( lda.LT.max( 1, n ) ) THEN
168 info = -5
169 ELSE IF( ldb.LT.max( 1, n ) ) THEN
170 info = -8
171 END IF
172 IF( info.NE.0 ) THEN
173 CALL xerbla( 'DGETRS', -info )
174 RETURN
175 END IF
176*
177* Quick return if possible
178*
179 IF( n.EQ.0 .OR. nrhs.EQ.0 )
180 $ RETURN
181*
182 IF( notran ) THEN
183*
184* Solve A * X = B.
185*
186* Apply row interchanges to the right hand sides.
187*
188 CALL dlaswp( nrhs, b, ldb, 1, n, ipiv, 1 )
189*
190* Solve L*X = B, overwriting B with X.
191*
192 CALL dtrsm( 'Left', 'Lower', 'No transpose', 'Unit', n, nrhs,
193 $ one, a, lda, b, ldb )
194*
195* Solve U*X = B, overwriting B with X.
196*
197 CALL dtrsm( 'Left', 'Upper', 'No transpose', 'Non-unit', n,
198 $ nrhs, one, a, lda, b, ldb )
199 ELSE
200*
201* Solve A**T * X = B.
202*
203* Solve U**T *X = B, overwriting B with X.
204*
205 CALL dtrsm( 'Left', 'Upper', 'Transpose', 'Non-unit', n, nrhs,
206 $ one, a, lda, b, ldb )
207*
208* Solve L**T *X = B, overwriting B with X.
209*
210 CALL dtrsm( 'Left', 'Lower', 'Transpose', 'Unit', n, nrhs, one,
211 $ a, lda, b, ldb )
212*
213* Apply row interchanges to the solution vectors.
214*
215 CALL dlaswp( nrhs, b, ldb, 1, n, ipiv, -1 )
216 END IF
217*
218 RETURN
219*
220* End of DGETRS
221*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dlaswp(n, a, lda, k1, k2, ipiv, incx)
DLASWP performs a series of row interchanges on a general rectangular matrix.
Definition dlaswp.f:115
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dtrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRSM
Definition dtrsm.f:181
Here is the call graph for this function:
Here is the caller graph for this function: