151 SUBROUTINE clavhe( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
159 CHARACTER DIAG, TRANS, UPLO
160 INTEGER INFO, LDA, LDB, N, NRHS
164 COMPLEX A( LDA, * ), B( LDB, * )
171 parameter( one = ( 1.0e+0, 0.0e+0 ) )
176 COMPLEX D11, D12, D21, D22, T1, T2
186 INTRINSIC abs, conjg, max
193 IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
THEN
195 ELSE IF( .NOT.lsame( trans,
'N' ) .AND. .NOT.lsame( trans,
'C' ) )
198 ELSE IF( .NOT.lsame( diag,
'U' ) .AND. .NOT.lsame( diag,
'N' ) )
201 ELSE IF( n.LT.0 )
THEN
203 ELSE IF( lda.LT.max( 1, n ) )
THEN
205 ELSE IF( ldb.LT.max( 1, n ) )
THEN
209 CALL xerbla(
'CLAVHE ', -info )
218 nounit = lsame( diag,
'N' )
224 IF( lsame( trans,
'N' ) )
THEN
229 IF( lsame( uplo,
'U' ) )
THEN
237 IF( ipiv( k ).GT.0 )
THEN
244 $
CALL cscal( nrhs, a( k, k ), b( k, 1 ), ldb )
252 CALL cgeru( k-1, nrhs, one, a( 1, k ), 1, b( k, 1 ),
253 $ ldb, b( 1, 1 ), ldb )
259 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
276 b( k, j ) = d11*t1 + d12*t2
277 b( k+1, j ) = d21*t1 + d22*t2
287 CALL cgeru( k-1, nrhs, one, a( 1, k ), 1, b( k, 1 ),
288 $ ldb, b( 1, 1 ), ldb )
289 CALL cgeru( k-1, nrhs, one, a( 1, k+1 ), 1,
290 $ b( k+1, 1 ), ldb, b( 1, 1 ), ldb )
294 kp = abs( ipiv( k ) )
296 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
318 IF( ipiv( k ).GT.0 )
THEN
325 $
CALL cscal( nrhs, a( k, k ), b( k, 1 ), ldb )
334 CALL cgeru( n-k, nrhs, one, a( k+1, k ), 1,
335 $ b( k, 1 ), ldb, b( k+1, 1 ), ldb )
341 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
359 b( k-1, j ) = d11*t1 + d12*t2
360 b( k, j ) = d21*t1 + d22*t2
370 CALL cgeru( n-k, nrhs, one, a( k+1, k ), 1,
371 $ b( k, 1 ), ldb, b( k+1, 1 ), ldb )
372 CALL cgeru( n-k, nrhs, one, a( k+1, k-1 ), 1,
373 $ b( k-1, 1 ), ldb, b( k+1, 1 ), ldb )
378 kp = abs( ipiv( k ) )
380 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
398 IF( lsame( uplo,
'U' ) )
THEN
408 IF( ipiv( k ).GT.0 )
THEN
415 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
421 CALL clacgv( nrhs, b( k, 1 ), ldb )
422 CALL cgemv(
'Conjugate', k-1, nrhs, one, b, ldb,
423 $ a( 1, k ), 1, one, b( k, 1 ), ldb )
424 CALL clacgv( nrhs, b( k, 1 ), ldb )
427 $
CALL cscal( nrhs, a( k, k ), b( k, 1 ), ldb )
437 kp = abs( ipiv( k ) )
439 $
CALL cswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ),
447 CALL clacgv( nrhs, b( k, 1 ), ldb )
448 CALL cgemv(
'Conjugate', k-2, nrhs, one, b, ldb,
449 $ a( 1, k ), 1, one, b( k, 1 ), ldb )
450 CALL clacgv( nrhs, b( k, 1 ), ldb )
452 CALL clacgv( nrhs, b( k-1, 1 ), ldb )
453 CALL cgemv(
'Conjugate', k-2, nrhs, one, b, ldb,
454 $ a( 1, k-1 ), 1, one, b( k-1, 1 ), ldb )
455 CALL clacgv( nrhs, b( k-1, 1 ), ldb )
468 b( k-1, j ) = d11*t1 + d12*t2
469 b( k, j ) = d21*t1 + d22*t2
492 IF( ipiv( k ).GT.0 )
THEN
499 $
CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
503 CALL clacgv( nrhs, b( k, 1 ), ldb )
504 CALL cgemv(
'Conjugate', n-k, nrhs, one, b( k+1, 1 ),
505 $ ldb, a( k+1, k ), 1, one, b( k, 1 ), ldb )
506 CALL clacgv( nrhs, b( k, 1 ), ldb )
509 $
CALL cscal( nrhs, a( k, k ), b( k, 1 ), ldb )
519 kp = abs( ipiv( k ) )
521 $
CALL cswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ),
526 CALL clacgv( nrhs, b( k+1, 1 ), ldb )
527 CALL cgemv(
'Conjugate', n-k-1, nrhs, one,
528 $ b( k+2, 1 ), ldb, a( k+2, k+1 ), 1, one,
530 CALL clacgv( nrhs, b( k+1, 1 ), ldb )
532 CALL clacgv( nrhs, b( k, 1 ), ldb )
533 CALL cgemv(
'Conjugate', n-k-1, nrhs, one,
534 $ b( k+2, 1 ), ldb, a( k+2, k ), 1, one,
536 CALL clacgv( nrhs, b( k, 1 ), ldb )
549 b( k, j ) = d11*t1 + d12*t2
550 b( k+1, j ) = d21*t1 + d22*t2
subroutine xerbla(srname, info)
subroutine clavhe(uplo, trans, diag, n, nrhs, a, lda, ipiv, b, ldb, info)
CLAVHE
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