1 SUBROUTINE DGETRS
( TRANS
, N
, NRHS
, A
, LDA
, IPIV
, B
, LDB
, INFO
)
3 * -- LAPACK routine
(version
3.1) --
4 * Univ
. of Tennessee
, Univ
. of California Berkeley and NAG Ltd
..
7 * .. Scalar Arguments
..
9 INTEGER INFO
, LDA
, LDB
, N
, NRHS
11 * .. Array Arguments
..
13 DOUBLE PRECISION A
( LDA
, * ), B
( LDB
, * )
19 * DGETRS solves a system of linear equations
20 * A
* X
= B or A
' * X = B
21 * with a general N-by-N matrix A using the LU factorization computed
27 * TRANS (input) CHARACTER*1
28 * Specifies the form of the system of equations:
29 * = 'N
': A * X = B (No transpose)
30 * = 'T
': A'* X
= B
(Transpose
)
31 * = 'C': A
'* X = B (Conjugate transpose = Transpose)
34 * The order of the matrix A. N >= 0.
36 * NRHS (input) INTEGER
37 * The number of right hand sides, i.e., the number of columns
38 * of the matrix B. NRHS >= 0.
40 * A (input) DOUBLE PRECISION array, dimension (LDA,N)
41 * The factors L and U from the factorization A = P*L*U
42 * as computed by DGETRF.
45 * The leading dimension of the array A. LDA >= max(1,N).
47 * IPIV (input) INTEGER array, dimension (N)
48 * The pivot indices from DGETRF; for 1<=i<=N, row i of the
49 * matrix was interchanged with row IPIV(i).
51 * B (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
52 * On entry, the right hand side matrix B.
53 * On exit, the solution matrix X.
56 * The leading dimension of the array B. LDB >= max(1,N).
58 * INFO (output) INTEGER
59 * = 0: successful exit
60 * < 0: if INFO = -i, the i-th argument had an illegal value
62 * =====================================================================
66 PARAMETER ( ONE = 1.0D+0 )
71 * .. External Functions ..
75 * .. External Subroutines ..
76 EXTERNAL DLASWP, DTRSM, XERBLA
78 * .. Intrinsic Functions ..
81 * .. Executable Statements ..
83 * Test the input parameters.
86 NOTRAN = LSAME( TRANS, 'N
' )
87 IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T
' ) .AND. .NOT.
88 $ LSAME( TRANS, 'C
' ) ) THEN
90 ELSE IF( N.LT.0 ) THEN
92 ELSE IF( NRHS.LT.0 ) THEN
94 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
96 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
100 CALL XERBLA( 'DGETRS
', -INFO )
104 * Quick return if possible
106 IF( N.EQ.0 .OR. NRHS.EQ.0 )
113 * Apply row interchanges to the right hand sides.
115 CALL DLASWP( NRHS, B, LDB, 1, N, IPIV, 1 )
117 * Solve L*X = B, overwriting B with X.
119 CALL DTRSM( 'Left
', 'Lower
', 'No transpose
', 'Unit
', N, NRHS,
120 $ ONE, A, LDA, B, LDB )
122 * Solve U*X = B, overwriting B with X.
124 CALL DTRSM( 'Left
', 'Upper
', 'No transpose
', 'Non
-unit
', N,
125 $ NRHS, ONE, A, LDA, B, LDB )
130 * Solve U
'*X = B, overwriting B with X.
132 CALL DTRSM( 'Left
', 'Upper
', 'Transpose
', 'Non
-unit
', N, NRHS,
133 $ ONE, A, LDA, B, LDB )
135 * Solve L'*X
= B
, overwriting B with X
.
137 CALL DTRSM
( 'Left', 'Lower', 'Transpose', 'Unit', N
, NRHS
, ONE
,
140 * Apply row interchanges
to the solution vectors
.
142 CALL DLASWP
( NRHS
, B
, LDB
, 1, N
, IPIV
, -1 )