LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zsyt01_rook.f
Go to the documentation of this file.
1 *> \brief \b ZSYT01_ROOK
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 ZSYT01_ROOK( UPLO, N, A, LDA, AFAC, LDAFAC, IPIV, C, LDC,
12 * 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 *> ZSYT01_ROOK reconstructs a complex symmetric 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, EPS is the machine epsilon,
35 *> L' is the transpose of L, and U' is the transpose of U.
36 *> \endverbatim
37 *
38 * Arguments:
39 * ==========
40 *
41 *> \param[in] UPLO
42 *> \verbatim
43 *> UPLO is CHARACTER*1
44 *> Specifies whether the upper or lower triangular part of the
45 *> complex symmetric matrix A is stored:
46 *> = 'U': Upper triangular
47 *> = 'L': Lower triangular
48 *> \endverbatim
49 *>
50 *> \param[in] N
51 *> \verbatim
52 *> N is INTEGER
53 *> The number of rows and columns of the matrix A. N >= 0.
54 *> \endverbatim
55 *>
56 *> \param[in] A
57 *> \verbatim
58 *> A is COMPLEX*16 array, dimension (LDA,N)
59 *> The original complex symmetric matrix A.
60 *> \endverbatim
61 *>
62 *> \param[in] LDA
63 *> \verbatim
64 *> LDA is INTEGER
65 *> The leading dimension of the array A. LDA >= max(1,N)
66 *> \endverbatim
67 *>
68 *> \param[in] AFAC
69 *> \verbatim
70 *> AFAC is COMPLEX*16 array, dimension (LDAFAC,N)
71 *> The factored form of the matrix A. AFAC contains the block
72 *> diagonal matrix D and the multipliers used to obtain the
73 *> factor L or U from the block L*D*L' or U*D*U' factorization
74 *> as computed by ZSYTRF_ROOK.
75 *> \endverbatim
76 *>
77 *> \param[in] LDAFAC
78 *> \verbatim
79 *> LDAFAC is INTEGER
80 *> The leading dimension of the array AFAC. LDAFAC >= max(1,N).
81 *> \endverbatim
82 *>
83 *> \param[in] IPIV
84 *> \verbatim
85 *> IPIV is INTEGER array, dimension (N)
86 *> The pivot indices from ZSYTRF_ROOK.
87 *> \endverbatim
88 *>
89 *> \param[out] C
90 *> \verbatim
91 *> C is COMPLEX*16 array, dimension (LDC,N)
92 *> \endverbatim
93 *>
94 *> \param[in] LDC
95 *> \verbatim
96 *> LDC is INTEGER
97 *> The leading dimension of the array C. LDC >= max(1,N).
98 *> \endverbatim
99 *>
100 *> \param[out] RWORK
101 *> \verbatim
102 *> RWORK is DOUBLE PRECISION array, dimension (N)
103 *> \endverbatim
104 *>
105 *> \param[out] RESID
106 *> \verbatim
107 *> RESID is DOUBLE PRECISION
108 *> If UPLO = 'L', norm(L*D*L' - A) / ( N * norm(A) * EPS )
109 *> If UPLO = 'U', norm(U*D*U' - A) / ( N * norm(A) * EPS )
110 *> \endverbatim
111 *
112 * Authors:
113 * ========
114 *
115 *> \author Univ. of Tennessee
116 *> \author Univ. of California Berkeley
117 *> \author Univ. of Colorado Denver
118 *> \author NAG Ltd.
119 *
120 *> \date November 2013
121 *
122 *> \ingroup complex16_lin
123 *
124 * =====================================================================
125  SUBROUTINE zsyt01_rook( UPLO, N, A, LDA, AFAC, LDAFAC, IPIV, C,
126  $ ldc, rwork, resid )
127 *
128 * -- LAPACK test routine (version 3.5.0) --
129 * -- LAPACK is a software package provided by Univ. of Tennessee, --
130 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131 * November 2013
132 *
133 * .. Scalar Arguments ..
134  CHARACTER UPLO
135  INTEGER LDA, LDAFAC, LDC, N
136  DOUBLE PRECISION RESID
137 * ..
138 * .. Array Arguments ..
139  INTEGER IPIV( * )
140  DOUBLE PRECISION RWORK( * )
141  COMPLEX*16 A( lda, * ), AFAC( ldafac, * ), C( ldc, * )
142 * ..
143 *
144 * =====================================================================
145 *
146 * .. Parameters ..
147  DOUBLE PRECISION ZERO, ONE
148  parameter ( zero = 0.0d+0, one = 1.0d+0 )
149  COMPLEX*16 CZERO, CONE
150  parameter ( czero = ( 0.0d+0, 0.0d+0 ),
151  $ cone = ( 1.0d+0, 0.0d+0 ) )
152 * ..
153 * .. Local Scalars ..
154  INTEGER I, INFO, J
155  DOUBLE PRECISION ANORM, EPS
156 * ..
157 * .. External Functions ..
158  LOGICAL LSAME
159  DOUBLE PRECISION DLAMCH, ZLANSY
160  EXTERNAL lsame, dlamch, zlansy
161 * ..
162 * .. External Subroutines ..
163  EXTERNAL zlaset, zlavsy_rook
164 * ..
165 * .. Intrinsic Functions ..
166  INTRINSIC dble
167 * ..
168 * .. Executable Statements ..
169 *
170 * Quick exit if N = 0.
171 *
172  IF( n.LE.0 ) THEN
173  resid = zero
174  RETURN
175  END IF
176 *
177 * Determine EPS and the norm of A.
178 *
179  eps = dlamch( 'Epsilon' )
180  anorm = zlansy( '1', uplo, n, a, lda, rwork )
181 *
182 * Initialize C to the identity matrix.
183 *
184  CALL zlaset( 'Full', n, n, czero, cone, c, ldc )
185 *
186 * Call ZLAVSY_ROOK to form the product D * U' (or D * L' ).
187 *
188  CALL zlavsy_rook( uplo, 'Transpose', 'Non-unit', n, n, afac,
189  $ ldafac, ipiv, c, ldc, info )
190 *
191 * Call ZLAVSY_ROOK again to multiply by U (or L ).
192 *
193  CALL zlavsy_rook( uplo, 'No transpose', 'Unit', n, n, afac,
194  $ ldafac, ipiv, c, ldc, info )
195 *
196 * Compute the difference C - A .
197 *
198  IF( lsame( uplo, 'U' ) ) THEN
199  DO 20 j = 1, n
200  DO 10 i = 1, j
201  c( i, j ) = c( i, j ) - a( i, j )
202  10 CONTINUE
203  20 CONTINUE
204  ELSE
205  DO 40 j = 1, n
206  DO 30 i = j, n
207  c( i, j ) = c( i, j ) - a( i, j )
208  30 CONTINUE
209  40 CONTINUE
210  END IF
211 *
212 * Compute norm( C - A ) / ( N * norm(A) * EPS )
213 *
214  resid = zlansy( '1', uplo, n, c, ldc, rwork )
215 *
216  IF( anorm.LE.zero ) THEN
217  IF( resid.NE.zero )
218  $ resid = one / eps
219  ELSE
220  resid = ( ( resid / dble( n ) ) / anorm ) / eps
221  END IF
222 *
223  RETURN
224 *
225 * End of ZSYT01_ROOK
226 *
227  END
subroutine zsyt01_rook(UPLO, N, A, LDA, AFAC, LDAFAC, IPIV, C, LDC, RWORK, RESID)
ZSYT01_ROOK
Definition: zsyt01_rook.f:127
subroutine zlavsy_rook(UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZLAVSY_ROOK
Definition: zlavsy_rook.f:157
subroutine zlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: zlaset.f:108