fix build error
[platform/upstream/openblas.git] / reference / zlauumf.f
1       SUBROUTINE ZLAUUMF( UPLO, N, A, LDA, INFO )
2 *
3 *  -- LAPACK auxiliary routine (version 3.0) --
4 *     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
5 *     Courant Institute, Argonne National Lab, and Rice University
6 *     September 30, 1994
7 *
8 *     .. Scalar Arguments ..
9       CHARACTER          UPLO
10       INTEGER            INFO, LDA, N
11 *     ..
12 *     .. Array Arguments ..
13       COMPLEX*16         A( LDA, * )
14 *     ..
15 *
16 *  Purpose
17 *  =======
18 *
19 *  ZLAUUM computes the product U * U' or L' * L, where the triangular
20 *  factor U or L is stored in the upper or lower triangular part of
21 *  the array A.
22 *
23 *  If UPLO = 'U' or 'u' then the upper triangle of the result is stored,
24 *  overwriting the factor U in A.
25 *  If UPLO = 'L' or 'l' then the lower triangle of the result is stored,
26 *  overwriting the factor L in A.
27 *
28 *  This is the blocked form of the algorithm, calling Level 3 BLAS.
29 *
30 *  Arguments
31 *  =========
32 *
33 *  UPLO    (input) CHARACTER*1
34 *          Specifies whether the triangular factor stored in the array A
35 *          is upper or lower triangular:
36 *          = 'U':  Upper triangular
37 *          = 'L':  Lower triangular
38 *
39 *  N       (input) INTEGER
40 *          The order of the triangular factor U or L.  N >= 0.
41 *
42 *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
43 *          On entry, the triangular factor U or L.
44 *          On exit, if UPLO = 'U', the upper triangle of A is
45 *          overwritten with the upper triangle of the product U * U';
46 *          if UPLO = 'L', the lower triangle of A is overwritten with
47 *          the lower triangle of the product L' * L.
48 *
49 *  LDA     (input) INTEGER
50 *          The leading dimension of the array A.  LDA >= max(1,N).
51 *
52 *  INFO    (output) INTEGER
53 *          = 0: successful exit
54 *          < 0: if INFO = -k, the k-th argument had an illegal value
55 *
56 *  =====================================================================
57 *
58 *     .. Parameters ..
59       DOUBLE PRECISION   ONE
60       PARAMETER          ( ONE = 1.0D+0 )
61       COMPLEX*16         CONE
62       PARAMETER          ( CONE = ( 1.0D+0, 0.0D+0 ) )
63 *     ..
64 *     .. Local Scalars ..
65       LOGICAL            UPPER
66       INTEGER            I, IB, NB
67 *     ..
68 *     .. External Functions ..
69       LOGICAL            LSAME
70       EXTERNAL           LSAME
71 *     ..
72 *     .. External Subroutines ..
73       EXTERNAL           XERBLA, ZGEMM, ZHERK, ZLAUU2, ZTRMM
74 *     ..
75 *     .. Intrinsic Functions ..
76       INTRINSIC          MAX, MIN
77 *     ..
78 *     .. Executable Statements ..
79 *
80 *     Test the input parameters.
81 *
82       INFO = 0
83       UPPER = LSAME( UPLO, 'U' )
84       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
85          INFO = -1
86       ELSE IF( N.LT.0 ) THEN
87          INFO = -2
88       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
89          INFO = -4
90       END IF
91       IF( INFO.NE.0 ) THEN
92          CALL XERBLA( 'ZLAUUM', -INFO )
93          RETURN
94       END IF
95 *
96 *     Quick return if possible
97 *
98       IF( N.EQ.0 )
99      $   RETURN
100 *
101 *     Determine the block size for this environment.
102 *
103       NB = 128
104 *
105       IF( NB.LE.1 .OR. NB.GE.N ) THEN
106 *
107 *        Use unblocked code
108 *
109          CALL ZLAUU2( UPLO, N, A, LDA, INFO )
110       ELSE
111 *
112 *        Use blocked code
113 *
114          IF( UPPER ) THEN
115 *
116 *           Compute the product U * U'.
117 *
118             DO 10 I = 1, N, NB
119                IB = MIN( NB, N-I+1 )
120                CALL ZTRMM( 'Right', 'Upper', 'Conjugate transpose',
121      $                     'Non-unit', I-1, IB, CONE, A( I, I ), LDA,
122      $                     A( 1, I ), LDA )
123                CALL ZLAUU2( 'Upper', IB, A( I, I ), LDA, INFO )
124                IF( I+IB.LE.N ) THEN
125                   CALL ZGEMM( 'No transpose', 'Conjugate transpose',
126      $                        I-1, IB, N-I-IB+1, CONE, A( 1, I+IB ),
127      $                        LDA, A( I, I+IB ), LDA, CONE, A( 1, I ),
128      $                        LDA )
129                   CALL ZHERK( 'Upper', 'No transpose', IB, N-I-IB+1,
130      $                        ONE, A( I, I+IB ), LDA, ONE, A( I, I ),
131      $                        LDA )
132                END IF
133    10       CONTINUE
134          ELSE
135 *
136 *           Compute the product L' * L.
137 *
138             DO 20 I = 1, N, NB
139                IB = MIN( NB, N-I+1 )
140                CALL ZTRMM( 'Left', 'Lower', 'Conjugate transpose',
141      $                     'Non-unit', IB, I-1, CONE, A( I, I ), LDA,
142      $                     A( I, 1 ), LDA )
143                CALL ZLAUU2( 'Lower', IB, A( I, I ), LDA, INFO )
144                IF( I+IB.LE.N ) THEN
145                   CALL ZGEMM( 'Conjugate transpose', 'No transpose', IB,
146      $                        I-1, N-I-IB+1, CONE, A( I+IB, I ), LDA,
147      $                        A( I+IB, 1 ), LDA, CONE, A( I, 1 ), LDA )
148                   CALL ZHERK( 'Lower', 'Conjugate transpose', IB,
149      $                        N-I-IB+1, ONE, A( I+IB, I ), LDA, ONE,
150      $                        A( I, I ), LDA )
151                END IF
152    20       CONTINUE
153          END IF
154       END IF
155 *
156       RETURN
157 *
158 *     End of ZLAUUM
159 *
160       END