1 *> \brief \b SLAUU2 computes the product UUH or LHL, where U and L are upper or lower triangular matrices (unblocked algorithm).
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SLAUU2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slauu2.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slauu2.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slauu2.f">
21 * SUBROUTINE SLAUU2( UPLO, N, A, LDA, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, N
27 * .. Array Arguments ..
37 *> SLAUU2 computes the product U * U**T or L**T * L, where the triangular
38 *> factor U or L is stored in the upper or lower triangular part of
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.
46 *> This is the unblocked form of the algorithm, calling Level 2 BLAS.
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
64 *> The order of the triangular factor U or L. N >= 0.
69 *> A is REAL 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**T;
73 *> if UPLO = 'L', the lower triangle of A is overwritten with
74 *> the lower triangle of the product L**T * L.
80 *> The leading dimension of the array A. LDA >= max(1,N).
86 *> = 0: successful exit
87 *> < 0: if INFO = -k, the k-th argument had an illegal value
93 *> \author Univ. of Tennessee
94 *> \author Univ. of California Berkeley
95 *> \author Univ. of Colorado Denver
98 *> \date September 2012
100 *> \ingroup realOTHERauxiliary
102 * =====================================================================
103 SUBROUTINE SLAUU2( UPLO, N, A, LDA, INFO )
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..--
110 * .. Scalar Arguments ..
114 * .. Array Arguments ..
118 * =====================================================================
122 PARAMETER ( ONE = 1.0E+0 )
124 * .. Local Scalars ..
129 * .. External Functions ..
134 * .. External Subroutines ..
135 EXTERNAL SGEMV, SSCAL, XERBLA
137 * .. Intrinsic Functions ..
140 * .. Executable Statements ..
142 * Test the input parameters.
145 UPPER = LSAME( UPLO, 'U' )
146 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
148 ELSE IF( N.LT.0 ) THEN
150 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
154 CALL XERBLA( 'SLAUU2', -INFO )
158 * Quick return if possible
165 * Compute the product U * U**T.
170 A( I, I ) = SDOT( N-I+1, A( I, I ), LDA, A( I, I ), LDA )
171 CALL SGEMV( 'No transpose', I-1, N-I, ONE, A( 1, I+1 ),
172 $ LDA, A( I, I+1 ), LDA, AII, A( 1, I ), 1 )
174 CALL SSCAL( I, AII, A( 1, I ), 1 )
180 * Compute the product L**T * L.
185 A( I, I ) = SDOT( N-I+1, A( I, I ), 1, A( I, I ), 1 )
186 CALL SGEMV( 'Transpose', N-I, I-1, ONE, A( I+1, 1 ), LDA,
187 $ A( I+1, I ), 1, AII, A( I, 1 ), LDA )
189 CALL SSCAL( I, AII, A( I, 1 ), LDA )