101 SUBROUTINE dlauum( UPLO, N, A, LDA, INFO )
112 DOUBLE PRECISION A( LDA, * )
119 parameter( one = 1.0d+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(
'DLAUUM', -info )
161 nb = ilaenv( 1,
'DLAUUM', uplo, n, -1, -1, -1 )
163 IF( nb.LE.1 .OR. nb.GE.n )
THEN
167 CALL dlauu2( uplo, n, a, lda, info )
177 ib = min( nb, n-i+1 )
178 CALL dtrmm(
'Right',
'Upper',
'Transpose',
'Non-unit',
179 $ i-1, ib, one, a( i, i ), lda, a( 1, i ),
181 CALL dlauu2(
'Upper', ib, a( i, i ), lda, info )
183 CALL dgemm(
'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 dsyrk(
'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 dtrmm(
'Left',
'Lower',
'Transpose',
'Non-unit', ib,
198 $ i-1, one, a( i, i ), lda, a( i, 1 ), lda )
199 CALL dlauu2(
'Lower', ib, a( i, i ), lda, info )
201 CALL dgemm(
'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 dsyrk(
'Lower',
'Transpose', ib, n-i-ib+1, one,
205 $ a( i+ib, i ), lda, one, a( i, i ), lda )
subroutine xerbla(srname, info)
subroutine dgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
DGEMM
subroutine dsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
DSYRK
subroutine dlauu2(uplo, n, a, lda, info)
DLAUU2 computes the product UUH or LHL, where U and L are upper or lower triangular matrices (unblock...
subroutine dlauum(uplo, n, a, lda, info)
DLAUUM computes the product UUH or LHL, where U and L are upper or lower triangular matrices (blocked...
subroutine dtrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRMM