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