1*> \brief \b ZHET01_AA
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*  Definition:
9*  ===========
10*
11*       SUBROUTINE ZHET01_AA( UPLO, N, A, LDA, AFAC, LDAFAC, IPIV,
12*                             C, LDC, RWORK, RESID )
13*
14*       .. Scalar Arguments ..
15*       CHARACTER          UPLO
16*       INTEGER            LDA, LDAFAC, LDC, N
17*       DOUBLE PRECISION   RESID
18*       ..
19*       .. Array Arguments ..
20*       INTEGER            IPIV( * )
21*       DOUBLE PRECISION   RWORK( * )
22*       COMPLEX*16         A( LDA, * ), AFAC( LDAFAC, * ), C( LDC, * )
23*       ..
24*
25*
26*> \par Purpose:
27*  =============
28*>
29*> \verbatim
30*>
31*> ZHET01_AA reconstructs a hermitian indefinite matrix A from its
32*> block L*D*L' or U*D*U' factorization and computes the residual
33*>    norm( C - A ) / ( N * norm(A) * EPS ),
34*> where C is the reconstructed matrix and EPS is the machine epsilon.
35*> \endverbatim
36*
37*  Arguments:
38*  ==========
39*
40*> \param[in] UPLO
41*> \verbatim
42*>          UPLO is CHARACTER*1
43*>          Specifies whether the upper or lower triangular part of the
44*>          hermitian matrix A is stored:
45*>          = 'U':  Upper triangular
46*>          = 'L':  Lower triangular
47*> \endverbatim
48*>
49*> \param[in] N
50*> \verbatim
51*>          N is INTEGER
52*>          The number of rows and columns of the matrix A.  N >= 0.
53*> \endverbatim
54*>
55*> \param[in] A
56*> \verbatim
57*>          A is COMPLEX*16 array, dimension (LDA,N)
58*>          The original hermitian matrix A.
59*> \endverbatim
60*>
61*> \param[in] LDA
62*> \verbatim
63*>          LDA is INTEGER
64*>          The leading dimension of the array A.  LDA >= max(1,N)
65*> \endverbatim
66*>
67*> \param[in] AFAC
68*> \verbatim
69*>          AFAC is COMPLEX*16 array, dimension (LDAFAC,N)
70*>          The factored form of the matrix A.  AFAC contains the block
71*>          diagonal matrix D and the multipliers used to obtain the
72*>          factor L or U from the block L*D*L' or U*D*U' factorization
73*>          as computed by ZHETRF.
74*> \endverbatim
75*>
76*> \param[in] LDAFAC
77*> \verbatim
78*>          LDAFAC is INTEGER
79*>          The leading dimension of the array AFAC.  LDAFAC >= max(1,N).
80*> \endverbatim
81*>
82*> \param[in] IPIV
83*> \verbatim
84*>          IPIV is INTEGER array, dimension (N)
85*>          The pivot indices from ZHETRF.
86*> \endverbatim
87*>
88*> \param[out] C
89*> \verbatim
90*>          C is COMPLEX*16 array, dimension (LDC,N)
91*> \endverbatim
92*>
93*> \param[in] LDC
94*> \verbatim
95*>          LDC is INTEGER
96*>          The leading dimension of the array C.  LDC >= max(1,N).
97*> \endverbatim
98*>
99*> \param[out] RWORK
100*> \verbatim
101*>          RWORK is COMPLEX*16 array, dimension (N)
102*> \endverbatim
103*>
104*> \param[out] RESID
105*> \verbatim
106*>          RESID is COMPLEX*16
107*>          If UPLO = 'L', norm(L*D*L' - A) / ( N * norm(A) * EPS )
108*>          If UPLO = 'U', norm(U*D*U' - A) / ( N * norm(A) * EPS )
109*> \endverbatim
110*
111*  Authors:
112*  ========
113*
114*> \author Univ. of Tennessee
115*> \author Univ. of California Berkeley
116*> \author Univ. of Colorado Denver
117*> \author NAG Ltd.
118*
119*> \ingroup complex16_lin
120*
121*  =====================================================================
122      SUBROUTINE ZHET01_AA( UPLO, N, A, LDA, AFAC, LDAFAC, IPIV, C,
123     $                      LDC, RWORK, RESID )
124*
125*  -- LAPACK test routine --
126*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
127*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
128*
129*     .. Scalar Arguments ..
130      CHARACTER          UPLO
131      INTEGER            LDA, LDAFAC, LDC, N
132      DOUBLE PRECISION   RESID
133*     ..
134*     .. Array Arguments ..
135      INTEGER            IPIV( * )
136      DOUBLE PRECISION   RWORK( * )
137      COMPLEX*16         A( LDA, * ), AFAC( LDAFAC, * ), C( LDC, * )
138*     ..
139*
140*  =====================================================================
141*
142*     .. Parameters ..
143      COMPLEX*16         CZERO, CONE
144      PARAMETER          ( CZERO = ( 0.0D+0, 0.0D+0 ),
145     $                     CONE  = ( 1.0D+0, 0.0D+0 ) )
146      DOUBLE PRECISION   ZERO, ONE
147      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
148*     ..
149*     .. Local Scalars ..
150      INTEGER            I, J
151      DOUBLE PRECISION   ANORM, EPS
152*     ..
153*     .. External Functions ..
154      LOGICAL            LSAME
155      DOUBLE PRECISION   DLAMCH, ZLANHE
156      EXTERNAL           LSAME, DLAMCH, ZLANHE
157*     ..
158*     .. External Subroutines ..
159      EXTERNAL           ZLASET, ZLAVHE
160*     ..
161*     .. Intrinsic Functions ..
162      INTRINSIC          DBLE
163*     ..
164*     .. Executable Statements ..
165*
166*     Quick exit if N = 0.
167*
168      IF( N.LE.0 ) THEN
169         RESID = ZERO
170         RETURN
171      END IF
172*
173*     Determine EPS and the norm of A.
174*
175      EPS = DLAMCH( 'Epsilon' )
176      ANORM = ZLANHE( '1', UPLO, N, A, LDA, RWORK )
177*
178*     Initialize C to the tridiagonal matrix T.
179*
180      CALL ZLASET( 'Full', N, N, CZERO, CZERO, C, LDC )
181      CALL ZLACPY( 'F', 1, N, AFAC( 1, 1 ), LDAFAC+1, C( 1, 1 ), LDC+1 )
182      IF( N.GT.1 ) THEN
183         IF( LSAME( UPLO, 'U' ) ) THEN
184            CALL ZLACPY( 'F', 1, N-1, AFAC( 1, 2 ), LDAFAC+1, C( 1, 2 ),
185     $                   LDC+1 )
186            CALL ZLACPY( 'F', 1, N-1, AFAC( 1, 2 ), LDAFAC+1, C( 2, 1 ),
187     $                   LDC+1 )
188            CALL ZLACGV( N-1, C( 2, 1 ), LDC+1 )
189         ELSE
190            CALL ZLACPY( 'F', 1, N-1, AFAC( 2, 1 ), LDAFAC+1, C( 1, 2 ),
191     $                   LDC+1 )
192            CALL ZLACPY( 'F', 1, N-1, AFAC( 2, 1 ), LDAFAC+1, C( 2, 1 ),
193     $                   LDC+1 )
194            CALL ZLACGV( N-1, C( 1, 2 ), LDC+1 )
195         ENDIF
196*
197*        Call ZTRMM to form the product U' * D (or L * D ).
198*
199         IF( LSAME( UPLO, 'U' ) ) THEN
200            CALL ZTRMM( 'Left', UPLO, 'Conjugate transpose', 'Unit',
201     $                  N-1, N, CONE, AFAC( 1, 2 ), LDAFAC, C( 2, 1 ),
202     $                  LDC )
203         ELSE
204            CALL ZTRMM( 'Left', UPLO, 'No transpose', 'Unit', N-1, N,
205     $                  CONE, AFAC( 2, 1 ), LDAFAC, C( 2, 1 ), LDC )
206         END IF
207*
208*        Call ZTRMM again to multiply by U (or L ).
209*
210         IF( LSAME( UPLO, 'U' ) ) THEN
211            CALL ZTRMM( 'Right', UPLO, 'No transpose', 'Unit', N, N-1,
212     $                  CONE, AFAC( 1, 2 ), LDAFAC, C( 1, 2 ), LDC )
213         ELSE
214            CALL ZTRMM( 'Right', UPLO, 'Conjugate transpose', 'Unit', N,
215     $                  N-1, CONE, AFAC( 2, 1 ), LDAFAC, C( 1, 2 ),
216     $                  LDC )
217         END IF
218*
219*        Apply hermitian pivots
220*
221         DO J = N, 1, -1
222            I = IPIV( J )
223            IF( I.NE.J )
224     $         CALL ZSWAP( N, C( J, 1 ), LDC, C( I, 1 ), LDC )
225         END DO
226         DO J = N, 1, -1
227            I = IPIV( J )
228            IF( I.NE.J )
229     $         CALL ZSWAP( N, C( 1, J ), 1, C( 1, I ), 1 )
230         END DO
231      ENDIF
232*
233*
234*     Compute the difference  C - A .
235*
236      IF( LSAME( UPLO, 'U' ) ) THEN
237         DO J = 1, N
238            DO I = 1, J
239               C( I, J ) = C( I, J ) - A( I, J )
240            END DO
241         END DO
242      ELSE
243         DO J = 1, N
244            DO I = J, N
245               C( I, J ) = C( I, J ) - A( I, J )
246            END DO
247         END DO
248      END IF
249*
250*     Compute norm( C - A ) / ( N * norm(A) * EPS )
251*
252      RESID = ZLANHE( '1', UPLO, N, C, LDC, RWORK )
253*
254      IF( ANORM.LE.ZERO ) THEN
255         IF( RESID.NE.ZERO )
256     $      RESID = ONE / EPS
257      ELSE
258         RESID = ( ( RESID / DBLE( N ) ) / ANORM ) / EPS
259      END IF
260*
261      RETURN
262*
263*     End of ZHET01_AA
264*
265      END
266