167      SUBROUTINE ssycon_3( UPLO, N, A, LDA, E, IPIV, ANORM, RCOND,
 
  168     $                     WORK, IWORK, INFO )
 
  180      INTEGER            IPIV( * ), IWORK( * )
 
  181      REAL               A( LDA, * ), E( * ), WORK( * )
 
  188      parameter( one = 1.0e+0, zero = 0.0e+0 )
 
  213      upper = lsame( uplo, 
'U' )
 
  214      IF( .NOT.upper .AND. .NOT.lsame( uplo, 
'L' ) ) 
THEN 
  216      ELSE IF( n.LT.0 ) 
THEN 
  218      ELSE IF( lda.LT.max( 1, n ) ) 
THEN 
  220      ELSE IF( anorm.LT.zero ) 
THEN 
  224         CALL xerbla( 
'SSYCON_3', -info )
 
  234      ELSE IF( anorm.LE.zero ) 
THEN 
  245            IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
 
  253            IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
 
  262      CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
 
  267         CALL ssytrs_3( uplo, n, 1, a, lda, e, ipiv, work, n, info )
 
  274     $   rcond = ( one / ainvnm ) / anorm
 
 
subroutine ssycon_3(uplo, n, a, lda, e, ipiv, anorm, rcond, work, iwork, info)
SSYCON_3
subroutine ssytrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)
SSYTRS_3
subroutine slacn2(n, v, x, isgn, est, kase, isave)
SLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...