99      SUBROUTINE slauum( UPLO, N, A, LDA, INFO )
 
  117      parameter( one = 1.0e+0 )
 
  126      EXTERNAL           lsame, ilaenv
 
  139      upper = lsame( uplo, 
'U' )
 
  140      IF( .NOT.upper .AND. .NOT.lsame( uplo, 
'L' ) ) 
THEN 
  142      ELSE IF( n.LT.0 ) 
THEN 
  144      ELSE IF( lda.LT.max( 1, n ) ) 
THEN 
  148         CALL xerbla( 
'SLAUUM', -info )
 
  159      nb = ilaenv( 1, 
'SLAUUM', uplo, n, -1, -1, -1 )
 
  161      IF( nb.LE.1 .OR. nb.GE.n ) 
THEN 
  165         CALL slauu2( uplo, n, a, lda, info )
 
  175               ib = min( nb, n-i+1 )
 
  176               CALL strmm( 
'Right', 
'Upper', 
'Transpose', 
'Non-unit',
 
  177     $                     i-1, ib, one, a( i, i ), lda, a( 1, i ),
 
  179               CALL slauu2( 
'Upper', ib, a( i, i ), lda, info )
 
  181                  CALL sgemm( 
'No transpose', 
'Transpose', i-1, ib,
 
  182     $                        n-i-ib+1, one, a( 1, i+ib ), lda,
 
  183     $                        a( i, i+ib ), lda, one, a( 1, i ), lda )
 
  184                  CALL ssyrk( 
'Upper', 
'No transpose', ib, n-i-ib+1,
 
  185     $                        one, a( i, i+ib ), lda, one, a( i, i ),
 
  194               ib = min( nb, n-i+1 )
 
  195               CALL strmm( 
'Left', 
'Lower', 
'Transpose', 
'Non-unit',
 
  197     $                     i-1, one, a( i, i ), lda, a( i, 1 ), lda )
 
  198               CALL slauu2( 
'Lower', ib, a( i, i ), lda, info )
 
  200                  CALL sgemm( 
'Transpose', 
'No transpose', ib, i-1,
 
  201     $                        n-i-ib+1, one, a( i+ib, i ), lda,
 
  202     $                        a( i+ib, 1 ), lda, one, a( i, 1 ), lda )
 
  203                  CALL ssyrk( 
'Lower', 
'Transpose', ib, n-i-ib+1,
 
  205     $                        a( i+ib, i ), lda, one, a( i, i ), lda )
 
 
subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SGEMM
subroutine ssyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
SSYRK
subroutine slauu2(uplo, n, a, lda, info)
SLAUU2 computes the product UUH or LHL, where U and L are upper or lower triangular matrices (unblock...
subroutine slauum(uplo, n, a, lda, info)
SLAUUM computes the product UUH or LHL, where U and L are upper or lower triangular matrices (blocked...
subroutine strmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
STRMM