LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zgetri.f
Go to the documentation of this file.
1 *> \brief \b ZGETRI
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZGETRI + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgetri.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgetri.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgetri.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZGETRI( 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 * COMPLEX*16 A( LDA, * ), WORK( * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> ZGETRI computes the inverse of a matrix using the LU factorization
38 *> computed by ZGETRF.
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 COMPLEX*16 array, dimension (LDA,N)
56 *> On entry, the factors L and U from the factorization
57 *> A = P*L*U as computed by ZGETRF.
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 ZGETRF; 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 COMPLEX*16 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 complex16GEcomputational
113 *
114 * =====================================================================
115  SUBROUTINE zgetri( 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  COMPLEX*16 a( lda, * ), work( * )
128 * ..
129 *
130 * =====================================================================
131 *
132 * .. Parameters ..
133  COMPLEX*16 zero, one
134  parameter( zero = ( 0.0d+0, 0.0d+0 ),
135  $ one = ( 1.0d+0, 0.0d+0 ) )
136 * ..
137 * .. Local Scalars ..
138  LOGICAL lquery
139  INTEGER i, iws, j, jb, jj, jp, ldwork, lwkopt, nb,
140  $ nbmin, nn
141 * ..
142 * .. External Functions ..
143  INTEGER ilaenv
144  EXTERNAL ilaenv
145 * ..
146 * .. External Subroutines ..
147  EXTERNAL xerbla, zgemm, zgemv, zswap, ztrsm, ztrtri
148 * ..
149 * .. Intrinsic Functions ..
150  INTRINSIC max, min
151 * ..
152 * .. Executable Statements ..
153 *
154 * Test the input parameters.
155 *
156  info = 0
157  nb = ilaenv( 1, 'ZGETRI', ' ', n, -1, -1, -1 )
158  lwkopt = n*nb
159  work( 1 ) = lwkopt
160  lquery = ( lwork.EQ.-1 )
161  IF( n.LT.0 ) THEN
162  info = -1
163  ELSE IF( lda.LT.max( 1, n ) ) THEN
164  info = -3
165  ELSE IF( lwork.LT.max( 1, n ) .AND. .NOT.lquery ) THEN
166  info = -6
167  END IF
168  IF( info.NE.0 ) THEN
169  CALL xerbla( 'ZGETRI', -info )
170  return
171  ELSE IF( lquery ) THEN
172  return
173  END IF
174 *
175 * Quick return if possible
176 *
177  IF( n.EQ.0 )
178  $ return
179 *
180 * Form inv(U). If INFO > 0 from ZTRTRI, then U is singular,
181 * and the inverse is not computed.
182 *
183  CALL ztrtri( 'Upper', 'Non-unit', n, a, lda, info )
184  IF( info.GT.0 )
185  $ return
186 *
187  nbmin = 2
188  ldwork = n
189  IF( nb.GT.1 .AND. nb.LT.n ) THEN
190  iws = max( ldwork*nb, 1 )
191  IF( lwork.LT.iws ) THEN
192  nb = lwork / ldwork
193  nbmin = max( 2, ilaenv( 2, 'ZGETRI', ' ', n, -1, -1, -1 ) )
194  END IF
195  ELSE
196  iws = n
197  END IF
198 *
199 * Solve the equation inv(A)*L = inv(U) for inv(A).
200 *
201  IF( nb.LT.nbmin .OR. nb.GE.n ) THEN
202 *
203 * Use unblocked code.
204 *
205  DO 20 j = n, 1, -1
206 *
207 * Copy current column of L to WORK and replace with zeros.
208 *
209  DO 10 i = j + 1, n
210  work( i ) = a( i, j )
211  a( i, j ) = zero
212  10 continue
213 *
214 * Compute current column of inv(A).
215 *
216  IF( j.LT.n )
217  $ CALL zgemv( 'No transpose', n, n-j, -one, a( 1, j+1 ),
218  $ lda, work( j+1 ), 1, one, a( 1, j ), 1 )
219  20 continue
220  ELSE
221 *
222 * Use blocked code.
223 *
224  nn = ( ( n-1 ) / nb )*nb + 1
225  DO 50 j = nn, 1, -nb
226  jb = min( nb, n-j+1 )
227 *
228 * Copy current block column of L to WORK and replace with
229 * zeros.
230 *
231  DO 40 jj = j, j + jb - 1
232  DO 30 i = jj + 1, n
233  work( i+( jj-j )*ldwork ) = a( i, jj )
234  a( i, jj ) = zero
235  30 continue
236  40 continue
237 *
238 * Compute current block column of inv(A).
239 *
240  IF( j+jb.LE.n )
241  $ CALL zgemm( 'No transpose', 'No transpose', n, jb,
242  $ n-j-jb+1, -one, a( 1, j+jb ), lda,
243  $ work( j+jb ), ldwork, one, a( 1, j ), lda )
244  CALL ztrsm( 'Right', 'Lower', 'No transpose', 'Unit', n, jb,
245  $ one, work( j ), ldwork, a( 1, j ), lda )
246  50 continue
247  END IF
248 *
249 * Apply column interchanges.
250 *
251  DO 60 j = n - 1, 1, -1
252  jp = ipiv( j )
253  IF( jp.NE.j )
254  $ CALL zswap( n, a( 1, j ), 1, a( 1, jp ), 1 )
255  60 continue
256 *
257  work( 1 ) = iws
258  return
259 *
260 * End of ZGETRI
261 *
262  END