LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
clauu2.f
Go to the documentation of this file.
1 *> \brief \b CLAUU2 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 *> \htmlonly
9 *> Download CLAUU2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clauu2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clauu2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clauu2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CLAUU2( UPLO, N, A, LDA, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER UPLO
25 * INTEGER INFO, LDA, N
26 * ..
27 * .. Array Arguments ..
28 * COMPLEX A( LDA, * )
29 * ..
30 *
31 *
32 *> \par Purpose:
33 * =============
34 *>
35 *> \verbatim
36 *>
37 *> CLAUU2 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 unblocked form of the algorithm, calling Level 2 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 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 *> \date September 2012
99 *
100 *> \ingroup complexOTHERauxiliary
101 *
102 * =====================================================================
103  SUBROUTINE clauu2( UPLO, N, A, LDA, INFO )
104 *
105 * -- LAPACK auxiliary routine (version 3.4.2) --
106 * -- LAPACK is a software package provided by Univ. of Tennessee, --
107 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
108 * September 2012
109 *
110 * .. Scalar Arguments ..
111  CHARACTER UPLO
112  INTEGER INFO, LDA, N
113 * ..
114 * .. Array Arguments ..
115  COMPLEX A( lda, * )
116 * ..
117 *
118 * =====================================================================
119 *
120 * .. Parameters ..
121  COMPLEX ONE
122  parameter ( one = ( 1.0e+0, 0.0e+0 ) )
123 * ..
124 * .. Local Scalars ..
125  LOGICAL UPPER
126  INTEGER I
127  REAL AII
128 * ..
129 * .. External Functions ..
130  LOGICAL LSAME
131  COMPLEX CDOTC
132  EXTERNAL lsame, cdotc
133 * ..
134 * .. External Subroutines ..
135  EXTERNAL cgemv, clacgv, csscal, xerbla
136 * ..
137 * .. Intrinsic Functions ..
138  INTRINSIC cmplx, max, real
139 * ..
140 * .. Executable Statements ..
141 *
142 * Test the input parameters.
143 *
144  info = 0
145  upper = lsame( uplo, 'U' )
146  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
147  info = -1
148  ELSE IF( n.LT.0 ) THEN
149  info = -2
150  ELSE IF( lda.LT.max( 1, n ) ) THEN
151  info = -4
152  END IF
153  IF( info.NE.0 ) THEN
154  CALL xerbla( 'CLAUU2', -info )
155  RETURN
156  END IF
157 *
158 * Quick return if possible
159 *
160  IF( n.EQ.0 )
161  $ RETURN
162 *
163  IF( upper ) THEN
164 *
165 * Compute the product U * U**H.
166 *
167  DO 10 i = 1, n
168  aii = a( i, i )
169  IF( i.LT.n ) THEN
170  a( i, i ) = aii*aii + REAL( CDOTC( N-I, A( I, I+1 ), LDA, $ A( I, I+1 ), LDA ) )
171  CALL clacgv( n-i, a( i, i+1 ), lda )
172  CALL cgemv( 'No transpose', i-1, n-i, one, a( 1, i+1 ),
173  $ lda, a( i, i+1 ), lda, cmplx( aii ),
174  $ a( 1, i ), 1 )
175  CALL clacgv( n-i, a( i, i+1 ), lda )
176  ELSE
177  CALL csscal( i, aii, a( 1, i ), 1 )
178  END IF
179  10 CONTINUE
180 *
181  ELSE
182 *
183 * Compute the product L**H * L.
184 *
185  DO 20 i = 1, n
186  aii = a( i, i )
187  IF( i.LT.n ) THEN
188  a( i, i ) = aii*aii + REAL( CDOTC( N-I, A( I+1, I ), 1, $ A( I+1, I ), 1 ) )
189  CALL clacgv( i-1, a( i, 1 ), lda )
190  CALL cgemv( 'Conjugate transpose', n-i, i-1, one,
191  $ a( i+1, 1 ), lda, a( i+1, i ), 1,
192  $ cmplx( aii ), a( i, 1 ), lda )
193  CALL clacgv( i-1, a( i, 1 ), lda )
194  ELSE
195  CALL csscal( i, aii, a( i, 1 ), lda )
196  END IF
197  20 CONTINUE
198  END IF
199 *
200  RETURN
201 *
202 * End of CLAUU2
203 *
204  END
205 
subroutine clauu2(UPLO, N, A, LDA, INFO)
CLAUU2 computes the product UUH or LHL, where U and L are upper or lower triangular matrices (unblock...
Definition: clauu2.f:104
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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:76
subroutine csscal(N, SA, CX, INCX)
CSSCAL
Definition: csscal.f:54