LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine clauum ( character  UPLO,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
integer  INFO 
)

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

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

Purpose:
 CLAUUM 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 blocked form of the algorithm, calling Level 3 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.
Date
September 2012

Definition at line 104 of file clauum.f.

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  REAL one
122  parameter ( one = 1.0e+0 )
123  COMPLEX cone
124  parameter ( cone = ( 1.0e+0, 0.0e+0 ) )
125 * ..
126 * .. Local Scalars ..
127  LOGICAL upper
128  INTEGER i, ib, nb
129 * ..
130 * .. External Functions ..
131  LOGICAL lsame
132  INTEGER ilaenv
133  EXTERNAL lsame, ilaenv
134 * ..
135 * .. External Subroutines ..
136  EXTERNAL cgemm, cherk, clauu2, ctrmm, xerbla
137 * ..
138 * .. Intrinsic Functions ..
139  INTRINSIC max, min
140 * ..
141 * .. Executable Statements ..
142 *
143 * Test the input parameters.
144 *
145  info = 0
146  upper = lsame( uplo, 'U' )
147  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
148  info = -1
149  ELSE IF( n.LT.0 ) THEN
150  info = -2
151  ELSE IF( lda.LT.max( 1, n ) ) THEN
152  info = -4
153  END IF
154  IF( info.NE.0 ) THEN
155  CALL xerbla( 'CLAUUM', -info )
156  RETURN
157  END IF
158 *
159 * Quick return if possible
160 *
161  IF( n.EQ.0 )
162  $ RETURN
163 *
164 * Determine the block size for this environment.
165 *
166  nb = ilaenv( 1, 'CLAUUM', uplo, n, -1, -1, -1 )
167 *
168  IF( nb.LE.1 .OR. nb.GE.n ) THEN
169 *
170 * Use unblocked code
171 *
172  CALL clauu2( uplo, n, a, lda, info )
173  ELSE
174 *
175 * Use blocked code
176 *
177  IF( upper ) THEN
178 *
179 * Compute the product U * U**H.
180 *
181  DO 10 i = 1, n, nb
182  ib = min( nb, n-i+1 )
183  CALL ctrmm( 'Right', 'Upper', 'Conjugate transpose',
184  $ 'Non-unit', i-1, ib, cone, a( i, i ), lda,
185  $ a( 1, i ), lda )
186  CALL clauu2( 'Upper', ib, a( i, i ), lda, info )
187  IF( i+ib.LE.n ) THEN
188  CALL cgemm( 'No transpose', 'Conjugate transpose',
189  $ i-1, ib, n-i-ib+1, cone, a( 1, i+ib ),
190  $ lda, a( i, i+ib ), lda, cone, a( 1, i ),
191  $ lda )
192  CALL cherk( 'Upper', 'No transpose', ib, n-i-ib+1,
193  $ one, a( i, i+ib ), lda, one, a( i, i ),
194  $ lda )
195  END IF
196  10 CONTINUE
197  ELSE
198 *
199 * Compute the product L**H * L.
200 *
201  DO 20 i = 1, n, nb
202  ib = min( nb, n-i+1 )
203  CALL ctrmm( 'Left', 'Lower', 'Conjugate transpose',
204  $ 'Non-unit', ib, i-1, cone, a( i, i ), lda,
205  $ a( i, 1 ), lda )
206  CALL clauu2( 'Lower', ib, a( i, i ), lda, info )
207  IF( i+ib.LE.n ) THEN
208  CALL cgemm( 'Conjugate transpose', 'No transpose', ib,
209  $ i-1, n-i-ib+1, cone, a( i+ib, i ), lda,
210  $ a( i+ib, 1 ), lda, cone, a( i, 1 ), lda )
211  CALL cherk( 'Lower', 'Conjugate transpose', ib,
212  $ n-i-ib+1, one, a( i+ib, i ), lda, one,
213  $ a( i, i ), lda )
214  END IF
215  20 CONTINUE
216  END IF
217  END IF
218 *
219  RETURN
220 *
221 * End of CLAUUM
222 *
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 cherk(UPLO, TRANS, N, K, ALPHA, A, LDA, BETA, C, LDC)
CHERK
Definition: cherk.f:175
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83
subroutine ctrmm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
CTRMM
Definition: ctrmm.f:179
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: