101 SUBROUTINE slauum( UPLO, N, A, LDA, INFO )
119 parameter( one = 1.0e+0 )
128 EXTERNAL lsame, ilaenv
141 upper = lsame( uplo,
'U' )
142 IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
144 ELSE IF( n.LT.0 )
THEN
146 ELSE IF( lda.LT.max( 1, n ) )
THEN
150 CALL xerbla(
'SLAUUM', -info )
161 nb = ilaenv( 1,
'SLAUUM', uplo, n, -1, -1, -1 )
163 IF( nb.LE.1 .OR. nb.GE.n )
THEN
167 CALL slauu2( uplo, n, a, lda, info )
177 ib = min( nb, n-i+1 )
178 CALL strmm(
'Right',
'Upper',
'Transpose',
'Non-unit',
179 $ i-1, ib, one, a( i, i ), lda, a( 1, i ),
181 CALL slauu2(
'Upper', ib, a( i, i ), lda, info )
183 CALL sgemm(
'No transpose',
'Transpose', i-1, ib,
184 $ n-i-ib+1, one, a( 1, i+ib ), lda,
185 $ a( i, i+ib ), lda, one, a( 1, i ), lda )
186 CALL ssyrk(
'Upper',
'No transpose', ib, n-i-ib+1,
187 $ one, a( i, i+ib ), lda, one, a( i, i ),
196 ib = min( nb, n-i+1 )
197 CALL strmm(
'Left',
'Lower',
'Transpose',
'Non-unit', ib,
198 $ i-1, one, a( i, i ), lda, a( i, 1 ), lda )
199 CALL slauu2(
'Lower', ib, a( i, i ), lda, info )
201 CALL sgemm(
'Transpose',
'No transpose', ib, i-1,
202 $ n-i-ib+1, one, a( i+ib, i ), lda,
203 $ a( i+ib, 1 ), lda, one, a( i, 1 ), lda )
204 CALL ssyrk(
'Lower',
'Transpose', ib, n-i-ib+1, one,
205 $ a( i+ib, i ), lda, one, a( i, i ), lda )
subroutine xerbla(srname, info)
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