LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sgetri.f
Go to the documentation of this file.
1 *> \brief \b SGETRI
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SGETRI + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgetri.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgetri.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgetri.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SGETRI( N, A, LDA, IPIV, WORK, LWORK, INFO )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, LWORK, N
25 * ..
26 * .. Array Arguments ..
27 * INTEGER IPIV( * )
28 * REAL A( LDA, * ), WORK( * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> SGETRI computes the inverse of a matrix using the LU factorization
38 *> computed by SGETRF.
39 *>
40 *> This method inverts U and then computes inv(A) by solving the system
41 *> inv(A)*L = inv(U) for inv(A).
42 *> \endverbatim
43 *
44 * Arguments:
45 * ==========
46 *
47 *> \param[in] N
48 *> \verbatim
49 *> N is INTEGER
50 *> The order of the matrix A. N >= 0.
51 *> \endverbatim
52 *>
53 *> \param[in,out] A
54 *> \verbatim
55 *> A is REAL array, dimension (LDA,N)
56 *> On entry, the factors L and U from the factorization
57 *> A = P*L*U as computed by SGETRF.
58 *> On exit, if INFO = 0, the inverse of the original matrix A.
59 *> \endverbatim
60 *>
61 *> \param[in] LDA
62 *> \verbatim
63 *> LDA is INTEGER
64 *> The leading dimension of the array A. LDA >= max(1,N).
65 *> \endverbatim
66 *>
67 *> \param[in] IPIV
68 *> \verbatim
69 *> IPIV is INTEGER array, dimension (N)
70 *> The pivot indices from SGETRF; for 1<=i<=N, row i of the
71 *> matrix was interchanged with row IPIV(i).
72 *> \endverbatim
73 *>
74 *> \param[out] WORK
75 *> \verbatim
76 *> WORK is REAL array, dimension (MAX(1,LWORK))
77 *> On exit, if INFO=0, then WORK(1) returns the optimal LWORK.
78 *> \endverbatim
79 *>
80 *> \param[in] LWORK
81 *> \verbatim
82 *> LWORK is INTEGER
83 *> The dimension of the array WORK. LWORK >= max(1,N).
84 *> For optimal performance LWORK >= N*NB, where NB is
85 *> the optimal blocksize returned by ILAENV.
86 *>
87 *> If LWORK = -1, then a workspace query is assumed; the routine
88 *> only calculates the optimal size of the WORK array, returns
89 *> this value as the first entry of the WORK array, and no error
90 *> message related to LWORK is issued by XERBLA.
91 *> \endverbatim
92 *>
93 *> \param[out] INFO
94 *> \verbatim
95 *> INFO is INTEGER
96 *> = 0: successful exit
97 *> < 0: if INFO = -i, the i-th argument had an illegal value
98 *> > 0: if INFO = i, U(i,i) is exactly zero; the matrix is
99 *> singular and its inverse could not be computed.
100 *> \endverbatim
101 *
102 * Authors:
103 * ========
104 *
105 *> \author Univ. of Tennessee
106 *> \author Univ. of California Berkeley
107 *> \author Univ. of Colorado Denver
108 *> \author NAG Ltd.
109 *
110 *> \date November 2011
111 *
112 *> \ingroup realGEcomputational
113 *
114 * =====================================================================
115  SUBROUTINE sgetri( N, A, LDA, IPIV, WORK, LWORK, INFO )
116 *
117 * -- LAPACK computational routine (version 3.4.0) --
118 * -- LAPACK is a software package provided by Univ. of Tennessee, --
119 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120 * November 2011
121 *
122 * .. Scalar Arguments ..
123  INTEGER INFO, LDA, LWORK, N
124 * ..
125 * .. Array Arguments ..
126  INTEGER IPIV( * )
127  REAL A( lda, * ), WORK( * )
128 * ..
129 *
130 * =====================================================================
131 *
132 * .. Parameters ..
133  REAL ZERO, ONE
134  parameter ( zero = 0.0e+0, one = 1.0e+0 )
135 * ..
136 * .. Local Scalars ..
137  LOGICAL LQUERY
138  INTEGER I, IWS, J, JB, JJ, JP, LDWORK, LWKOPT, NB,
139  $ nbmin, nn
140 * ..
141 * .. External Functions ..
142  INTEGER ILAENV
143  EXTERNAL ilaenv
144 * ..
145 * .. External Subroutines ..
146  EXTERNAL sgemm, sgemv, sswap, strsm, strtri, xerbla
147 * ..
148 * .. Intrinsic Functions ..
149  INTRINSIC max, min
150 * ..
151 * .. Executable Statements ..
152 *
153 * Test the input parameters.
154 *
155  info = 0
156  nb = ilaenv( 1, 'SGETRI', ' ', n, -1, -1, -1 )
157  lwkopt = n*nb
158  work( 1 ) = lwkopt
159  lquery = ( lwork.EQ.-1 )
160  IF( n.LT.0 ) THEN
161  info = -1
162  ELSE IF( lda.LT.max( 1, n ) ) THEN
163  info = -3
164  ELSE IF( lwork.LT.max( 1, n ) .AND. .NOT.lquery ) THEN
165  info = -6
166  END IF
167  IF( info.NE.0 ) THEN
168  CALL xerbla( 'SGETRI', -info )
169  RETURN
170  ELSE IF( lquery ) THEN
171  RETURN
172  END IF
173 *
174 * Quick return if possible
175 *
176  IF( n.EQ.0 )
177  $ RETURN
178 *
179 * Form inv(U). If INFO > 0 from STRTRI, then U is singular,
180 * and the inverse is not computed.
181 *
182  CALL strtri( 'Upper', 'Non-unit', n, a, lda, info )
183  IF( info.GT.0 )
184  $ RETURN
185 *
186  nbmin = 2
187  ldwork = n
188  IF( nb.GT.1 .AND. nb.LT.n ) THEN
189  iws = max( ldwork*nb, 1 )
190  IF( lwork.LT.iws ) THEN
191  nb = lwork / ldwork
192  nbmin = max( 2, ilaenv( 2, 'SGETRI', ' ', n, -1, -1, -1 ) )
193  END IF
194  ELSE
195  iws = n
196  END IF
197 *
198 * Solve the equation inv(A)*L = inv(U) for inv(A).
199 *
200  IF( nb.LT.nbmin .OR. nb.GE.n ) THEN
201 *
202 * Use unblocked code.
203 *
204  DO 20 j = n, 1, -1
205 *
206 * Copy current column of L to WORK and replace with zeros.
207 *
208  DO 10 i = j + 1, n
209  work( i ) = a( i, j )
210  a( i, j ) = zero
211  10 CONTINUE
212 *
213 * Compute current column of inv(A).
214 *
215  IF( j.LT.n )
216  $ CALL sgemv( 'No transpose', n, n-j, -one, a( 1, j+1 ),
217  $ lda, work( j+1 ), 1, one, a( 1, j ), 1 )
218  20 CONTINUE
219  ELSE
220 *
221 * Use blocked code.
222 *
223  nn = ( ( n-1 ) / nb )*nb + 1
224  DO 50 j = nn, 1, -nb
225  jb = min( nb, n-j+1 )
226 *
227 * Copy current block column of L to WORK and replace with
228 * zeros.
229 *
230  DO 40 jj = j, j + jb - 1
231  DO 30 i = jj + 1, n
232  work( i+( jj-j )*ldwork ) = a( i, jj )
233  a( i, jj ) = zero
234  30 CONTINUE
235  40 CONTINUE
236 *
237 * Compute current block column of inv(A).
238 *
239  IF( j+jb.LE.n )
240  $ CALL sgemm( 'No transpose', 'No transpose', n, jb,
241  $ n-j-jb+1, -one, a( 1, j+jb ), lda,
242  $ work( j+jb ), ldwork, one, a( 1, j ), lda )
243  CALL strsm( 'Right', 'Lower', 'No transpose', 'Unit', n, jb,
244  $ one, work( j ), ldwork, a( 1, j ), lda )
245  50 CONTINUE
246  END IF
247 *
248 * Apply column interchanges.
249 *
250  DO 60 j = n - 1, 1, -1
251  jp = ipiv( j )
252  IF( jp.NE.j )
253  $ CALL sswap( n, a( 1, j ), 1, a( 1, jp ), 1 )
254  60 CONTINUE
255 *
256  work( 1 ) = iws
257  RETURN
258 *
259 * End of SGETRI
260 *
261  END
subroutine strsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
STRSM
Definition: strsm.f:183
subroutine sgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
SGEMM
Definition: sgemm.f:189
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine sgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SGEMV
Definition: sgemv.f:158
subroutine sswap(N, SX, INCX, SY, INCY)
SSWAP
Definition: sswap.f:53
subroutine strtri(UPLO, DIAG, N, A, LDA, INFO)
STRTRI
Definition: strtri.f:111
subroutine sgetri(N, A, LDA, IPIV, WORK, LWORK, INFO)
SGETRI
Definition: sgetri.f:116