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

◆ clauu2()

subroutine clauu2 ( character  uplo,
integer  n,
complex, dimension( lda, * )  a,
integer  lda,
integer  info 
)

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

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

Purpose:
 CLAUU2 computes the product U * U**H or L**H * 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 unblocked form of the algorithm, calling Level 2 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 COMPLEX 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**H;
          if UPLO = 'L', the lower triangle of A is overwritten with
          the lower triangle of the product L**H * 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 clauu2.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 COMPLEX A( LDA, * )
113* ..
114*
115* =====================================================================
116*
117* .. Parameters ..
118 COMPLEX ONE
119 parameter( one = ( 1.0e+0, 0.0e+0 ) )
120* ..
121* .. Local Scalars ..
122 LOGICAL UPPER
123 INTEGER I
124 REAL AII
125* ..
126* .. External Functions ..
127 LOGICAL LSAME
128 COMPLEX CDOTC
129 EXTERNAL lsame, cdotc
130* ..
131* .. External Subroutines ..
132 EXTERNAL cgemv, clacgv, csscal, xerbla
133* ..
134* .. Intrinsic Functions ..
135 INTRINSIC cmplx, max, real
136* ..
137* .. Executable Statements ..
138*
139* Test the input parameters.
140*
141 info = 0
142 upper = lsame( uplo, 'U' )
143 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
144 info = -1
145 ELSE IF( n.LT.0 ) THEN
146 info = -2
147 ELSE IF( lda.LT.max( 1, n ) ) THEN
148 info = -4
149 END IF
150 IF( info.NE.0 ) THEN
151 CALL xerbla( 'CLAUU2', -info )
152 RETURN
153 END IF
154*
155* Quick return if possible
156*
157 IF( n.EQ.0 )
158 $ RETURN
159*
160 IF( upper ) THEN
161*
162* Compute the product U * U**H.
163*
164 DO 10 i = 1, n
165 aii = real( a( i, i ) )
166 IF( i.LT.n ) THEN
167 a( i, i ) = aii*aii + real( cdotc( n-i, a( i, i+1 ), lda,
168 $ a( i, i+1 ), lda ) )
169 CALL clacgv( n-i, a( i, i+1 ), lda )
170 CALL cgemv( 'No transpose', i-1, n-i, one, a( 1, i+1 ),
171 $ lda, a( i, i+1 ), lda, cmplx( aii ),
172 $ a( 1, i ), 1 )
173 CALL clacgv( n-i, a( i, i+1 ), lda )
174 ELSE
175 CALL csscal( 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 = real( a( i, i ) )
185 IF( i.LT.n ) THEN
186 a( i, i ) = aii*aii + real( cdotc( n-i, a( i+1, i ), 1,
187 $ a( i+1, i ), 1 ) )
188 CALL clacgv( i-1, a( i, 1 ), lda )
189 CALL cgemv( 'Conjugate transpose', n-i, i-1, one,
190 $ a( i+1, 1 ), lda, a( i+1, i ), 1,
191 $ cmplx( aii ), a( i, 1 ), lda )
192 CALL clacgv( i-1, a( i, 1 ), lda )
193 ELSE
194 CALL csscal( i, aii, a( i, 1 ), lda )
195 END IF
196 20 CONTINUE
197 END IF
198*
199 RETURN
200*
201* End of CLAUU2
202*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
complex function cdotc(n, cx, incx, cy, incy)
CDOTC
Definition cdotc.f:83
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
Definition cgemv.f:160
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:74
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
Here is the call graph for this function:
Here is the caller graph for this function: