LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlauu2.f
Go to the documentation of this file.
1*> \brief \b ZLAUU2 computes the product UUH or LHL, where U and L are upper or lower triangular matrices (unblocked algorithm).
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZLAUU2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlauu2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlauu2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlauu2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZLAUU2( UPLO, N, A, LDA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* COMPLEX*16 A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZLAUU2 computes the product U * U**H or L**H * 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 unblocked form of the algorithm, calling Level 2 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 COMPLEX*16 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**H;
71*> if UPLO = 'L', the lower triangle of A is overwritten with
72*> the lower triangle of the product L**H * 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 lauu2
97*
98* =====================================================================
99 SUBROUTINE zlauu2( 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 COMPLEX*16 A( LDA, * )
111* ..
112*
113* =====================================================================
114*
115* .. Parameters ..
116 COMPLEX*16 ONE
117 parameter( one = ( 1.0d+0, 0.0d+0 ) )
118* ..
119* .. Local Scalars ..
120 LOGICAL UPPER
121 INTEGER I
122 DOUBLE PRECISION AII
123* ..
124* .. External Functions ..
125 LOGICAL LSAME
126 COMPLEX*16 ZDOTC
127 EXTERNAL lsame, zdotc
128* ..
129* .. External Subroutines ..
130 EXTERNAL xerbla, zdscal, zgemv, zlacgv
131* ..
132* .. Intrinsic Functions ..
133 INTRINSIC dble, dcmplx, max
134* ..
135* .. Executable Statements ..
136*
137* Test the input parameters.
138*
139 info = 0
140 upper = lsame( uplo, 'U' )
141 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
142 info = -1
143 ELSE IF( n.LT.0 ) THEN
144 info = -2
145 ELSE IF( lda.LT.max( 1, n ) ) THEN
146 info = -4
147 END IF
148 IF( info.NE.0 ) THEN
149 CALL xerbla( 'ZLAUU2', -info )
150 RETURN
151 END IF
152*
153* Quick return if possible
154*
155 IF( n.EQ.0 )
156 $ RETURN
157*
158 IF( upper ) THEN
159*
160* Compute the product U * U**H.
161*
162 DO 10 i = 1, n
163 aii = dble( a( i, i ) )
164 IF( i.LT.n ) THEN
165 a( i, i ) = aii*aii + dble( zdotc( n-i, a( i, i+1 ),
166 $ lda,
167 $ a( i, i+1 ), lda ) )
168 CALL zlacgv( n-i, a( i, i+1 ), lda )
169 CALL zgemv( 'No transpose', i-1, n-i, one, a( 1,
170 $ i+1 ),
171 $ lda, a( i, i+1 ), lda, dcmplx( aii ),
172 $ a( 1, i ), 1 )
173 CALL zlacgv( n-i, a( i, i+1 ), lda )
174 ELSE
175 CALL zdscal( i, aii, a( 1, i ), 1 )
176 END IF
177 10 CONTINUE
178*
179 ELSE
180*
181* Compute the product L**H * L.
182*
183 DO 20 i = 1, n
184 aii = dble( a( i, i ) )
185 IF( i.LT.n ) THEN
186 a( i, i ) = aii*aii + dble( zdotc( n-i, a( i+1, i ),
187 $ 1,
188 $ a( i+1, i ), 1 ) )
189 CALL zlacgv( i-1, a( i, 1 ), lda )
190 CALL zgemv( 'Conjugate transpose', n-i, i-1, one,
191 $ a( i+1, 1 ), lda, a( i+1, i ), 1,
192 $ dcmplx( aii ), a( i, 1 ), lda )
193 CALL zlacgv( i-1, a( i, 1 ), lda )
194 ELSE
195 CALL zdscal( i, aii, a( i, 1 ), lda )
196 END IF
197 20 CONTINUE
198 END IF
199*
200 RETURN
201*
202* End of ZLAUU2
203*
204 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zlacgv(n, x, incx)
ZLACGV conjugates a complex vector.
Definition zlacgv.f:72
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:100
subroutine zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78