129 SUBROUTINE clavhp( UPLO, TRANS, DIAG, N, NRHS, A, IPIV, B, LDB,
137 CHARACTER DIAG, TRANS, UPLO
138 INTEGER INFO, LDB, N, NRHS
142 COMPLEX A( * ), B( LDB, * )
149 parameter( one = ( 1.0e+0, 0.0e+0 ) )
153 INTEGER J, K, KC, KCNEXT, KP
154 COMPLEX D11, D12, D21, D22, T1, T2
164 INTRINSIC abs, conjg, max
171 IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
THEN
173 ELSE IF( .NOT.lsame( trans,
'N' ) .AND. .NOT.lsame( trans,
'C' ) )
176 ELSE IF( .NOT.lsame( diag,
'U' ) .AND. .NOT.lsame( diag,
'N' ) )
179 ELSE IF( n.LT.0 )
THEN
181 ELSE IF( ldb.LT.max( 1, n ) )
THEN
185 CALL xerbla(
'CLAVHP ', -info )
194 nounit = lsame( diag,
'N' )
200 IF( lsame( trans,
'N' ) )
THEN
205 IF( lsame( uplo,
'U' ) )
THEN
217 IF( ipiv( k ).GT.0 )
THEN
222 $
CALL cscal( nrhs, a( kc+k-1 ), b( k, 1 ), ldb )
230 CALL cgeru( k-1, nrhs, one, a( kc ), 1, b( k, 1 ),
231 $ ldb, b( 1, 1 ), ldb )
237 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
252 d12 = a( kcnext+k-1 )
257 b( k, j ) = d11*t1 + d12*t2
258 b( k+1, j ) = d21*t1 + d22*t2
268 CALL cgeru( k-1, nrhs, one, a( kc ), 1, b( k, 1 ),
269 $ ldb, b( 1, 1 ), ldb )
270 CALL cgeru( k-1, nrhs, one, a( kcnext ), 1,
271 $ b( k+1, 1 ), ldb, b( 1, 1 ), ldb )
275 kp = abs( ipiv( k ) )
277 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
293 kc = n*( n+1 ) / 2 + 1
302 IF( ipiv( k ).GT.0 )
THEN
309 $
CALL cscal( nrhs, a( kc ), b( k, 1 ), ldb )
318 CALL cgeru( n-k, nrhs, one, a( kc+1 ), 1, b( k, 1 ),
319 $ ldb, b( k+1, 1 ), ldb )
325 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
333 kcnext = kc - ( n-k+2 )
345 b( k-1, j ) = d11*t1 + d12*t2
346 b( k, j ) = d21*t1 + d22*t2
356 CALL cgeru( n-k, nrhs, one, a( kc+1 ), 1, b( k, 1 ),
357 $ ldb, b( k+1, 1 ), ldb )
358 CALL cgeru( n-k, nrhs, one, a( kcnext+2 ), 1,
359 $ b( k-1, 1 ), ldb, b( k+1, 1 ), ldb )
364 kp = abs( ipiv( k ) )
366 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
385 IF( lsame( uplo,
'U' ) )
THEN
390 kc = n*( n+1 ) / 2 + 1
397 IF( ipiv( k ).GT.0 )
THEN
404 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
410 CALL clacgv( nrhs, b( k, 1 ), ldb )
411 CALL cgemv(
'Conjugate', k-1, nrhs, one, b, ldb,
412 $ a( kc ), 1, one, b( k, 1 ), ldb )
413 CALL clacgv( nrhs, b( k, 1 ), ldb )
416 $
CALL cscal( nrhs, a( kc+k-1 ), b( k, 1 ), ldb )
422 kcnext = kc - ( k-1 )
427 kp = abs( ipiv( k ) )
429 $
CALL cswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ),
434 CALL clacgv( nrhs, b( k, 1 ), ldb )
435 CALL cgemv(
'Conjugate', k-2, nrhs, one, b, ldb,
436 $ a( kc ), 1, one, b( k, 1 ), ldb )
437 CALL clacgv( nrhs, b( k, 1 ), ldb )
439 CALL clacgv( nrhs, b( k-1, 1 ), ldb )
440 CALL cgemv(
'Conjugate', k-2, nrhs, one, b, ldb,
441 $ a( kcnext ), 1, one, b( k-1, 1 ), ldb )
442 CALL clacgv( nrhs, b( k-1, 1 ), ldb )
455 b( k-1, j ) = d11*t1 + d12*t2
456 b( k, j ) = d21*t1 + d22*t2
481 IF( ipiv( k ).GT.0 )
THEN
488 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
492 CALL clacgv( nrhs, b( k, 1 ), ldb )
493 CALL cgemv(
'Conjugate', n-k, nrhs, one, b( k+1, 1 ),
494 $ ldb, a( kc+1 ), 1, one, b( k, 1 ), ldb )
495 CALL clacgv( nrhs, b( k, 1 ), ldb )
498 $
CALL cscal( nrhs, a( kc ), b( k, 1 ), ldb )
505 kcnext = kc + n - k + 1
510 kp = abs( ipiv( k ) )
512 $
CALL cswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ),
517 CALL clacgv( nrhs, b( k+1, 1 ), ldb )
518 CALL cgemv(
'Conjugate', n-k-1, nrhs, one,
519 $ b( k+2, 1 ), ldb, a( kcnext+1 ), 1, one,
521 CALL clacgv( nrhs, b( k+1, 1 ), ldb )
523 CALL clacgv( nrhs, b( k, 1 ), ldb )
524 CALL cgemv(
'Conjugate', n-k-1, nrhs, one,
525 $ b( k+2, 1 ), ldb, a( kc+2 ), 1, one,
527 CALL clacgv( nrhs, b( k, 1 ), ldb )
540 b( k, j ) = d11*t1 + d12*t2
541 b( k+1, j ) = d21*t1 + d22*t2
544 kc = kcnext + ( n-k )
subroutine xerbla(srname, info)
subroutine clavhp(uplo, trans, diag, n, nrhs, a, ipiv, b, ldb, info)
CLAVHP
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
subroutine cgeru(m, n, alpha, x, incx, y, incy, a, lda)
CGERU
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
subroutine cscal(n, ca, cx, incx)
CSCAL
subroutine cswap(n, cx, incx, cy, incy)
CSWAP