LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
chptri.f
Go to the documentation of this file.
1*> \brief \b CHPTRI
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CHPTRI + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chptri.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chptri.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chptri.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CHPTRI( UPLO, N, AP, IPIV, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, N
24* ..
25* .. Array Arguments ..
26* INTEGER IPIV( * )
27* COMPLEX AP( * ), WORK( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> CHPTRI computes the inverse of a complex Hermitian indefinite matrix
37*> A in packed storage using the factorization A = U*D*U**H or
38*> A = L*D*L**H computed by CHPTRF.
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] UPLO
45*> \verbatim
46*> UPLO is CHARACTER*1
47*> Specifies whether the details of the factorization are stored
48*> as an upper or lower triangular matrix.
49*> = 'U': Upper triangular, form is A = U*D*U**H;
50*> = 'L': Lower triangular, form is A = L*D*L**H.
51*> \endverbatim
52*>
53*> \param[in] N
54*> \verbatim
55*> N is INTEGER
56*> The order of the matrix A. N >= 0.
57*> \endverbatim
58*>
59*> \param[in,out] AP
60*> \verbatim
61*> AP is COMPLEX array, dimension (N*(N+1)/2)
62*> On entry, the block diagonal matrix D and the multipliers
63*> used to obtain the factor U or L as computed by CHPTRF,
64*> stored as a packed triangular matrix.
65*>
66*> On exit, if INFO = 0, the (Hermitian) inverse of the original
67*> matrix, stored as a packed triangular matrix. The j-th column
68*> of inv(A) is stored in the array AP as follows:
69*> if UPLO = 'U', AP(i + (j-1)*j/2) = inv(A)(i,j) for 1<=i<=j;
70*> if UPLO = 'L',
71*> AP(i + (j-1)*(2n-j)/2) = inv(A)(i,j) for j<=i<=n.
72*> \endverbatim
73*>
74*> \param[in] IPIV
75*> \verbatim
76*> IPIV is INTEGER array, dimension (N)
77*> Details of the interchanges and the block structure of D
78*> as determined by CHPTRF.
79*> \endverbatim
80*>
81*> \param[out] WORK
82*> \verbatim
83*> WORK is COMPLEX array, dimension (N)
84*> \endverbatim
85*>
86*> \param[out] INFO
87*> \verbatim
88*> INFO is INTEGER
89*> = 0: successful exit
90*> < 0: if INFO = -i, the i-th argument had an illegal value
91*> > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
92*> inverse could not be computed.
93*> \endverbatim
94*
95* Authors:
96* ========
97*
98*> \author Univ. of Tennessee
99*> \author Univ. of California Berkeley
100*> \author Univ. of Colorado Denver
101*> \author NAG Ltd.
102*
103*> \ingroup hptri
104*
105* =====================================================================
106 SUBROUTINE chptri( UPLO, N, AP, IPIV, WORK, INFO )
107*
108* -- LAPACK computational routine --
109* -- LAPACK is a software package provided by Univ. of Tennessee, --
110* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
111*
112* .. Scalar Arguments ..
113 CHARACTER UPLO
114 INTEGER INFO, N
115* ..
116* .. Array Arguments ..
117 INTEGER IPIV( * )
118 COMPLEX AP( * ), WORK( * )
119* ..
120*
121* =====================================================================
122*
123* .. Parameters ..
124 REAL ONE
125 COMPLEX CONE, ZERO
126 parameter( one = 1.0e+0, cone = ( 1.0e+0, 0.0e+0 ),
127 $ zero = ( 0.0e+0, 0.0e+0 ) )
128* ..
129* .. Local Scalars ..
130 LOGICAL UPPER
131 INTEGER J, K, KC, KCNEXT, KP, KPC, KSTEP, KX, NPP
132 REAL AK, AKP1, D, T
133 COMPLEX AKKP1, TEMP
134* ..
135* .. External Functions ..
136 LOGICAL LSAME
137 COMPLEX CDOTC
138 EXTERNAL lsame, cdotc
139* ..
140* .. External Subroutines ..
141 EXTERNAL ccopy, chpmv, cswap, xerbla
142* ..
143* .. Intrinsic Functions ..
144 INTRINSIC abs, conjg, real
145* ..
146* .. Executable Statements ..
147*
148* Test the input parameters.
149*
150 info = 0
151 upper = lsame( uplo, 'U' )
152 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
153 info = -1
154 ELSE IF( n.LT.0 ) THEN
155 info = -2
156 END IF
157 IF( info.NE.0 ) THEN
158 CALL xerbla( 'CHPTRI', -info )
159 RETURN
160 END IF
161*
162* Quick return if possible
163*
164 IF( n.EQ.0 )
165 $ RETURN
166*
167* Check that the diagonal matrix D is nonsingular.
168*
169 IF( upper ) THEN
170*
171* Upper triangular storage: examine D from bottom to top
172*
173 kp = n*( n+1 ) / 2
174 DO 10 info = n, 1, -1
175 IF( ipiv( info ).GT.0 .AND. ap( kp ).EQ.zero )
176 $ RETURN
177 kp = kp - info
178 10 CONTINUE
179 ELSE
180*
181* Lower triangular storage: examine D from top to bottom.
182*
183 kp = 1
184 DO 20 info = 1, n
185 IF( ipiv( info ).GT.0 .AND. ap( kp ).EQ.zero )
186 $ RETURN
187 kp = kp + n - info + 1
188 20 CONTINUE
189 END IF
190 info = 0
191*
192 IF( upper ) THEN
193*
194* Compute inv(A) from the factorization A = U*D*U**H.
195*
196* K is the main loop index, increasing from 1 to N in steps of
197* 1 or 2, depending on the size of the diagonal blocks.
198*
199 k = 1
200 kc = 1
201 30 CONTINUE
202*
203* If K > N, exit from loop.
204*
205 IF( k.GT.n )
206 $ GO TO 50
207*
208 kcnext = kc + k
209 IF( ipiv( k ).GT.0 ) THEN
210*
211* 1 x 1 diagonal block
212*
213* Invert the diagonal block.
214*
215 ap( kc+k-1 ) = one / real( ap( kc+k-1 ) )
216*
217* Compute column K of the inverse.
218*
219 IF( k.GT.1 ) THEN
220 CALL ccopy( k-1, ap( kc ), 1, work, 1 )
221 CALL chpmv( uplo, k-1, -cone, ap, work, 1, zero,
222 $ ap( kc ), 1 )
223 ap( kc+k-1 ) = ap( kc+k-1 ) -
224 $ real( cdotc( k-1, work, 1, ap( kc ),
225 $ 1 ) )
226 END IF
227 kstep = 1
228 ELSE
229*
230* 2 x 2 diagonal block
231*
232* Invert the diagonal block.
233*
234 t = abs( ap( kcnext+k-1 ) )
235 ak = real( ap( kc+k-1 ) ) / t
236 akp1 = real( ap( kcnext+k ) ) / t
237 akkp1 = ap( kcnext+k-1 ) / t
238 d = t*( ak*akp1-one )
239 ap( kc+k-1 ) = akp1 / d
240 ap( kcnext+k ) = ak / d
241 ap( kcnext+k-1 ) = -akkp1 / d
242*
243* Compute columns K and K+1 of the inverse.
244*
245 IF( k.GT.1 ) THEN
246 CALL ccopy( k-1, ap( kc ), 1, work, 1 )
247 CALL chpmv( uplo, k-1, -cone, ap, work, 1, zero,
248 $ ap( kc ), 1 )
249 ap( kc+k-1 ) = ap( kc+k-1 ) -
250 $ real( cdotc( k-1, work, 1, ap( kc ),
251 $ 1 ) )
252 ap( kcnext+k-1 ) = ap( kcnext+k-1 ) -
253 $ cdotc( k-1, ap( kc ), 1,
254 $ ap( kcnext ),
255 $ 1 )
256 CALL ccopy( k-1, ap( kcnext ), 1, work, 1 )
257 CALL chpmv( uplo, k-1, -cone, ap, work, 1, zero,
258 $ ap( kcnext ), 1 )
259 ap( kcnext+k ) = ap( kcnext+k ) -
260 $ real( cdotc( k-1, work, 1,
261 $ ap( kcnext ),
262 $ 1 ) )
263 END IF
264 kstep = 2
265 kcnext = kcnext + k + 1
266 END IF
267*
268 kp = abs( ipiv( k ) )
269 IF( kp.NE.k ) THEN
270*
271* Interchange rows and columns K and KP in the leading
272* submatrix A(1:k+1,1:k+1)
273*
274 kpc = ( kp-1 )*kp / 2 + 1
275 CALL cswap( kp-1, ap( kc ), 1, ap( kpc ), 1 )
276 kx = kpc + kp - 1
277 DO 40 j = kp + 1, k - 1
278 kx = kx + j - 1
279 temp = conjg( ap( kc+j-1 ) )
280 ap( kc+j-1 ) = conjg( ap( kx ) )
281 ap( kx ) = temp
282 40 CONTINUE
283 ap( kc+kp-1 ) = conjg( ap( kc+kp-1 ) )
284 temp = ap( kc+k-1 )
285 ap( kc+k-1 ) = ap( kpc+kp-1 )
286 ap( kpc+kp-1 ) = temp
287 IF( kstep.EQ.2 ) THEN
288 temp = ap( kc+k+k-1 )
289 ap( kc+k+k-1 ) = ap( kc+k+kp-1 )
290 ap( kc+k+kp-1 ) = temp
291 END IF
292 END IF
293*
294 k = k + kstep
295 kc = kcnext
296 GO TO 30
297 50 CONTINUE
298*
299 ELSE
300*
301* Compute inv(A) from the factorization A = L*D*L**H.
302*
303* K is the main loop index, increasing from 1 to N in steps of
304* 1 or 2, depending on the size of the diagonal blocks.
305*
306 npp = n*( n+1 ) / 2
307 k = n
308 kc = npp
309 60 CONTINUE
310*
311* If K < 1, exit from loop.
312*
313 IF( k.LT.1 )
314 $ GO TO 80
315*
316 kcnext = kc - ( n-k+2 )
317 IF( ipiv( k ).GT.0 ) THEN
318*
319* 1 x 1 diagonal block
320*
321* Invert the diagonal block.
322*
323 ap( kc ) = one / real( ap( kc ) )
324*
325* Compute column K of the inverse.
326*
327 IF( k.LT.n ) THEN
328 CALL ccopy( n-k, ap( kc+1 ), 1, work, 1 )
329 CALL chpmv( uplo, n-k, -cone, ap( kc+n-k+1 ), work, 1,
330 $ zero, ap( kc+1 ), 1 )
331 ap( kc ) = ap( kc ) - real( cdotc( n-k, work, 1,
332 $ ap( kc+1 ), 1 ) )
333 END IF
334 kstep = 1
335 ELSE
336*
337* 2 x 2 diagonal block
338*
339* Invert the diagonal block.
340*
341 t = abs( ap( kcnext+1 ) )
342 ak = real( ap( kcnext ) ) / t
343 akp1 = real( ap( kc ) ) / t
344 akkp1 = ap( kcnext+1 ) / t
345 d = t*( ak*akp1-one )
346 ap( kcnext ) = akp1 / d
347 ap( kc ) = ak / d
348 ap( kcnext+1 ) = -akkp1 / d
349*
350* Compute columns K-1 and K of the inverse.
351*
352 IF( k.LT.n ) THEN
353 CALL ccopy( n-k, ap( kc+1 ), 1, work, 1 )
354 CALL chpmv( uplo, n-k, -cone, ap( kc+( n-k+1 ) ),
355 $ work,
356 $ 1, zero, ap( kc+1 ), 1 )
357 ap( kc ) = ap( kc ) - real( cdotc( n-k, work, 1,
358 $ ap( kc+1 ), 1 ) )
359 ap( kcnext+1 ) = ap( kcnext+1 ) -
360 $ cdotc( n-k, ap( kc+1 ), 1,
361 $ ap( kcnext+2 ), 1 )
362 CALL ccopy( n-k, ap( kcnext+2 ), 1, work, 1 )
363 CALL chpmv( uplo, n-k, -cone, ap( kc+( n-k+1 ) ),
364 $ work,
365 $ 1, zero, ap( kcnext+2 ), 1 )
366 ap( kcnext ) = ap( kcnext ) -
367 $ real( cdotc( n-k, work, 1,
368 $ ap( kcnext+2 ),
369 $ 1 ) )
370 END IF
371 kstep = 2
372 kcnext = kcnext - ( n-k+3 )
373 END IF
374*
375 kp = abs( ipiv( k ) )
376 IF( kp.NE.k ) THEN
377*
378* Interchange rows and columns K and KP in the trailing
379* submatrix A(k-1:n,k-1:n)
380*
381 kpc = npp - ( n-kp+1 )*( n-kp+2 ) / 2 + 1
382 IF( kp.LT.n )
383 $ CALL cswap( n-kp, ap( kc+kp-k+1 ), 1, ap( kpc+1 ), 1 )
384 kx = kc + kp - k
385 DO 70 j = k + 1, kp - 1
386 kx = kx + n - j + 1
387 temp = conjg( ap( kc+j-k ) )
388 ap( kc+j-k ) = conjg( ap( kx ) )
389 ap( kx ) = temp
390 70 CONTINUE
391 ap( kc+kp-k ) = conjg( ap( kc+kp-k ) )
392 temp = ap( kc )
393 ap( kc ) = ap( kpc )
394 ap( kpc ) = temp
395 IF( kstep.EQ.2 ) THEN
396 temp = ap( kc-n+k-1 )
397 ap( kc-n+k-1 ) = ap( kc-n+kp-1 )
398 ap( kc-n+kp-1 ) = temp
399 END IF
400 END IF
401*
402 k = k - kstep
403 kc = kcnext
404 GO TO 60
405 80 CONTINUE
406 END IF
407*
408 RETURN
409*
410* End of CHPTRI
411*
412 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
Definition ccopy.f:81
subroutine chpmv(uplo, n, alpha, ap, x, incx, beta, y, incy)
CHPMV
Definition chpmv.f:149
subroutine chptri(uplo, n, ap, ipiv, work, info)
CHPTRI
Definition chptri.f:107
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81