LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sgetrs.f
Go to the documentation of this file.
1*> \brief \b SGETRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SGETRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgetrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgetrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgetrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SGETRS( TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER TRANS
23* INTEGER INFO, LDA, LDB, N, NRHS
24* ..
25* .. Array Arguments ..
26* INTEGER IPIV( * )
27* REAL A( LDA, * ), B( LDB, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> SGETRS solves a system of linear equations
37*> A * X = B or A**T * X = B
38*> with a general N-by-N matrix A using the LU factorization computed
39*> by SGETRF.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] TRANS
46*> \verbatim
47*> TRANS is CHARACTER*1
48*> Specifies the form of the system of equations:
49*> = 'N': A * X = B (No transpose)
50*> = 'T': A**T* X = B (Transpose)
51*> = 'C': A**T* X = B (Conjugate transpose = Transpose)
52*> \endverbatim
53*>
54*> \param[in] N
55*> \verbatim
56*> N is INTEGER
57*> The order of the matrix A. N >= 0.
58*> \endverbatim
59*>
60*> \param[in] NRHS
61*> \verbatim
62*> NRHS is INTEGER
63*> The number of right hand sides, i.e., the number of columns
64*> of the matrix B. NRHS >= 0.
65*> \endverbatim
66*>
67*> \param[in] A
68*> \verbatim
69*> A is REAL array, dimension (LDA,N)
70*> The factors L and U from the factorization A = P*L*U
71*> as computed by SGETRF.
72*> \endverbatim
73*>
74*> \param[in] LDA
75*> \verbatim
76*> LDA is INTEGER
77*> The leading dimension of the array A. LDA >= max(1,N).
78*> \endverbatim
79*>
80*> \param[in] IPIV
81*> \verbatim
82*> IPIV is INTEGER array, dimension (N)
83*> The pivot indices from SGETRF; for 1<=i<=N, row i of the
84*> matrix was interchanged with row IPIV(i).
85*> \endverbatim
86*>
87*> \param[in,out] B
88*> \verbatim
89*> B is REAL array, dimension (LDB,NRHS)
90*> On entry, the right hand side matrix B.
91*> On exit, the solution matrix X.
92*> \endverbatim
93*>
94*> \param[in] LDB
95*> \verbatim
96*> LDB is INTEGER
97*> The leading dimension of the array B. LDB >= max(1,N).
98*> \endverbatim
99*>
100*> \param[out] INFO
101*> \verbatim
102*> INFO is INTEGER
103*> = 0: successful exit
104*> < 0: if INFO = -i, the i-th argument had an illegal value
105*> \endverbatim
106*
107* Authors:
108* ========
109*
110*> \author Univ. of Tennessee
111*> \author Univ. of California Berkeley
112*> \author Univ. of Colorado Denver
113*> \author NAG Ltd.
114*
115*> \ingroup getrs
116*
117* =====================================================================
118 SUBROUTINE sgetrs( TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
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 REAL A( LDA, * ), B( LDB, * )
131* ..
132*
133* =====================================================================
134*
135* .. Parameters ..
136 REAL ONE
137 parameter( one = 1.0e+0 )
138* ..
139* .. Local Scalars ..
140 LOGICAL NOTRAN
141* ..
142* .. External Functions ..
143 LOGICAL LSAME
144 EXTERNAL lsame
145* ..
146* .. External Subroutines ..
147 EXTERNAL slaswp, strsm, xerbla
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( 'SGETRS', -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 slaswp( nrhs, b, ldb, 1, n, ipiv, 1 )
187*
188* Solve L*X = B, overwriting B with X.
189*
190 CALL strsm( '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 strsm( 'Left', 'Upper', 'No transpose', 'Non-unit', n,
197 $ nrhs, one, a, lda, b, ldb )
198 ELSE
199*
200* Solve A**T * X = B.
201*
202* Solve U**T *X = B, overwriting B with X.
203*
204 CALL strsm( 'Left', 'Upper', 'Transpose', 'Non-unit', n,
205 $ nrhs,
206 $ one, a, lda, b, ldb )
207*
208* Solve L**T *X = B, overwriting B with X.
209*
210 CALL strsm( 'Left', 'Lower', 'Transpose', 'Unit', n, nrhs,
211 $ one,
212 $ a, lda, b, ldb )
213*
214* Apply row interchanges to the solution vectors.
215*
216 CALL slaswp( nrhs, b, ldb, 1, n, ipiv, -1 )
217 END IF
218*
219 RETURN
220*
221* End of SGETRS
222*
223 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
SGETRS
Definition sgetrs.f:119
subroutine slaswp(n, a, lda, k1, k2, ipiv, incx)
SLASWP performs a series of row interchanges on a general rectangular matrix.
Definition slaswp.f:113
subroutine strsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
STRSM
Definition strsm.f:181