LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlauum.f
Go to the documentation of this file.
1*> \brief \b DLAUUM computes the product UUH or LHL, where U and L are upper or lower triangular matrices (blocked algorithm).
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLAUUM + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlauum.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlauum.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlauum.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLAUUM( UPLO, N, A, LDA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> DLAUUM computes the product U * U**T or L**T * L, where the triangular
36*> factor U or L is stored in the upper or lower triangular part of
37*> the array A.
38*>
39*> If UPLO = 'U' or 'u' then the upper triangle of the result is stored,
40*> overwriting the factor U in A.
41*> If UPLO = 'L' or 'l' then the lower triangle of the result is stored,
42*> overwriting the factor L in A.
43*>
44*> This is the blocked form of the algorithm, calling Level 3 BLAS.
45*> \endverbatim
46*
47* Arguments:
48* ==========
49*
50*> \param[in] UPLO
51*> \verbatim
52*> UPLO is CHARACTER*1
53*> Specifies whether the triangular factor stored in the array A
54*> is upper or lower triangular:
55*> = 'U': Upper triangular
56*> = 'L': Lower triangular
57*> \endverbatim
58*>
59*> \param[in] N
60*> \verbatim
61*> N is INTEGER
62*> The order of the triangular factor U or L. N >= 0.
63*> \endverbatim
64*>
65*> \param[in,out] A
66*> \verbatim
67*> A is DOUBLE PRECISION array, dimension (LDA,N)
68*> On entry, the triangular factor U or L.
69*> On exit, if UPLO = 'U', the upper triangle of A is
70*> overwritten with the upper triangle of the product U * U**T;
71*> if UPLO = 'L', the lower triangle of A is overwritten with
72*> the lower triangle of the product L**T * L.
73*> \endverbatim
74*>
75*> \param[in] LDA
76*> \verbatim
77*> LDA is INTEGER
78*> The leading dimension of the array A. LDA >= max(1,N).
79*> \endverbatim
80*>
81*> \param[out] INFO
82*> \verbatim
83*> INFO is INTEGER
84*> = 0: successful exit
85*> < 0: if INFO = -k, the k-th argument had an illegal value
86*> \endverbatim
87*
88* Authors:
89* ========
90*
91*> \author Univ. of Tennessee
92*> \author Univ. of California Berkeley
93*> \author Univ. of Colorado Denver
94*> \author NAG Ltd.
95*
96*> \ingroup lauum
97*
98* =====================================================================
99 SUBROUTINE dlauum( UPLO, N, A, LDA, INFO )
100*
101* -- LAPACK auxiliary routine --
102* -- LAPACK is a software package provided by Univ. of Tennessee, --
103* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
104*
105* .. Scalar Arguments ..
106 CHARACTER UPLO
107 INTEGER INFO, LDA, N
108* ..
109* .. Array Arguments ..
110 DOUBLE PRECISION A( LDA, * )
111* ..
112*
113* =====================================================================
114*
115* .. Parameters ..
116 DOUBLE PRECISION ONE
117 parameter( one = 1.0d+0 )
118* ..
119* .. Local Scalars ..
120 LOGICAL UPPER
121 INTEGER I, IB, NB
122* ..
123* .. External Functions ..
124 LOGICAL LSAME
125 INTEGER ILAENV
126 EXTERNAL lsame, ilaenv
127* ..
128* .. External Subroutines ..
129 EXTERNAL dgemm, dlauu2, dsyrk, dtrmm, xerbla
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC max, min
133* ..
134* .. Executable Statements ..
135*
136* Test the input parameters.
137*
138 info = 0
139 upper = lsame( uplo, 'U' )
140 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
141 info = -1
142 ELSE IF( n.LT.0 ) THEN
143 info = -2
144 ELSE IF( lda.LT.max( 1, n ) ) THEN
145 info = -4
146 END IF
147 IF( info.NE.0 ) THEN
148 CALL xerbla( 'DLAUUM', -info )
149 RETURN
150 END IF
151*
152* Quick return if possible
153*
154 IF( n.EQ.0 )
155 $ RETURN
156*
157* Determine the block size for this environment.
158*
159 nb = ilaenv( 1, 'DLAUUM', uplo, n, -1, -1, -1 )
160*
161 IF( nb.LE.1 .OR. nb.GE.n ) THEN
162*
163* Use unblocked code
164*
165 CALL dlauu2( uplo, n, a, lda, info )
166 ELSE
167*
168* Use blocked code
169*
170 IF( upper ) THEN
171*
172* Compute the product U * U**T.
173*
174 DO 10 i = 1, n, nb
175 ib = min( nb, n-i+1 )
176 CALL dtrmm( 'Right', 'Upper', 'Transpose', 'Non-unit',
177 $ i-1, ib, one, a( i, i ), lda, a( 1, i ),
178 $ lda )
179 CALL dlauu2( 'Upper', ib, a( i, i ), lda, info )
180 IF( i+ib.LE.n ) THEN
181 CALL dgemm( '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 dsyrk( 'Upper', 'No transpose', ib, n-i-ib+1,
185 $ one, a( i, i+ib ), lda, one, a( i, i ),
186 $ lda )
187 END IF
188 10 CONTINUE
189 ELSE
190*
191* Compute the product L**T * L.
192*
193 DO 20 i = 1, n, nb
194 ib = min( nb, n-i+1 )
195 CALL dtrmm( 'Left', 'Lower', 'Transpose', 'Non-unit',
196 $ ib,
197 $ i-1, one, a( i, i ), lda, a( i, 1 ), lda )
198 CALL dlauu2( 'Lower', ib, a( i, i ), lda, info )
199 IF( i+ib.LE.n ) THEN
200 CALL dgemm( '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 dsyrk( 'Lower', 'Transpose', ib, n-i-ib+1,
204 $ 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*
215 END
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
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:100
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...
Definition dlauum.f:100
subroutine dtrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRMM
Definition dtrmm.f:177