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