LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
ssyt01_3.f
Go to the documentation of this file.
1 *> \brief \b SSYT01_3
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 SSYT01_3( UPLO, N, A, LDA, AFAC, LDAFAC, E, IPIV, C,
12 * 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 A( LDA, * ), AFAC( LDAFAC, * ), C( LDC, * ),
22 * $ E( * ), RWORK( * )
23 * ..
24 *
25 *
26 *> \par Purpose:
27 * =============
28 *>
29 *> \verbatim
30 *>
31 *> SSYT01_3 reconstructs a symmetric indefinite matrix A from its
32 *> block L*D*L' or U*D*U' factorization computed by SSYTRF_RK
33 *> (or SSYTRF_BK) and computes the residual
34 *> norm( C - A ) / ( N * norm(A) * EPS ),
35 *> where C is the reconstructed matrix and EPS is the machine epsilon.
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 *> 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 DOUBLE PRECISION array, dimension (LDA,N)
59 *> The original 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 DOUBLE PRECISION array, dimension (LDAFAC,N)
71 *> Diagonal of the block diagonal matrix D and factors U or L
72 *> as computed by SSYTRF_RK and SSYTRF_BK:
73 *> a) ONLY diagonal elements of the symmetric block diagonal
74 *> matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
75 *> (superdiagonal (or subdiagonal) elements of D
76 *> should be provided on entry in array E), and
77 *> b) If UPLO = 'U': factor U in the superdiagonal part of A.
78 *> If UPLO = 'L': factor L in the subdiagonal part of A.
79 *> \endverbatim
80 *>
81 *> \param[in] LDAFAC
82 *> \verbatim
83 *> LDAFAC is INTEGER
84 *> The leading dimension of the array AFAC.
85 *> LDAFAC >= max(1,N).
86 *> \endverbatim
87 *>
88 *> \param[in] E
89 *> \verbatim
90 *> E is DOUBLE PRECISION array, dimension (N)
91 *> On entry, contains the superdiagonal (or subdiagonal)
92 *> elements of the symmetric block diagonal matrix D
93 *> with 1-by-1 or 2-by-2 diagonal blocks, where
94 *> If UPLO = 'U': E(i) = D(i-1,i),i=2:N, E(1) not refernced;
95 *> If UPLO = 'L': E(i) = D(i+1,i),i=1:N-1, E(N) not referenced.
96 *> \endverbatim
97 *>
98 *> \param[in] IPIV
99 *> \verbatim
100 *> IPIV is INTEGER array, dimension (N)
101 *> The pivot indices from SSYTRF_RK (or SSYTRF_BK).
102 *> \endverbatim
103 *>
104 *> \param[out] C
105 *> \verbatim
106 *> C is DOUBLE PRECISION array, dimension (LDC,N)
107 *> \endverbatim
108 *>
109 *> \param[in] LDC
110 *> \verbatim
111 *> LDC is INTEGER
112 *> The leading dimension of the array C. LDC >= max(1,N).
113 *> \endverbatim
114 *>
115 *> \param[out] RWORK
116 *> \verbatim
117 *> RWORK is DOUBLE PRECISION array, dimension (N)
118 *> \endverbatim
119 *>
120 *> \param[out] RESID
121 *> \verbatim
122 *> RESID is DOUBLE PRECISION
123 *> If UPLO = 'L', norm(L*D*L' - A) / ( N * norm(A) * EPS )
124 *> If UPLO = 'U', norm(U*D*U' - A) / ( N * norm(A) * EPS )
125 *> \endverbatim
126 *
127 * Authors:
128 * ========
129 *
130 *> \author Univ. of Tennessee
131 *> \author Univ. of California Berkeley
132 *> \author Univ. of Colorado Denver
133 *> \author NAG Ltd.
134 *
135 *> \date December 2016
136 *
137 *> \ingroup single_lin
138 *
139 * =====================================================================
140  SUBROUTINE ssyt01_3( UPLO, N, A, LDA, AFAC, LDAFAC, E, IPIV, C,
141  $ ldc, rwork, resid )
142 *
143 * -- LAPACK test routine (version 3.7.0) --
144 * -- LAPACK is a software package provided by Univ. of Tennessee, --
145 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146 * December 2016
147 *
148 * .. Scalar Arguments ..
149  CHARACTER UPLO
150  INTEGER LDA, LDAFAC, LDC, N
151  REAL RESID
152 * ..
153 * .. Array Arguments ..
154  INTEGER IPIV( * )
155  REAL A( lda, * ), AFAC( ldafac, * ), C( ldc, * ),
156  $ e( * ), rwork( * )
157 * ..
158 *
159 * =====================================================================
160 *
161 * .. Parameters ..
162  REAL ZERO, ONE
163  parameter ( zero = 0.0e+0, one = 1.0e+0 )
164 * ..
165 * .. Local Scalars ..
166  INTEGER I, INFO, J
167  REAL ANORM, EPS
168 * ..
169 * .. External Functions ..
170  LOGICAL LSAME
171  REAL SLAMCH, SLANSY
172  EXTERNAL lsame, slamch, slansy
173 * ..
174 * .. External Subroutines ..
175  EXTERNAL slaset, slavsy_rook, ssyconvf_rook
176 * ..
177 * .. Intrinsic Functions ..
178  INTRINSIC real
179 * ..
180 * .. Executable Statements ..
181 *
182 * Quick exit if N = 0.
183 *
184  IF( n.LE.0 ) THEN
185  resid = zero
186  RETURN
187  END IF
188 *
189 * a) Revert to multiplyers of L
190 *
191  CALL ssyconvf_rook( uplo, 'R', n, afac, ldafac, e, ipiv, info )
192 *
193 * 1) Determine EPS and the norm of A.
194 *
195  eps = slamch( 'Epsilon' )
196  anorm = slansy( '1', uplo, n, a, lda, rwork )
197 *
198 * 2) Initialize C to the identity matrix.
199 *
200  CALL slaset( 'Full', n, n, zero, one, c, ldc )
201 *
202 * 3) Call SLAVSY_ROOK to form the product D * U' (or D * L' ).
203 *
204  CALL slavsy_rook( uplo, 'Transpose', 'Non-unit', n, n, afac,
205  $ ldafac, ipiv, c, ldc, info )
206 *
207 * 4) Call SLAVSY_ROOK again to multiply by U (or L ).
208 *
209  CALL slavsy_rook( uplo, 'No transpose', 'Unit', n, n, afac,
210  $ ldafac, ipiv, c, ldc, info )
211 *
212 * 5) Compute the difference C - A.
213 *
214  IF( lsame( uplo, 'U' ) ) THEN
215  DO j = 1, n
216  DO i = 1, j
217  c( i, j ) = c( i, j ) - a( i, j )
218  END DO
219  END DO
220  ELSE
221  DO j = 1, n
222  DO i = j, n
223  c( i, j ) = c( i, j ) - a( i, j )
224  END DO
225  END DO
226  END IF
227 *
228 * 6) Compute norm( C - A ) / ( N * norm(A) * EPS )
229 *
230  resid = slansy( '1', uplo, n, c, ldc, rwork )
231 *
232  IF( anorm.LE.zero ) THEN
233  IF( resid.NE.zero )
234  $ resid = one / eps
235  ELSE
236  resid = ( ( resid / REAL( N ) ) / anorm ) / eps
237  END IF
238 
239 *
240 * b) Convert to factor of L (or U)
241 *
242  CALL ssyconvf_rook( uplo, 'C', n, afac, ldafac, e, ipiv, info )
243 *
244  RETURN
245 *
246 * End of SSYT01_3
247 *
248  END
subroutine ssyconvf_rook(UPLO, WAY, N, A, LDA, E, IPIV, INFO)
SSYCONVF_ROOK
subroutine slaset(UPLO, M, N, ALPHA, BETA, A, LDA)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: slaset.f:112
subroutine ssyt01_3(UPLO, N, A, LDA, AFAC, LDAFAC, E, IPIV, C, LDC, RWORK, RESID)
SSYT01_3
Definition: ssyt01_3.f:142
subroutine slavsy_rook(UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
SLAVSY_ROOK
Definition: slavsy_rook.f:159