LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlauum()

subroutine dlauum ( character  uplo,
integer  n,
double precision, dimension( lda, * )  a,
integer  lda,
integer  info 
)

DLAUUM computes the product UUH or LHL, where U and L are upper or lower triangular matrices (blocked algorithm).

Download DLAUUM + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DLAUUM computes the product U * U**T or L**T * L, where the triangular
 factor U or L is stored in the upper or lower triangular part of
 the array A.

 If UPLO = 'U' or 'u' then the upper triangle of the result is stored,
 overwriting the factor U in A.
 If UPLO = 'L' or 'l' then the lower triangle of the result is stored,
 overwriting the factor L in A.

 This is the blocked form of the algorithm, calling Level 3 BLAS.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the triangular factor stored in the array A
          is upper or lower triangular:
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]N
          N is INTEGER
          The order of the triangular factor U or L.  N >= 0.
[in,out]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          On entry, the triangular factor U or L.
          On exit, if UPLO = 'U', the upper triangle of A is
          overwritten with the upper triangle of the product U * U**T;
          if UPLO = 'L', the lower triangle of A is overwritten with
          the lower triangle of the product L**T * L.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[out]INFO
          INFO is INTEGER
          = 0: successful exit
          < 0: if INFO = -k, the k-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 101 of file dlauum.f.

102*
103* -- LAPACK auxiliary routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 CHARACTER UPLO
109 INTEGER INFO, LDA, N
110* ..
111* .. Array Arguments ..
112 DOUBLE PRECISION A( LDA, * )
113* ..
114*
115* =====================================================================
116*
117* .. Parameters ..
118 DOUBLE PRECISION ONE
119 parameter( one = 1.0d+0 )
120* ..
121* .. Local Scalars ..
122 LOGICAL UPPER
123 INTEGER I, IB, NB
124* ..
125* .. External Functions ..
126 LOGICAL LSAME
127 INTEGER ILAENV
128 EXTERNAL lsame, ilaenv
129* ..
130* .. External Subroutines ..
131 EXTERNAL dgemm, dlauu2, dsyrk, dtrmm, xerbla
132* ..
133* .. Intrinsic Functions ..
134 INTRINSIC max, min
135* ..
136* .. Executable Statements ..
137*
138* Test the input parameters.
139*
140 info = 0
141 upper = lsame( uplo, 'U' )
142 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
143 info = -1
144 ELSE IF( n.LT.0 ) THEN
145 info = -2
146 ELSE IF( lda.LT.max( 1, n ) ) THEN
147 info = -4
148 END IF
149 IF( info.NE.0 ) THEN
150 CALL xerbla( 'DLAUUM', -info )
151 RETURN
152 END IF
153*
154* Quick return if possible
155*
156 IF( n.EQ.0 )
157 $ RETURN
158*
159* Determine the block size for this environment.
160*
161 nb = ilaenv( 1, 'DLAUUM', uplo, n, -1, -1, -1 )
162*
163 IF( nb.LE.1 .OR. nb.GE.n ) THEN
164*
165* Use unblocked code
166*
167 CALL dlauu2( uplo, n, a, lda, info )
168 ELSE
169*
170* Use blocked code
171*
172 IF( upper ) THEN
173*
174* Compute the product U * U**T.
175*
176 DO 10 i = 1, n, nb
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 ),
180 $ lda )
181 CALL dlauu2( 'Upper', ib, a( i, i ), lda, info )
182 IF( i+ib.LE.n ) THEN
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 ),
188 $ lda )
189 END IF
190 10 CONTINUE
191 ELSE
192*
193* Compute the product L**T * L.
194*
195 DO 20 i = 1, n, nb
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 )
200 IF( i+ib.LE.n ) THEN
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 )
206 END IF
207 20 CONTINUE
208 END IF
209 END IF
210*
211 RETURN
212*
213* End of DLAUUM
214*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
DGEMM
Definition dgemm.f:188
subroutine dsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
DSYRK
Definition dsyrk.f:169
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
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...
Definition dlauu2.f:102
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dtrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRMM
Definition dtrmm.f:177
Here is the call graph for this function:
Here is the caller graph for this function: