LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ chptrs()

subroutine chptrs ( character uplo,
integer n,
integer nrhs,
complex, dimension( * ) ap,
integer, dimension( * ) ipiv,
complex, dimension( ldb, * ) b,
integer ldb,
integer info )

CHPTRS

Download CHPTRS + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> CHPTRS solves a system of linear equations A*X = B with a complex
!> Hermitian matrix A stored in packed format using the factorization
!> A = U*D*U**H or A = L*D*L**H computed by CHPTRF.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          Specifies whether the details of the factorization are stored
!>          as an upper or lower triangular matrix.
!>          = 'U':  Upper triangular, form is A = U*D*U**H;
!>          = 'L':  Lower triangular, form is A = L*D*L**H.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]NRHS
!>          NRHS is INTEGER
!>          The number of right hand sides, i.e., the number of columns
!>          of the matrix B.  NRHS >= 0.
!> 
[in]AP
!>          AP is COMPLEX array, dimension (N*(N+1)/2)
!>          The block diagonal matrix D and the multipliers used to
!>          obtain the factor U or L as computed by CHPTRF, stored as a
!>          packed triangular matrix.
!> 
[in]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>          Details of the interchanges and the block structure of D
!>          as determined by CHPTRF.
!> 
[in,out]B
!>          B is COMPLEX array, dimension (LDB,NRHS)
!>          On entry, the right hand side matrix B.
!>          On exit, the solution matrix X.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= max(1,N).
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0: if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 112 of file chptrs.f.

113*
114* -- LAPACK computational routine --
115* -- LAPACK is a software package provided by Univ. of Tennessee, --
116* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117*
118* .. Scalar Arguments ..
119 CHARACTER UPLO
120 INTEGER INFO, LDB, N, NRHS
121* ..
122* .. Array Arguments ..
123 INTEGER IPIV( * )
124 COMPLEX AP( * ), B( LDB, * )
125* ..
126*
127* =====================================================================
128*
129* .. Parameters ..
130 COMPLEX ONE
131 parameter( one = ( 1.0e+0, 0.0e+0 ) )
132* ..
133* .. Local Scalars ..
134 LOGICAL UPPER
135 INTEGER J, K, KC, KP
136 REAL S
137 COMPLEX AK, AKM1, AKM1K, BK, BKM1, DENOM
138* ..
139* .. External Functions ..
140 LOGICAL LSAME
141 EXTERNAL lsame
142* ..
143* .. External Subroutines ..
144 EXTERNAL cgemv, cgeru, clacgv, csscal, cswap,
145 $ xerbla
146* ..
147* .. Intrinsic Functions ..
148 INTRINSIC conjg, max, real
149* ..
150* .. Executable Statements ..
151*
152 info = 0
153 upper = lsame( uplo, 'U' )
154 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
155 info = -1
156 ELSE IF( n.LT.0 ) THEN
157 info = -2
158 ELSE IF( nrhs.LT.0 ) THEN
159 info = -3
160 ELSE IF( ldb.LT.max( 1, n ) ) THEN
161 info = -7
162 END IF
163 IF( info.NE.0 ) THEN
164 CALL xerbla( 'CHPTRS', -info )
165 RETURN
166 END IF
167*
168* Quick return if possible
169*
170 IF( n.EQ.0 .OR. nrhs.EQ.0 )
171 $ RETURN
172*
173 IF( upper ) THEN
174*
175* Solve A*X = B, where A = U*D*U**H.
176*
177* First solve U*D*X = B, overwriting B with X.
178*
179* K is the main loop index, decreasing from N to 1 in steps of
180* 1 or 2, depending on the size of the diagonal blocks.
181*
182 k = n
183 kc = n*( n+1 ) / 2 + 1
184 10 CONTINUE
185*
186* If K < 1, exit from loop.
187*
188 IF( k.LT.1 )
189 $ GO TO 30
190*
191 kc = kc - k
192 IF( ipiv( k ).GT.0 ) THEN
193*
194* 1 x 1 diagonal block
195*
196* Interchange rows K and IPIV(K).
197*
198 kp = ipiv( k )
199 IF( kp.NE.k )
200 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
201*
202* Multiply by inv(U(K)), where U(K) is the transformation
203* stored in column K of A.
204*
205 CALL cgeru( k-1, nrhs, -one, ap( kc ), 1, b( k, 1 ), ldb,
206 $ b( 1, 1 ), ldb )
207*
208* Multiply by the inverse of the diagonal block.
209*
210 s = real( one ) / real( ap( kc+k-1 ) )
211 CALL csscal( nrhs, s, b( k, 1 ), ldb )
212 k = k - 1
213 ELSE
214*
215* 2 x 2 diagonal block
216*
217* Interchange rows K-1 and -IPIV(K).
218*
219 kp = -ipiv( k )
220 IF( kp.NE.k-1 )
221 $ CALL cswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ), ldb )
222*
223* Multiply by inv(U(K)), where U(K) is the transformation
224* stored in columns K-1 and K of A.
225*
226 CALL cgeru( k-2, nrhs, -one, ap( kc ), 1, b( k, 1 ), ldb,
227 $ b( 1, 1 ), ldb )
228 CALL cgeru( k-2, nrhs, -one, ap( kc-( k-1 ) ), 1,
229 $ b( k-1, 1 ), ldb, b( 1, 1 ), ldb )
230*
231* Multiply by the inverse of the diagonal block.
232*
233 akm1k = ap( kc+k-2 )
234 akm1 = ap( kc-1 ) / akm1k
235 ak = ap( kc+k-1 ) / conjg( akm1k )
236 denom = akm1*ak - one
237 DO 20 j = 1, nrhs
238 bkm1 = b( k-1, j ) / akm1k
239 bk = b( k, j ) / conjg( akm1k )
240 b( k-1, j ) = ( ak*bkm1-bk ) / denom
241 b( k, j ) = ( akm1*bk-bkm1 ) / denom
242 20 CONTINUE
243 kc = kc - k + 1
244 k = k - 2
245 END IF
246*
247 GO TO 10
248 30 CONTINUE
249*
250* Next solve U**H *X = B, overwriting B with X.
251*
252* K is the main loop index, increasing from 1 to N in steps of
253* 1 or 2, depending on the size of the diagonal blocks.
254*
255 k = 1
256 kc = 1
257 40 CONTINUE
258*
259* If K > N, exit from loop.
260*
261 IF( k.GT.n )
262 $ GO TO 50
263*
264 IF( ipiv( k ).GT.0 ) THEN
265*
266* 1 x 1 diagonal block
267*
268* Multiply by inv(U**H(K)), where U(K) is the transformation
269* stored in column K of A.
270*
271 IF( k.GT.1 ) THEN
272 CALL clacgv( nrhs, b( k, 1 ), ldb )
273 CALL cgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
274 $ ldb, ap( kc ), 1, one, b( k, 1 ), ldb )
275 CALL clacgv( nrhs, b( k, 1 ), ldb )
276 END IF
277*
278* Interchange rows K and IPIV(K).
279*
280 kp = ipiv( k )
281 IF( kp.NE.k )
282 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
283 kc = kc + k
284 k = k + 1
285 ELSE
286*
287* 2 x 2 diagonal block
288*
289* Multiply by inv(U**H(K+1)), where U(K+1) is the transformation
290* stored in columns K and K+1 of A.
291*
292 IF( k.GT.1 ) THEN
293 CALL clacgv( nrhs, b( k, 1 ), ldb )
294 CALL cgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
295 $ ldb, ap( kc ), 1, one, b( k, 1 ), ldb )
296 CALL clacgv( nrhs, b( k, 1 ), ldb )
297*
298 CALL clacgv( nrhs, b( k+1, 1 ), ldb )
299 CALL cgemv( 'Conjugate transpose', k-1, nrhs, -one, b,
300 $ ldb, ap( kc+k ), 1, one, b( k+1, 1 ), ldb )
301 CALL clacgv( nrhs, b( k+1, 1 ), ldb )
302 END IF
303*
304* Interchange rows K and -IPIV(K).
305*
306 kp = -ipiv( k )
307 IF( kp.NE.k )
308 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
309 kc = kc + 2*k + 1
310 k = k + 2
311 END IF
312*
313 GO TO 40
314 50 CONTINUE
315*
316 ELSE
317*
318* Solve A*X = B, where A = L*D*L**H.
319*
320* First solve L*D*X = B, overwriting B with X.
321*
322* K is the main loop index, increasing from 1 to N in steps of
323* 1 or 2, depending on the size of the diagonal blocks.
324*
325 k = 1
326 kc = 1
327 60 CONTINUE
328*
329* If K > N, exit from loop.
330*
331 IF( k.GT.n )
332 $ GO TO 80
333*
334 IF( ipiv( k ).GT.0 ) THEN
335*
336* 1 x 1 diagonal block
337*
338* Interchange rows K and IPIV(K).
339*
340 kp = ipiv( k )
341 IF( kp.NE.k )
342 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
343*
344* Multiply by inv(L(K)), where L(K) is the transformation
345* stored in column K of A.
346*
347 IF( k.LT.n )
348 $ CALL cgeru( n-k, nrhs, -one, ap( kc+1 ), 1, b( k, 1 ),
349 $ ldb, b( k+1, 1 ), ldb )
350*
351* Multiply by the inverse of the diagonal block.
352*
353 s = real( one ) / real( ap( kc ) )
354 CALL csscal( nrhs, s, b( k, 1 ), ldb )
355 kc = kc + n - k + 1
356 k = k + 1
357 ELSE
358*
359* 2 x 2 diagonal block
360*
361* Interchange rows K+1 and -IPIV(K).
362*
363 kp = -ipiv( k )
364 IF( kp.NE.k+1 )
365 $ CALL cswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ), ldb )
366*
367* Multiply by inv(L(K)), where L(K) is the transformation
368* stored in columns K and K+1 of A.
369*
370 IF( k.LT.n-1 ) THEN
371 CALL cgeru( n-k-1, nrhs, -one, ap( kc+2 ), 1, b( k,
372 $ 1 ),
373 $ ldb, b( k+2, 1 ), ldb )
374 CALL cgeru( n-k-1, nrhs, -one, ap( kc+n-k+2 ), 1,
375 $ b( k+1, 1 ), ldb, b( k+2, 1 ), ldb )
376 END IF
377*
378* Multiply by the inverse of the diagonal block.
379*
380 akm1k = ap( kc+1 )
381 akm1 = ap( kc ) / conjg( akm1k )
382 ak = ap( kc+n-k+1 ) / akm1k
383 denom = akm1*ak - one
384 DO 70 j = 1, nrhs
385 bkm1 = b( k, j ) / conjg( akm1k )
386 bk = b( k+1, j ) / akm1k
387 b( k, j ) = ( ak*bkm1-bk ) / denom
388 b( k+1, j ) = ( akm1*bk-bkm1 ) / denom
389 70 CONTINUE
390 kc = kc + 2*( n-k ) + 1
391 k = k + 2
392 END IF
393*
394 GO TO 60
395 80 CONTINUE
396*
397* Next solve L**H *X = B, overwriting B with X.
398*
399* K is the main loop index, decreasing from N to 1 in steps of
400* 1 or 2, depending on the size of the diagonal blocks.
401*
402 k = n
403 kc = n*( n+1 ) / 2 + 1
404 90 CONTINUE
405*
406* If K < 1, exit from loop.
407*
408 IF( k.LT.1 )
409 $ GO TO 100
410*
411 kc = kc - ( n-k+1 )
412 IF( ipiv( k ).GT.0 ) THEN
413*
414* 1 x 1 diagonal block
415*
416* Multiply by inv(L**H(K)), where L(K) is the transformation
417* stored in column K of A.
418*
419 IF( k.LT.n ) THEN
420 CALL clacgv( nrhs, b( k, 1 ), ldb )
421 CALL cgemv( 'Conjugate transpose', n-k, nrhs, -one,
422 $ b( k+1, 1 ), ldb, ap( kc+1 ), 1, one,
423 $ b( k, 1 ), ldb )
424 CALL clacgv( nrhs, b( k, 1 ), ldb )
425 END IF
426*
427* Interchange rows K and IPIV(K).
428*
429 kp = ipiv( k )
430 IF( kp.NE.k )
431 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
432 k = k - 1
433 ELSE
434*
435* 2 x 2 diagonal block
436*
437* Multiply by inv(L**H(K-1)), where L(K-1) is the transformation
438* stored in columns K-1 and K of A.
439*
440 IF( k.LT.n ) THEN
441 CALL clacgv( nrhs, b( k, 1 ), ldb )
442 CALL cgemv( 'Conjugate transpose', n-k, nrhs, -one,
443 $ b( k+1, 1 ), ldb, ap( kc+1 ), 1, one,
444 $ b( k, 1 ), ldb )
445 CALL clacgv( nrhs, b( k, 1 ), ldb )
446*
447 CALL clacgv( nrhs, b( k-1, 1 ), ldb )
448 CALL cgemv( 'Conjugate transpose', n-k, nrhs, -one,
449 $ b( k+1, 1 ), ldb, ap( kc-( n-k ) ), 1, one,
450 $ b( k-1, 1 ), ldb )
451 CALL clacgv( nrhs, b( k-1, 1 ), ldb )
452 END IF
453*
454* Interchange rows K and -IPIV(K).
455*
456 kp = -ipiv( k )
457 IF( kp.NE.k )
458 $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
459 kc = kc - ( n-k+2 )
460 k = k - 2
461 END IF
462*
463 GO TO 90
464 100 CONTINUE
465 END IF
466*
467 RETURN
468*
469* End of CHPTRS
470*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
Definition cgemv.f:160
subroutine cgeru(m, n, alpha, x, incx, y, incy, a, lda)
CGERU
Definition cgeru.f:130
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:72
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81
Here is the call graph for this function:
Here is the caller graph for this function: