LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zhetrs.f
Go to the documentation of this file.
1*> \brief \b ZHETRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZHETRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhetrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhetrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhetrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZHETRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, LDB, N, NRHS
24* ..
25* .. Array Arguments ..
26* INTEGER IPIV( * )
27* COMPLEX*16 A( LDA, * ), B( LDB, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZHETRS solves a system of linear equations A*X = B with a complex
37*> Hermitian matrix A using the factorization A = U*D*U**H or
38*> A = L*D*L**H computed by ZHETRF.
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] 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] A
67*> \verbatim
68*> A is COMPLEX*16 array, dimension (LDA,N)
69*> The block diagonal matrix D and the multipliers used to
70*> obtain the factor U or L as computed by ZHETRF.
71*> \endverbatim
72*>
73*> \param[in] LDA
74*> \verbatim
75*> LDA is INTEGER
76*> The leading dimension of the array A. LDA >= max(1,N).
77*> \endverbatim
78*>
79*> \param[in] IPIV
80*> \verbatim
81*> IPIV is INTEGER array, dimension (N)
82*> Details of the interchanges and the block structure of D
83*> as determined by ZHETRF.
84*> \endverbatim
85*>
86*> \param[in,out] B
87*> \verbatim
88*> B is COMPLEX*16 array, dimension (LDB,NRHS)
89*> On entry, the right hand side matrix B.
90*> On exit, the solution matrix X.
91*> \endverbatim
92*>
93*> \param[in] LDB
94*> \verbatim
95*> LDB is INTEGER
96*> The leading dimension of the array B. LDB >= max(1,N).
97*> \endverbatim
98*>
99*> \param[out] INFO
100*> \verbatim
101*> INFO is INTEGER
102*> = 0: successful exit
103*> < 0: if INFO = -i, the i-th argument had an illegal value
104*> \endverbatim
105*
106* Authors:
107* ========
108*
109*> \author Univ. of Tennessee
110*> \author Univ. of California Berkeley
111*> \author Univ. of Colorado Denver
112*> \author NAG Ltd.
113*
114*> \ingroup hetrs
115*
116* =====================================================================
117 SUBROUTINE zhetrs( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
118*
119* -- LAPACK computational routine --
120* -- LAPACK is a software package provided by Univ. of Tennessee, --
121* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
122*
123* .. Scalar Arguments ..
124 CHARACTER UPLO
125 INTEGER INFO, LDA, LDB, N, NRHS
126* ..
127* .. Array Arguments ..
128 INTEGER IPIV( * )
129 COMPLEX*16 A( LDA, * ), B( LDB, * )
130* ..
131*
132* =====================================================================
133*
134* .. Parameters ..
135 COMPLEX*16 ONE
136 parameter( one = ( 1.0d+0, 0.0d+0 ) )
137* ..
138* .. Local Scalars ..
139 LOGICAL UPPER
140 INTEGER J, K, KP
141 DOUBLE PRECISION S
142 COMPLEX*16 AK, AKM1, AKM1K, BK, BKM1, DENOM
143* ..
144* .. External Functions ..
145 LOGICAL LSAME
146 EXTERNAL lsame
147* ..
148* .. External Subroutines ..
149 EXTERNAL xerbla, zdscal, zgemv, zgeru, zlacgv,
150 $ zswap
151* ..
152* .. Intrinsic Functions ..
153 INTRINSIC dble, dconjg, max
154* ..
155* .. Executable Statements ..
156*
157 info = 0
158 upper = lsame( uplo, 'U' )
159 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
160 info = -1
161 ELSE IF( n.LT.0 ) THEN
162 info = -2
163 ELSE IF( nrhs.LT.0 ) THEN
164 info = -3
165 ELSE IF( lda.LT.max( 1, n ) ) THEN
166 info = -5
167 ELSE IF( ldb.LT.max( 1, n ) ) THEN
168 info = -8
169 END IF
170 IF( info.NE.0 ) THEN
171 CALL xerbla( 'ZHETRS', -info )
172 RETURN
173 END IF
174*
175* Quick return if possible
176*
177 IF( n.EQ.0 .OR. nrhs.EQ.0 )
178 $ RETURN
179*
180 IF( upper ) THEN
181*
182* Solve A*X = B, where A = U*D*U**H.
183*
184* First solve U*D*X = B, overwriting B with X.
185*
186* K is the main loop index, decreasing from N to 1 in steps of
187* 1 or 2, depending on the size of the diagonal blocks.
188*
189 k = n
190 10 CONTINUE
191*
192* If K < 1, exit from loop.
193*
194 IF( k.LT.1 )
195 $ GO TO 30
196*
197 IF( ipiv( k ).GT.0 ) THEN
198*
199* 1 x 1 diagonal block
200*
201* Interchange rows K and IPIV(K).
202*
203 kp = ipiv( k )
204 IF( kp.NE.k )
205 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
206*
207* Multiply by inv(U(K)), where U(K) is the transformation
208* stored in column K of A.
209*
210 CALL zgeru( k-1, nrhs, -one, a( 1, k ), 1, b( k, 1 ),
211 $ ldb,
212 $ b( 1, 1 ), ldb )
213*
214* Multiply by the inverse of the diagonal block.
215*
216 s = dble( one ) / dble( a( k, k ) )
217 CALL zdscal( nrhs, s, b( k, 1 ), ldb )
218 k = k - 1
219 ELSE
220*
221* 2 x 2 diagonal block
222*
223* Interchange rows K-1 and -IPIV(K).
224*
225 kp = -ipiv( k )
226 IF( kp.NE.k-1 )
227 $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
228*
229* Multiply by inv(U(K)), where U(K) is the transformation
230* stored in columns K-1 and K of A.
231*
232 CALL zgeru( k-2, nrhs, -one, a( 1, k ), 1, b( k, 1 ),
233 $ ldb,
234 $ b( 1, 1 ), ldb )
235 CALL zgeru( k-2, nrhs, -one, a( 1, k-1 ), 1, b( k-1, 1 ),
236 $ ldb, b( 1, 1 ), ldb )
237*
238* Multiply by the inverse of the diagonal block.
239*
240 akm1k = a( k-1, k )
241 akm1 = a( k-1, k-1 ) / akm1k
242 ak = a( k, k ) / dconjg( akm1k )
243 denom = akm1*ak - one
244 DO 20 j = 1, nrhs
245 bkm1 = b( k-1, j ) / akm1k
246 bk = b( k, j ) / dconjg( akm1k )
247 b( k-1, j ) = ( ak*bkm1-bk ) / denom
248 b( k, j ) = ( akm1*bk-bkm1 ) / denom
249 20 CONTINUE
250 k = k - 2
251 END IF
252*
253 GO TO 10
254 30 CONTINUE
255*
256* Next solve U**H *X = B, overwriting B with X.
257*
258* K is the main loop index, increasing from 1 to N in steps of
259* 1 or 2, depending on the size of the diagonal blocks.
260*
261 k = 1
262 40 CONTINUE
263*
264* If K > N, exit from loop.
265*
266 IF( k.GT.n )
267 $ GO TO 50
268*
269 IF( ipiv( k ).GT.0 ) THEN
270*
271* 1 x 1 diagonal block
272*
273* Multiply by inv(U**H(K)), where U(K) is the transformation
274* stored in column K of A.
275*
276 IF( k.GT.1 ) THEN
277 CALL zlacgv( nrhs, b( k, 1 ), ldb )
278 CALL zgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
279 $ ldb, a( 1, k ), 1, one, b( k, 1 ), ldb )
280 CALL zlacgv( nrhs, b( k, 1 ), ldb )
281 END IF
282*
283* Interchange rows K and IPIV(K).
284*
285 kp = ipiv( k )
286 IF( kp.NE.k )
287 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
288 k = k + 1
289 ELSE
290*
291* 2 x 2 diagonal block
292*
293* Multiply by inv(U**H(K+1)), where U(K+1) is the transformation
294* stored in columns K and K+1 of A.
295*
296 IF( k.GT.1 ) THEN
297 CALL zlacgv( nrhs, b( k, 1 ), ldb )
298 CALL zgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
299 $ ldb, a( 1, k ), 1, one, b( k, 1 ), ldb )
300 CALL zlacgv( nrhs, b( k, 1 ), ldb )
301*
302 CALL zlacgv( nrhs, b( k+1, 1 ), ldb )
303 CALL zgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
304 $ ldb, a( 1, k+1 ), 1, one, b( k+1, 1 ), ldb )
305 CALL zlacgv( nrhs, b( k+1, 1 ), ldb )
306 END IF
307*
308* Interchange rows K and -IPIV(K).
309*
310 kp = -ipiv( k )
311 IF( kp.NE.k )
312 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
313 k = k + 2
314 END IF
315*
316 GO TO 40
317 50 CONTINUE
318*
319 ELSE
320*
321* Solve A*X = B, where A = L*D*L**H.
322*
323* First solve L*D*X = B, overwriting B with X.
324*
325* K is the main loop index, increasing from 1 to N in steps of
326* 1 or 2, depending on the size of the diagonal blocks.
327*
328 k = 1
329 60 CONTINUE
330*
331* If K > N, exit from loop.
332*
333 IF( k.GT.n )
334 $ GO TO 80
335*
336 IF( ipiv( k ).GT.0 ) THEN
337*
338* 1 x 1 diagonal block
339*
340* Interchange rows K and IPIV(K).
341*
342 kp = ipiv( k )
343 IF( kp.NE.k )
344 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
345*
346* Multiply by inv(L(K)), where L(K) is the transformation
347* stored in column K of A.
348*
349 IF( k.LT.n )
350 $ CALL zgeru( n-k, nrhs, -one, a( k+1, k ), 1, b( k,
351 $ 1 ),
352 $ ldb, b( k+1, 1 ), ldb )
353*
354* Multiply by the inverse of the diagonal block.
355*
356 s = dble( one ) / dble( a( k, k ) )
357 CALL zdscal( nrhs, s, b( k, 1 ), ldb )
358 k = k + 1
359 ELSE
360*
361* 2 x 2 diagonal block
362*
363* Interchange rows K+1 and -IPIV(K).
364*
365 kp = -ipiv( k )
366 IF( kp.NE.k+1 )
367 $ CALL zswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ), ldb )
368*
369* Multiply by inv(L(K)), where L(K) is the transformation
370* stored in columns K and K+1 of A.
371*
372 IF( k.LT.n-1 ) THEN
373 CALL zgeru( n-k-1, nrhs, -one, a( k+2, k ), 1, b( k,
374 $ 1 ),
375 $ ldb, b( k+2, 1 ), ldb )
376 CALL zgeru( n-k-1, nrhs, -one, a( k+2, k+1 ), 1,
377 $ b( k+1, 1 ), ldb, b( k+2, 1 ), ldb )
378 END IF
379*
380* Multiply by the inverse of the diagonal block.
381*
382 akm1k = a( k+1, k )
383 akm1 = a( k, k ) / dconjg( akm1k )
384 ak = a( k+1, k+1 ) / akm1k
385 denom = akm1*ak - one
386 DO 70 j = 1, nrhs
387 bkm1 = b( k, j ) / dconjg( akm1k )
388 bk = b( k+1, j ) / akm1k
389 b( k, j ) = ( ak*bkm1-bk ) / denom
390 b( k+1, j ) = ( akm1*bk-bkm1 ) / denom
391 70 CONTINUE
392 k = k + 2
393 END IF
394*
395 GO TO 60
396 80 CONTINUE
397*
398* Next solve L**H *X = B, overwriting B with X.
399*
400* K is the main loop index, decreasing from N to 1 in steps of
401* 1 or 2, depending on the size of the diagonal blocks.
402*
403 k = n
404 90 CONTINUE
405*
406* If K < 1, exit from loop.
407*
408 IF( k.LT.1 )
409 $ GO TO 100
410*
411 IF( ipiv( k ).GT.0 ) THEN
412*
413* 1 x 1 diagonal block
414*
415* Multiply by inv(L**H(K)), where L(K) is the transformation
416* stored in column K of A.
417*
418 IF( k.LT.n ) THEN
419 CALL zlacgv( nrhs, b( k, 1 ), ldb )
420 CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
421 $ b( k+1, 1 ), ldb, a( k+1, k ), 1, one,
422 $ b( k, 1 ), ldb )
423 CALL zlacgv( nrhs, b( k, 1 ), ldb )
424 END IF
425*
426* Interchange rows K and IPIV(K).
427*
428 kp = ipiv( k )
429 IF( kp.NE.k )
430 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
431 k = k - 1
432 ELSE
433*
434* 2 x 2 diagonal block
435*
436* Multiply by inv(L**H(K-1)), where L(K-1) is the transformation
437* stored in columns K-1 and K of A.
438*
439 IF( k.LT.n ) THEN
440 CALL zlacgv( nrhs, b( k, 1 ), ldb )
441 CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
442 $ b( k+1, 1 ), ldb, a( k+1, k ), 1, one,
443 $ b( k, 1 ), ldb )
444 CALL zlacgv( nrhs, b( k, 1 ), ldb )
445*
446 CALL zlacgv( nrhs, b( k-1, 1 ), ldb )
447 CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
448 $ b( k+1, 1 ), ldb, a( k+1, k-1 ), 1, one,
449 $ b( k-1, 1 ), ldb )
450 CALL zlacgv( nrhs, b( k-1, 1 ), ldb )
451 END IF
452*
453* Interchange rows K and -IPIV(K).
454*
455 kp = -ipiv( k )
456 IF( kp.NE.k )
457 $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
458 k = k - 2
459 END IF
460*
461 GO TO 90
462 100 CONTINUE
463 END IF
464*
465 RETURN
466*
467* End of ZHETRS
468*
469 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zgeru(m, n, alpha, x, incx, y, incy, a, lda)
ZGERU
Definition zgeru.f:130
subroutine zhetrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
ZHETRS
Definition zhetrs.f:118
subroutine zlacgv(n, x, incx)
ZLACGV conjugates a complex vector.
Definition zlacgv.f:72
subroutine zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78
subroutine zswap(n, zx, incx, zy, incy)
ZSWAP
Definition zswap.f:81