LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sgesv.f
Go to the documentation of this file.
1*> \addtogroup gesv
2*>
3*> \brief <b> SGESV computes the solution to system of linear equations A * X = B for GE matrices</b> (simple driver)
4*
5* =========== DOCUMENTATION ===========
6*
7* Online html documentation available at
8* http://www.netlib.org/lapack/explore-html/
9*
10*> \htmlonly
11*> Download SGESV + dependencies
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgesv.f">
13*> [TGZ]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgesv.f">
15*> [ZIP]</a>
16*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgesv.f">
17*> [TXT]</a>
18*> \endhtmlonly
19*
20* Definition:
21* ===========
22*
23* SUBROUTINE SGESV( N, NRHS, A, LDA, IPIV, B, LDB, INFO )
24*
25* .. Scalar Arguments ..
26* INTEGER INFO, LDA, LDB, N, NRHS
27* ..
28* .. Array Arguments ..
29* INTEGER IPIV( * )
30* REAL A( LDA, * ), B( LDB, * )
31* ..
32*
33*
34*> \par Purpose:
35* =============
36*>
37*> \verbatim
38*>
39*> SGESV computes the solution to a real system of linear equations
40*> A * X = B,
41*> where A is an N-by-N matrix and X and B are N-by-NRHS matrices.
42*>
43*> The LU decomposition with partial pivoting and row interchanges is
44*> used to factor A as
45*> A = P * L * U,
46*> where P is a permutation matrix, L is unit lower triangular, and U is
47*> upper triangular. The factored form of A is then used to solve the
48*> system of equations A * X = B.
49*> \endverbatim
50*
51* Arguments:
52* ==========
53*
54*> \param[in] N
55*> \verbatim
56*> N is INTEGER
57*> The number of linear equations, i.e., the order of the
58*> matrix A. N >= 0.
59*> \endverbatim
60*>
61*> \param[in] NRHS
62*> \verbatim
63*> NRHS is INTEGER
64*> The number of right hand sides, i.e., the number of columns
65*> of the matrix B. NRHS >= 0.
66*> \endverbatim
67*>
68*> \param[in,out] A
69*> \verbatim
70*> A is REAL array, dimension (LDA,N)
71*> On entry, the N-by-N coefficient matrix A.
72*> On exit, the factors L and U from the factorization
73*> A = P*L*U; the unit diagonal elements of L are not stored.
74*> \endverbatim
75*>
76*> \param[in] LDA
77*> \verbatim
78*> LDA is INTEGER
79*> The leading dimension of the array A. LDA >= max(1,N).
80*> \endverbatim
81*>
82*> \param[out] IPIV
83*> \verbatim
84*> IPIV is INTEGER array, dimension (N)
85*> The pivot indices that define the permutation matrix P;
86*> row i of the matrix was interchanged with row IPIV(i).
87*> \endverbatim
88*>
89*> \param[in,out] B
90*> \verbatim
91*> B is REAL array, dimension (LDB,NRHS)
92*> On entry, the N-by-NRHS matrix of right hand side matrix B.
93*> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
94*> \endverbatim
95*>
96*> \param[in] LDB
97*> \verbatim
98*> LDB is INTEGER
99*> The leading dimension of the array B. LDB >= max(1,N).
100*> \endverbatim
101*>
102*> \param[out] INFO
103*> \verbatim
104*> INFO is INTEGER
105*> = 0: successful exit
106*> < 0: if INFO = -i, the i-th argument had an illegal value
107*> > 0: if INFO = i, U(i,i) is exactly zero. The factorization
108*> has been completed, but the factor U is exactly
109*> singular, so the solution could not be computed.
110*> \endverbatim
111*
112* Authors:
113* ========
114*
115*> \author Univ. of Tennessee
116*> \author Univ. of California Berkeley
117*> \author Univ. of Colorado Denver
118*> \author NAG Ltd.
119*
120*> \ingroup gesv
121*
122* =====================================================================
123 SUBROUTINE sgesv( N, NRHS, A, LDA, IPIV, B, LDB, INFO )
124*
125* -- LAPACK driver routine --
126* -- LAPACK is a software package provided by Univ. of Tennessee, --
127* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
128*
129* .. Scalar Arguments ..
130 INTEGER INFO, LDA, LDB, N, NRHS
131* ..
132* .. Array Arguments ..
133 INTEGER IPIV( * )
134 REAL A( LDA, * ), B( LDB, * )
135* ..
136*
137* =====================================================================
138*
139* .. External Subroutines ..
140 EXTERNAL sgetrf, sgetrs, xerbla
141* ..
142* .. Intrinsic Functions ..
143 INTRINSIC max
144* ..
145* .. Executable Statements ..
146*
147* Test the input parameters.
148*
149 info = 0
150 IF( n.LT.0 ) THEN
151 info = -1
152 ELSE IF( nrhs.LT.0 ) THEN
153 info = -2
154 ELSE IF( lda.LT.max( 1, n ) ) THEN
155 info = -4
156 ELSE IF( ldb.LT.max( 1, n ) ) THEN
157 info = -7
158 END IF
159 IF( info.NE.0 ) THEN
160 CALL xerbla( 'SGESV ', -info )
161 RETURN
162 END IF
163*
164* Compute the LU factorization of A.
165*
166 CALL sgetrf( n, n, a, lda, ipiv, info )
167 IF( info.EQ.0 ) THEN
168*
169* Solve the system A*X = B, overwriting B with X.
170*
171 CALL sgetrs( 'No transpose', n, nrhs, a, lda, ipiv, b, ldb,
172 $ info )
173 END IF
174 RETURN
175*
176* End of SGESV
177*
178 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
Download SGESV + dependencies <a href="http://www.netlib.org/cgi-bin/netlibfiles....
Definition sgesv.f:124
subroutine sgetrf(m, n, a, lda, ipiv, info)
SGETRF
Definition sgetrf.f:108
subroutine sgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
SGETRS
Definition sgetrs.f:121