LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dchkec.f
Go to the documentation of this file.
1*> \brief \b DCHKEC
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 DCHKEC( THRESH, TSTERR, NIN, NOUT )
12*
13* .. Scalar Arguments ..
14* LOGICAL TSTERR
15* INTEGER NIN, NOUT
16* DOUBLE PRECISION THRESH
17* ..
18*
19*
20*> \par Purpose:
21* =============
22*>
23*> \verbatim
24*>
25*> DCHKEC tests eigen- condition estimation routines
26*> DLALN2, DLASY2, DLANV2, DLAQTR, DLAEXC,
27*> DTRSYL, DTREXC, DTRSNA, DTRSEN, DTGEXC
28*>
29*> In all cases, the routine runs through a fixed set of numerical
30*> examples, subjects them to various tests, and compares the test
31*> results to a threshold THRESH. In addition, DTREXC, DTRSNA and DTRSEN
32*> are tested by reading in precomputed examples from a file (on input
33*> unit NIN). Output is written to output unit NOUT.
34*> \endverbatim
35*
36* Arguments:
37* ==========
38*
39*> \param[in] THRESH
40*> \verbatim
41*> THRESH is DOUBLE PRECISION
42*> Threshold for residual tests. A computed test ratio passes
43*> the threshold if it is less than THRESH.
44*> \endverbatim
45*>
46*> \param[in] TSTERR
47*> \verbatim
48*> TSTERR is LOGICAL
49*> Flag that indicates whether error exits are to be tested.
50*> \endverbatim
51*>
52*> \param[in] NIN
53*> \verbatim
54*> NIN is INTEGER
55*> The logical unit number for input.
56*> \endverbatim
57*>
58*> \param[in] NOUT
59*> \verbatim
60*> NOUT is INTEGER
61*> The logical unit number for output.
62*> \endverbatim
63*
64* Authors:
65* ========
66*
67*> \author Univ. of Tennessee
68*> \author Univ. of California Berkeley
69*> \author Univ. of Colorado Denver
70*> \author NAG Ltd.
71*
72*> \ingroup double_eig
73*
74* =====================================================================
75 SUBROUTINE dchkec( THRESH, TSTERR, NIN, NOUT )
76*
77* -- LAPACK test routine --
78* -- LAPACK is a software package provided by Univ. of Tennessee, --
79* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
80*
81* .. Scalar Arguments ..
82 LOGICAL TSTERR
83 INTEGER NIN, NOUT
84 DOUBLE PRECISION THRESH
85* ..
86*
87* =====================================================================
88*
89* .. Local Scalars ..
90 LOGICAL OK
91 CHARACTER*3 PATH
92 INTEGER KLAEXC, KLALN2, KLANV2, KLAQTR, KLASY2, KTREXC,
93 $ KTRSEN, KTRSNA, KTRSYL, KTRSYL3, LLAEXC,
94 $ LLALN2, LLANV2, LLAQTR, LLASY2, LTREXC, LTRSYL,
95 $ NLANV2, NLAQTR, NLASY2, NTESTS, NTRSYL, KTGEXC,
96 $ LTGEXC
97 DOUBLE PRECISION EPS, RLAEXC, RLALN2, RLANV2, RLAQTR, RLASY2,
98 $ RTREXC, SFMIN, RTGEXC
99* ..
100* .. Local Arrays ..
101 INTEGER FTRSYL( 3 ), ITRSYL( 2 ), LTRSEN( 3 ),
102 $ LTRSNA( 3 ), NLAEXC( 2 ), NLALN2( 2 ),
103 $ NTGEXC( 2 ), NTREXC( 3 ), NTRSEN( 3 ),
104 $ NTRSNA( 3 )
105 DOUBLE PRECISION RTRSEN( 3 ), RTRSNA( 3 ), RTRSYL( 2 )
106* ..
107* .. External Subroutines ..
108 EXTERNAL derrec, dget31, dget32, dget33, dget34, dget35,
110* ..
111* .. External Functions ..
112 DOUBLE PRECISION DLAMCH
113 EXTERNAL dlamch
114* ..
115* .. Executable Statements ..
116*
117 path( 1: 1 ) = 'Double precision'
118 path( 2: 3 ) = 'EC'
119 eps = dlamch( 'P' )
120 sfmin = dlamch( 'S' )
121*
122* Print header information
123*
124 WRITE( nout, fmt = 9989 )
125 WRITE( nout, fmt = 9988 )eps, sfmin
126 WRITE( nout, fmt = 9987 )thresh
127*
128* Test error exits if TSTERR is .TRUE.
129*
130 IF( tsterr )
131 $ CALL derrec( path, nout )
132*
133 ok = .true.
134 CALL dget31( rlaln2, llaln2, nlaln2, klaln2 )
135 IF( rlaln2.GT.thresh .OR. nlaln2( 1 ).NE.0 ) THEN
136 ok = .false.
137 WRITE( nout, fmt = 9999 )rlaln2, llaln2, nlaln2, klaln2
138 END IF
139*
140 CALL dget32( rlasy2, llasy2, nlasy2, klasy2 )
141 IF( rlasy2.GT.thresh ) THEN
142 ok = .false.
143 WRITE( nout, fmt = 9998 )rlasy2, llasy2, nlasy2, klasy2
144 END IF
145*
146 CALL dget33( rlanv2, llanv2, nlanv2, klanv2 )
147 IF( rlanv2.GT.thresh .OR. nlanv2.NE.0 ) THEN
148 ok = .false.
149 WRITE( nout, fmt = 9997 )rlanv2, llanv2, nlanv2, klanv2
150 END IF
151*
152 CALL dget34( rlaexc, llaexc, nlaexc, klaexc )
153 IF( rlaexc.GT.thresh .OR. nlaexc( 2 ).NE.0 ) THEN
154 ok = .false.
155 WRITE( nout, fmt = 9996 )rlaexc, llaexc, nlaexc, klaexc
156 END IF
157*
158 CALL dget35( rtrsyl( 1 ), ltrsyl, ntrsyl, ktrsyl )
159 IF( rtrsyl( 1 ).GT.thresh ) THEN
160 ok = .false.
161 WRITE( nout, fmt = 9995 )rtrsyl( 1 ), ltrsyl, ntrsyl, ktrsyl
162 END IF
163*
164 CALL dsyl01( thresh, ftrsyl, rtrsyl, itrsyl, ktrsyl3 )
165 IF( ftrsyl( 1 ).GT.0 ) THEN
166 ok = .false.
167 WRITE( nout, fmt = 9970 )ftrsyl( 1 ), rtrsyl( 1 ), thresh
168 END IF
169 IF( ftrsyl( 2 ).GT.0 ) THEN
170 ok = .false.
171 WRITE( nout, fmt = 9971 )ftrsyl( 2 ), rtrsyl( 2 ), thresh
172 END IF
173 IF( ftrsyl( 3 ).GT.0 ) THEN
174 ok = .false.
175 WRITE( nout, fmt = 9972 )ftrsyl( 3 )
176 END IF
177*
178 CALL dget36( rtrexc, ltrexc, ntrexc, ktrexc, nin )
179 IF( rtrexc.GT.thresh .OR. ntrexc( 3 ).GT.0 ) THEN
180 ok = .false.
181 WRITE( nout, fmt = 9994 )rtrexc, ltrexc, ntrexc, ktrexc
182 END IF
183*
184 CALL dget37( rtrsna, ltrsna, ntrsna, ktrsna, nin )
185 IF( rtrsna( 1 ).GT.thresh .OR. rtrsna( 2 ).GT.thresh .OR.
186 $ ntrsna( 1 ).NE.0 .OR. ntrsna( 2 ).NE.0 .OR. ntrsna( 3 ).NE.0 )
187 $ THEN
188 ok = .false.
189 WRITE( nout, fmt = 9993 )rtrsna, ltrsna, ntrsna, ktrsna
190 END IF
191*
192 CALL dget38( rtrsen, ltrsen, ntrsen, ktrsen, nin )
193 IF( rtrsen( 1 ).GT.thresh .OR. rtrsen( 2 ).GT.thresh .OR.
194 $ ntrsen( 1 ).NE.0 .OR. ntrsen( 2 ).NE.0 .OR. ntrsen( 3 ).NE.0 )
195 $ THEN
196 ok = .false.
197 WRITE( nout, fmt = 9992 )rtrsen, ltrsen, ntrsen, ktrsen
198 END IF
199*
200 CALL dget39( rlaqtr, llaqtr, nlaqtr, klaqtr )
201 IF( rlaqtr.GT.thresh ) THEN
202 ok = .false.
203 WRITE( nout, fmt = 9991 )rlaqtr, llaqtr, nlaqtr, klaqtr
204 END IF
205*
206 CALL dget40( rtgexc, ltgexc, ntgexc, ktgexc, nin )
207 IF( rtgexc.GT.thresh ) THEN
208 ok = .false.
209 WRITE( nout, fmt = 9986 )rtgexc, ltgexc, ntgexc, ktgexc
210 END IF
211*
212 ntests = klaln2 + klasy2 + klanv2 + klaexc + ktrsyl + ktrexc +
213 $ ktrsna + ktrsen + klaqtr + ktgexc
214 IF( ok )
215 $ WRITE( nout, fmt = 9990 )path, ntests
216*
217 RETURN
218 9999 FORMAT( ' Error in DLALN2: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
219 $ 'INFO=', 2i8, ' KNT=', i8 )
220 9998 FORMAT( ' Error in DLASY2: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
221 $ 'INFO=', i8, ' KNT=', i8 )
222 9997 FORMAT( ' Error in DLANV2: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
223 $ 'INFO=', i8, ' KNT=', i8 )
224 9996 FORMAT( ' Error in DLAEXC: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
225 $ 'INFO=', 2i8, ' KNT=', i8 )
226 9995 FORMAT( ' Error in DTRSYL: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
227 $ 'INFO=', i8, ' KNT=', i8 )
228 9994 FORMAT( ' Error in DTREXC: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
229 $ 'INFO=', 3i8, ' KNT=', i8 )
230 9993 FORMAT( ' Error in DTRSNA: RMAX =', 3d12.3, / ' LMAX = ', 3i8,
231 $ ' NINFO=', 3i8, ' KNT=', i8 )
232 9992 FORMAT( ' Error in DTRSEN: RMAX =', 3d12.3, / ' LMAX = ', 3i8,
233 $ ' NINFO=', 3i8, ' KNT=', i8 )
234 9991 FORMAT( ' Error in DLAQTR: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
235 $ 'INFO=', i8, ' KNT=', i8 )
236 9990 FORMAT( / 1x, 'All tests for ', a3, ' routines passed the thresh',
237 $ 'old ( ', i6, ' tests run)' )
238 9989 FORMAT( ' Tests of the Nonsymmetric eigenproblem condition estim',
239 $ 'ation routines', / ' DLALN2, DLASY2, DLANV2, DLAEXC, DTRS',
240 $ 'YL, DTREXC, DTRSNA, DTRSEN, DLAQTR, DTGEXC', / )
241 9988 FORMAT( ' Relative machine precision (EPS) = ', d16.6, / ' Safe ',
242 $ 'minimum (SFMIN) = ', d16.6, / )
243 9987 FORMAT( ' Routines pass computational tests if test ratio is les',
244 $ 's than', f8.2, / / )
245 9986 FORMAT( ' Error in DTGEXC: RMAX =', d12.3, / ' LMAX = ', i8, ' N',
246 $ 'INFO=', 2i8, ' KNT=', i8 )
247 9972 FORMAT( 'DTRSYL and DTRSYL3 compute an inconsistent result ',
248 $ 'factor in ', i8, ' tests.')
249 9971 FORMAT( 'Error in DTRSYL3: ', i8, ' tests fail the threshold.', /
250 $ 'Maximum test ratio =', d12.3, ' threshold =', d12.3 )
251 9970 FORMAT( 'Error in DTRSYL: ', i8, ' tests fail the threshold.', /
252 $ 'Maximum test ratio =', d12.3, ' threshold =', d12.3 )
253*
254* End of DCHKEC
255*
256 END
subroutine dchkec(thresh, tsterr, nin, nout)
DCHKEC
Definition dchkec.f:76
subroutine derrec(path, nunit)
DERREC
Definition derrec.f:56
subroutine dget31(rmax, lmax, ninfo, knt)
DGET31
Definition dget31.f:91
subroutine dget32(rmax, lmax, ninfo, knt)
DGET32
Definition dget32.f:82
subroutine dget33(rmax, lmax, ninfo, knt)
DGET33
Definition dget33.f:76
subroutine dget34(rmax, lmax, ninfo, knt)
DGET34
Definition dget34.f:82
subroutine dget35(rmax, lmax, ninfo, knt)
DGET35
Definition dget35.f:78
subroutine dget36(rmax, lmax, ninfo, knt, nin)
DGET36
Definition dget36.f:88
subroutine dget37(rmax, lmax, ninfo, knt, nin)
DGET37
Definition dget37.f:90
subroutine dget38(rmax, lmax, ninfo, knt, nin)
DGET38
Definition dget38.f:91
subroutine dget39(rmax, lmax, ninfo, knt)
DGET39
Definition dget39.f:103
subroutine dget40(rmax, lmax, ninfo, knt, nin)
DGET40
Definition dget40.f:85
subroutine dsyl01(thresh, nfail, rmax, ninfo, knt)
DSYL01
Definition dsyl01.f:89