LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zhptrs.f
Go to the documentation of this file.
1 *> \brief \b ZHPTRS
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZHPTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhptrs.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhptrs.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhptrs.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZHPTRS( UPLO, N, NRHS, AP, IPIV, B, LDB, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER UPLO
25 * INTEGER INFO, LDB, N, NRHS
26 * ..
27 * .. Array Arguments ..
28 * INTEGER IPIV( * )
29 * COMPLEX*16 AP( * ), B( LDB, * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> ZHPTRS solves a system of linear equations A*X = B with a complex
39 *> Hermitian matrix A stored in packed format using the factorization
40 *> A = U*D*U**H or A = L*D*L**H computed by ZHPTRF.
41 *> \endverbatim
42 *
43 * Arguments:
44 * ==========
45 *
46 *> \param[in] UPLO
47 *> \verbatim
48 *> UPLO is CHARACTER*1
49 *> Specifies whether the details of the factorization are stored
50 *> as an upper or lower triangular matrix.
51 *> = 'U': Upper triangular, form is A = U*D*U**H;
52 *> = 'L': Lower triangular, form is A = L*D*L**H.
53 *> \endverbatim
54 *>
55 *> \param[in] N
56 *> \verbatim
57 *> N is INTEGER
58 *> The order of the matrix A. N >= 0.
59 *> \endverbatim
60 *>
61 *> \param[in] NRHS
62 *> \verbatim
63 *> NRHS is INTEGER
64 *> The number of right hand sides, i.e., the number of columns
65 *> of the matrix B. NRHS >= 0.
66 *> \endverbatim
67 *>
68 *> \param[in] AP
69 *> \verbatim
70 *> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
71 *> The block diagonal matrix D and the multipliers used to
72 *> obtain the factor U or L as computed by ZHPTRF, stored as a
73 *> packed triangular matrix.
74 *> \endverbatim
75 *>
76 *> \param[in] IPIV
77 *> \verbatim
78 *> IPIV is INTEGER array, dimension (N)
79 *> Details of the interchanges and the block structure of D
80 *> as determined by ZHPTRF.
81 *> \endverbatim
82 *>
83 *> \param[in,out] B
84 *> \verbatim
85 *> B is COMPLEX*16 array, dimension (LDB,NRHS)
86 *> On entry, the right hand side matrix B.
87 *> On exit, the solution matrix X.
88 *> \endverbatim
89 *>
90 *> \param[in] LDB
91 *> \verbatim
92 *> LDB is INTEGER
93 *> The leading dimension of the array B. LDB >= max(1,N).
94 *> \endverbatim
95 *>
96 *> \param[out] INFO
97 *> \verbatim
98 *> INFO is INTEGER
99 *> = 0: successful exit
100 *> < 0: if INFO = -i, the i-th argument had an illegal value
101 *> \endverbatim
102 *
103 * Authors:
104 * ========
105 *
106 *> \author Univ. of Tennessee
107 *> \author Univ. of California Berkeley
108 *> \author Univ. of Colorado Denver
109 *> \author NAG Ltd.
110 *
111 *> \date November 2011
112 *
113 *> \ingroup complex16OTHERcomputational
114 *
115 * =====================================================================
116  SUBROUTINE zhptrs( UPLO, N, NRHS, AP, IPIV, B, LDB, INFO )
117 *
118 * -- LAPACK computational routine (version 3.4.0) --
119 * -- LAPACK is a software package provided by Univ. of Tennessee, --
120 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
121 * November 2011
122 *
123 * .. Scalar Arguments ..
124  CHARACTER UPLO
125  INTEGER INFO, LDB, N, NRHS
126 * ..
127 * .. Array Arguments ..
128  INTEGER IPIV( * )
129  COMPLEX*16 AP( * ), 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, KC, 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, zswap
150 * ..
151 * .. Intrinsic Functions ..
152  INTRINSIC dble, dconjg, max
153 * ..
154 * .. Executable Statements ..
155 *
156  info = 0
157  upper = lsame( uplo, 'U' )
158  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
159  info = -1
160  ELSE IF( n.LT.0 ) THEN
161  info = -2
162  ELSE IF( nrhs.LT.0 ) THEN
163  info = -3
164  ELSE IF( ldb.LT.max( 1, n ) ) THEN
165  info = -7
166  END IF
167  IF( info.NE.0 ) THEN
168  CALL xerbla( 'ZHPTRS', -info )
169  RETURN
170  END IF
171 *
172 * Quick return if possible
173 *
174  IF( n.EQ.0 .OR. nrhs.EQ.0 )
175  $ RETURN
176 *
177  IF( upper ) THEN
178 *
179 * Solve A*X = B, where A = U*D*U**H.
180 *
181 * First solve U*D*X = B, overwriting B with X.
182 *
183 * K is the main loop index, decreasing from N to 1 in steps of
184 * 1 or 2, depending on the size of the diagonal blocks.
185 *
186  k = n
187  kc = n*( n+1 ) / 2 + 1
188  10 CONTINUE
189 *
190 * If K < 1, exit from loop.
191 *
192  IF( k.LT.1 )
193  $ GO TO 30
194 *
195  kc = kc - k
196  IF( ipiv( k ).GT.0 ) THEN
197 *
198 * 1 x 1 diagonal block
199 *
200 * Interchange rows K and IPIV(K).
201 *
202  kp = ipiv( k )
203  IF( kp.NE.k )
204  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
205 *
206 * Multiply by inv(U(K)), where U(K) is the transformation
207 * stored in column K of A.
208 *
209  CALL zgeru( k-1, nrhs, -one, ap( kc ), 1, b( k, 1 ), ldb,
210  $ b( 1, 1 ), ldb )
211 *
212 * Multiply by the inverse of the diagonal block.
213 *
214  s = dble( one ) / dble( ap( kc+k-1 ) )
215  CALL zdscal( nrhs, s, b( k, 1 ), ldb )
216  k = k - 1
217  ELSE
218 *
219 * 2 x 2 diagonal block
220 *
221 * Interchange rows K-1 and -IPIV(K).
222 *
223  kp = -ipiv( k )
224  IF( kp.NE.k-1 )
225  $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
226 *
227 * Multiply by inv(U(K)), where U(K) is the transformation
228 * stored in columns K-1 and K of A.
229 *
230  CALL zgeru( k-2, nrhs, -one, ap( kc ), 1, b( k, 1 ), ldb,
231  $ b( 1, 1 ), ldb )
232  CALL zgeru( k-2, nrhs, -one, ap( kc-( k-1 ) ), 1,
233  $ b( k-1, 1 ), ldb, b( 1, 1 ), ldb )
234 *
235 * Multiply by the inverse of the diagonal block.
236 *
237  akm1k = ap( kc+k-2 )
238  akm1 = ap( kc-1 ) / akm1k
239  ak = ap( kc+k-1 ) / dconjg( akm1k )
240  denom = akm1*ak - one
241  DO 20 j = 1, nrhs
242  bkm1 = b( k-1, j ) / akm1k
243  bk = b( k, j ) / dconjg( akm1k )
244  b( k-1, j ) = ( ak*bkm1-bk ) / denom
245  b( k, j ) = ( akm1*bk-bkm1 ) / denom
246  20 CONTINUE
247  kc = kc - k + 1
248  k = k - 2
249  END IF
250 *
251  GO TO 10
252  30 CONTINUE
253 *
254 * Next solve U**H *X = B, overwriting B with X.
255 *
256 * K is the main loop index, increasing from 1 to N in steps of
257 * 1 or 2, depending on the size of the diagonal blocks.
258 *
259  k = 1
260  kc = 1
261  40 CONTINUE
262 *
263 * If K > N, exit from loop.
264 *
265  IF( k.GT.n )
266  $ GO TO 50
267 *
268  IF( ipiv( k ).GT.0 ) THEN
269 *
270 * 1 x 1 diagonal block
271 *
272 * Multiply by inv(U**H(K)), where U(K) is the transformation
273 * stored in column K of A.
274 *
275  IF( k.GT.1 ) THEN
276  CALL zlacgv( nrhs, b( k, 1 ), ldb )
277  CALL zgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
278  $ ldb, ap( kc ), 1, one, b( k, 1 ), ldb )
279  CALL zlacgv( nrhs, b( k, 1 ), ldb )
280  END IF
281 *
282 * Interchange rows K and IPIV(K).
283 *
284  kp = ipiv( k )
285  IF( kp.NE.k )
286  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
287  kc = kc + k
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, ap( kc ), 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, ap( kc+k ), 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  kc = kc + 2*k + 1
314  k = k + 2
315  END IF
316 *
317  GO TO 40
318  50 CONTINUE
319 *
320  ELSE
321 *
322 * Solve A*X = B, where A = L*D*L**H.
323 *
324 * First solve L*D*X = B, overwriting B with X.
325 *
326 * K is the main loop index, increasing from 1 to N in steps of
327 * 1 or 2, depending on the size of the diagonal blocks.
328 *
329  k = 1
330  kc = 1
331  60 CONTINUE
332 *
333 * If K > N, exit from loop.
334 *
335  IF( k.GT.n )
336  $ GO TO 80
337 *
338  IF( ipiv( k ).GT.0 ) THEN
339 *
340 * 1 x 1 diagonal block
341 *
342 * Interchange rows K and IPIV(K).
343 *
344  kp = ipiv( k )
345  IF( kp.NE.k )
346  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
347 *
348 * Multiply by inv(L(K)), where L(K) is the transformation
349 * stored in column K of A.
350 *
351  IF( k.LT.n )
352  $ CALL zgeru( n-k, nrhs, -one, ap( kc+1 ), 1, b( k, 1 ),
353  $ ldb, b( k+1, 1 ), ldb )
354 *
355 * Multiply by the inverse of the diagonal block.
356 *
357  s = dble( one ) / dble( ap( kc ) )
358  CALL zdscal( nrhs, s, b( k, 1 ), ldb )
359  kc = kc + n - k + 1
360  k = k + 1
361  ELSE
362 *
363 * 2 x 2 diagonal block
364 *
365 * Interchange rows K+1 and -IPIV(K).
366 *
367  kp = -ipiv( k )
368  IF( kp.NE.k+1 )
369  $ CALL zswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ), ldb )
370 *
371 * Multiply by inv(L(K)), where L(K) is the transformation
372 * stored in columns K and K+1 of A.
373 *
374  IF( k.LT.n-1 ) THEN
375  CALL zgeru( n-k-1, nrhs, -one, ap( kc+2 ), 1, b( k, 1 ),
376  $ ldb, b( k+2, 1 ), ldb )
377  CALL zgeru( n-k-1, nrhs, -one, ap( kc+n-k+2 ), 1,
378  $ b( k+1, 1 ), ldb, b( k+2, 1 ), ldb )
379  END IF
380 *
381 * Multiply by the inverse of the diagonal block.
382 *
383  akm1k = ap( kc+1 )
384  akm1 = ap( kc ) / dconjg( akm1k )
385  ak = ap( kc+n-k+1 ) / akm1k
386  denom = akm1*ak - one
387  DO 70 j = 1, nrhs
388  bkm1 = b( k, j ) / dconjg( akm1k )
389  bk = b( k+1, j ) / akm1k
390  b( k, j ) = ( ak*bkm1-bk ) / denom
391  b( k+1, j ) = ( akm1*bk-bkm1 ) / denom
392  70 CONTINUE
393  kc = kc + 2*( n-k ) + 1
394  k = k + 2
395  END IF
396 *
397  GO TO 60
398  80 CONTINUE
399 *
400 * Next solve L**H *X = B, overwriting B with X.
401 *
402 * K is the main loop index, decreasing from N to 1 in steps of
403 * 1 or 2, depending on the size of the diagonal blocks.
404 *
405  k = n
406  kc = n*( n+1 ) / 2 + 1
407  90 CONTINUE
408 *
409 * If K < 1, exit from loop.
410 *
411  IF( k.LT.1 )
412  $ GO TO 100
413 *
414  kc = kc - ( n-k+1 )
415  IF( ipiv( k ).GT.0 ) THEN
416 *
417 * 1 x 1 diagonal block
418 *
419 * Multiply by inv(L**H(K)), where L(K) is the transformation
420 * stored in column K of A.
421 *
422  IF( k.LT.n ) THEN
423  CALL zlacgv( nrhs, b( k, 1 ), ldb )
424  CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
425  $ b( k+1, 1 ), ldb, ap( kc+1 ), 1, one,
426  $ b( k, 1 ), ldb )
427  CALL zlacgv( nrhs, b( k, 1 ), ldb )
428  END IF
429 *
430 * Interchange rows K and IPIV(K).
431 *
432  kp = ipiv( k )
433  IF( kp.NE.k )
434  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
435  k = k - 1
436  ELSE
437 *
438 * 2 x 2 diagonal block
439 *
440 * Multiply by inv(L**H(K-1)), where L(K-1) is the transformation
441 * stored in columns K-1 and K of A.
442 *
443  IF( k.LT.n ) THEN
444  CALL zlacgv( nrhs, b( k, 1 ), ldb )
445  CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
446  $ b( k+1, 1 ), ldb, ap( kc+1 ), 1, one,
447  $ b( k, 1 ), ldb )
448  CALL zlacgv( nrhs, b( k, 1 ), ldb )
449 *
450  CALL zlacgv( nrhs, b( k-1, 1 ), ldb )
451  CALL zgemv( 'Conjugate transpose', n-k, nrhs, -one,
452  $ b( k+1, 1 ), ldb, ap( kc-( n-k ) ), 1, one,
453  $ b( k-1, 1 ), ldb )
454  CALL zlacgv( nrhs, b( k-1, 1 ), ldb )
455  END IF
456 *
457 * Interchange rows K and -IPIV(K).
458 *
459  kp = -ipiv( k )
460  IF( kp.NE.k )
461  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
462  kc = kc - ( n-k+2 )
463  k = k - 2
464  END IF
465 *
466  GO TO 90
467  100 CONTINUE
468  END IF
469 *
470  RETURN
471 *
472 * End of ZHPTRS
473 *
474  END
subroutine zhptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZHPTRS
Definition: zhptrs.f:117
subroutine zgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
ZGEMV
Definition: zgemv.f:160
subroutine zswap(N, ZX, INCX, ZY, INCY)
ZSWAP
Definition: zswap.f:52
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zdscal(N, DA, ZX, INCX)
ZDSCAL
Definition: zdscal.f:54
subroutine zgeru(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
ZGERU
Definition: zgeru.f:132
subroutine zlacgv(N, X, INCX)
ZLACGV conjugates a complex vector.
Definition: zlacgv.f:76