LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
derrvxx.f
Go to the documentation of this file.
1*> \brief \b DERRVXX
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 DERRVX( PATH, NUNIT )
12*
13* .. Scalar Arguments ..
14* CHARACTER*3 PATH
15* INTEGER NUNIT
16* ..
17*
18*
19*> \par Purpose:
20* =============
21*>
22*> \verbatim
23*>
24*> DERRVX tests the error exits for the DOUBLE PRECISION driver routines
25*> for solving linear systems of equations.
26*> \endverbatim
27*
28* Arguments:
29* ==========
30*
31*> \param[in] PATH
32*> \verbatim
33*> PATH is CHARACTER*3
34*> The LAPACK path name for the routines to be tested.
35*> \endverbatim
36*>
37*> \param[in] NUNIT
38*> \verbatim
39*> NUNIT is INTEGER
40*> The unit number for output.
41*> \endverbatim
42*
43* Authors:
44* ========
45*
46*> \author Univ. of Tennessee
47*> \author Univ. of California Berkeley
48*> \author Univ. of Colorado Denver
49*> \author NAG Ltd.
50*
51*> \ingroup double_lin
52*
53* =====================================================================
54 SUBROUTINE derrvx( PATH, NUNIT )
55*
56* -- LAPACK test routine --
57* -- LAPACK is a software package provided by Univ. of Tennessee, --
58* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
59*
60* .. Scalar Arguments ..
61 CHARACTER*3 PATH
62 INTEGER NUNIT
63* ..
64*
65* =====================================================================
66*
67* .. Parameters ..
68 INTEGER NMAX
69 parameter( nmax = 4 )
70 REAL ONE
71 parameter( one = 1.0d+0 )
72* ..
73* .. Local Scalars ..
74 CHARACTER EQ
75 CHARACTER*2 C2
76 INTEGER I, INFO, J, N_ERR_BNDS, NPARAMS
77 DOUBLE PRECISION RCOND, RPVGRW, BERR
78* ..
79* .. Local Arrays ..
80 INTEGER IP( NMAX ), IW( NMAX )
81 DOUBLE PRECISION A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
82 $ C( NMAX ), E( NMAX ), R( NMAX ), R1( NMAX ),
83 $ R2( NMAX ), W( 2*NMAX ), X( NMAX ),
84 $ ERR_BNDS_N( NMAX, 3 ), ERR_BNDS_C( NMAX, 3 ),
85 $ PARAMS( 1 )
86* ..
87* .. External Functions ..
88 LOGICAL LSAMEN
89 EXTERNAL lsamen
90* ..
91* .. External Subroutines ..
92 EXTERNAL chkxer, dgbsv, dgbsvx, dgesv, dgesvx, dgtsv,
97* ..
98* .. Scalars in Common ..
99 LOGICAL LERR, OK
100 CHARACTER*32 SRNAMT
101 INTEGER INFOT, NOUT
102* ..
103* .. Common blocks ..
104 COMMON / infoc / infot, nout, ok, lerr
105 COMMON / srnamc / srnamt
106* ..
107* .. Intrinsic Functions ..
108 INTRINSIC dble
109* ..
110* .. Executable Statements ..
111*
112 nout = nunit
113 WRITE( nout, fmt = * )
114 c2 = path( 2: 3 )
115*
116* Set the variables to innocuous values.
117*
118 DO 20 j = 1, nmax
119 DO 10 i = 1, nmax
120 a( i, j ) = 1.d0 / dble( i+j )
121 af( i, j ) = 1.d0 / dble( i+j )
122 10 CONTINUE
123 b( j ) = 0.d+0
124 e( j ) = 0.d+0
125 r1( j ) = 0.d+0
126 r2( j ) = 0.d+0
127 w( j ) = 0.d+0
128 x( j ) = 0.d+0
129 c( j ) = 0.d+0
130 r( j ) = 0.d+0
131 ip( j ) = j
132 20 CONTINUE
133 eq = ' '
134 ok = .true.
135*
136 IF( lsamen( 2, c2, 'GE' ) ) THEN
137*
138* DGESV
139*
140 srnamt = 'DGESV '
141 infot = 1
142 CALL dgesv( -1, 0, a, 1, ip, b, 1, info )
143 CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
144 infot = 2
145 CALL dgesv( 0, -1, a, 1, ip, b, 1, info )
146 CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
147 infot = 4
148 CALL dgesv( 2, 1, a, 1, ip, b, 2, info )
149 CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
150 infot = 7
151 CALL dgesv( 2, 1, a, 2, ip, b, 1, info )
152 CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
153*
154* DGESVX
155*
156 srnamt = 'DGESVX'
157 infot = 1
158 CALL dgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
159 $ x, 1, rcond, r1, r2, w, iw, info )
160 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
161 infot = 2
162 CALL dgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
163 $ x, 1, rcond, r1, r2, w, iw, info )
164 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
165 infot = 3
166 CALL dgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
167 $ x, 1, rcond, r1, r2, w, iw, info )
168 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
169 infot = 4
170 CALL dgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
171 $ x, 1, rcond, r1, r2, w, iw, info )
172 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
173 infot = 6
174 CALL dgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
175 $ x, 2, rcond, r1, r2, w, iw, info )
176 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
177 infot = 8
178 CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
179 $ x, 2, rcond, r1, r2, w, iw, info )
180 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
181 infot = 10
182 eq = '/'
183 CALL dgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
184 $ x, 1, rcond, r1, r2, w, iw, info )
185 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
186 infot = 11
187 eq = 'R'
188 CALL dgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
189 $ x, 1, rcond, r1, r2, w, iw, info )
190 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
191 infot = 12
192 eq = 'C'
193 CALL dgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
194 $ x, 1, rcond, r1, r2, w, iw, info )
195 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
196 infot = 14
197 CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
198 $ x, 2, rcond, r1, r2, w, iw, info )
199 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
200 infot = 16
201 CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
202 $ x, 1, rcond, r1, r2, w, iw, info )
203 CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
204*
205* DGESVXX
206*
207 n_err_bnds = 3
208 nparams = 1
209 srnamt = 'DGESVXX'
210 infot = 1
211 CALL dgesvxx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
212 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
213 $ err_bnds_c, nparams, params, w, iw, info )
214 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
215 infot = 2
216 CALL dgesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
217 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
218 $ err_bnds_c, nparams, params, w, iw, info )
219 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
220 infot = 3
221 CALL dgesvxx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
222 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
223 $ err_bnds_c, nparams, params, w, iw, info )
224 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
225 infot = 4
226 CALL dgesvxx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
227 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
228 $ err_bnds_c, nparams, params, w, iw, info )
229 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
230 infot = 6
231 CALL dgesvxx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
232 $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
233 $ err_bnds_c, nparams, params, w, iw, info )
234 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
235 infot = 8
236 CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
237 $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
238 $ err_bnds_c, nparams, params, w, iw, info )
239 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
240 infot = 10
241 eq = '/'
242 CALL dgesvxx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
243 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
244 $ err_bnds_c, nparams, params, w, iw, info )
245 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
246 infot = 11
247 eq = 'R'
248 CALL dgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
249 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
250 $ err_bnds_c, nparams, params, w, iw, info )
251 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
252 infot = 12
253 eq = 'C'
254 CALL dgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
255 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
256 $ err_bnds_c, nparams, params, w, iw, info )
257 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
258 infot = 14
259 CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
260 $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
261 $ err_bnds_c, nparams, params, w, iw, info )
262 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
263 infot = 16
264 CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
265 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
266 $ err_bnds_c, nparams, params, w, iw, info )
267 CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
268*
269 ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
270*
271* DGBSV
272*
273 srnamt = 'DGBSV '
274 infot = 1
275 CALL dgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
276 CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
277 infot = 2
278 CALL dgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
279 CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
280 infot = 3
281 CALL dgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
282 CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
283 infot = 4
284 CALL dgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
285 CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
286 infot = 6
287 CALL dgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
288 CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
289 infot = 9
290 CALL dgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
291 CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
292*
293* DGBSVX
294*
295 srnamt = 'DGBSVX'
296 infot = 1
297 CALL dgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
298 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
299 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
300 infot = 2
301 CALL dgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
302 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
303 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
304 infot = 3
305 CALL dgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
306 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
307 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
308 infot = 4
309 CALL dgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
310 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
311 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
312 infot = 5
313 CALL dgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
314 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
315 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
316 infot = 6
317 CALL dgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
318 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
319 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
320 infot = 8
321 CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
322 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
323 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
324 infot = 10
325 CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
326 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
327 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
328 infot = 12
329 eq = '/'
330 CALL dgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
331 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
332 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
333 infot = 13
334 eq = 'R'
335 CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
336 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
337 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
338 infot = 14
339 eq = 'C'
340 CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
341 $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
342 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
343 infot = 16
344 CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
345 $ b, 1, x, 2, rcond, r1, r2, w, iw, info )
346 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
347 infot = 18
348 CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
349 $ b, 2, x, 1, rcond, r1, r2, w, iw, info )
350 CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
351*
352* DGBSVXX
353*
354 n_err_bnds = 3
355 nparams = 1
356 srnamt = 'DGBSVXX'
357 infot = 1
358 CALL dgbsvxx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
359 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
360 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
361 $ info )
362 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
363 infot = 2
364 CALL dgbsvxx( 'N', '/', 0, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
365 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
366 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
367 $ info )
368 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
369 infot = 3
370 CALL dgbsvxx( 'N', 'N', -1, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
371 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
372 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
373 $ info )
374 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
375 infot = 4
376 CALL dgbsvxx( 'N', 'N', 2, -1, 1, 0, a, 1, af, 1, ip, eq,
377 $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
378 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
379 $ info )
380 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
381 infot = 5
382 CALL dgbsvxx( 'N', 'N', 2, 1, -1, 0, a, 1, af, 1, ip, eq,
383 $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
384 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
385 $ info )
386 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
387 infot = 6
388 CALL dgbsvxx( 'N', 'N', 0, 1, 1, -1, a, 1, af, 1, ip, eq, r, c,
389 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
390 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
391 $ info )
392 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
393 infot = 8
394 CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 2, af, 2, ip, eq, r, c,
395 $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
396 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
397 $ info )
398 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
399 infot = 10
400 CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 3, ip, eq, r, c,
401 $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
402 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
403 $ info )
404 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
405 infot = 12
406 eq = '/'
407 CALL dgbsvxx( 'F', 'N', 0, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
408 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
409 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
410 $ info )
411 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
412 infot = 13
413 eq = 'R'
414 CALL dgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
415 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
416 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
417 $ info )
418 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
419 infot = 14
420 eq = 'C'
421 CALL dgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
422 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
423 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
424 $ info )
425 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
426 infot = 15
427 CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
428 $ b, 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
429 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
430 $ info )
431 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
432 infot = 16
433 CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
434 $ b, 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
435 $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
436 $ info )
437 CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
438*
439 ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
440*
441* DGTSV
442*
443 srnamt = 'DGTSV '
444 infot = 1
445 CALL dgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
446 $ info )
447 CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
448 infot = 2
449 CALL dgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
450 $ info )
451 CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
452 infot = 7
453 CALL dgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
454 CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
455*
456* DGTSVX
457*
458 srnamt = 'DGTSVX'
459 infot = 1
460 CALL dgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
461 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
462 $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
463 CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
464 infot = 2
465 CALL dgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
466 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
467 $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
468 CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
469 infot = 3
470 CALL dgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
471 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
472 $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
473 CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
474 infot = 4
475 CALL dgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
476 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
477 $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
478 CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
479 infot = 14
480 CALL dgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
481 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
482 $ ip, b, 1, x, 2, rcond, r1, r2, w, iw, info )
483 CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
484 infot = 16
485 CALL dgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
486 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
487 $ ip, b, 2, x, 1, rcond, r1, r2, w, iw, info )
488 CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
489*
490 ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
491*
492* DPOSV
493*
494 srnamt = 'DPOSV '
495 infot = 1
496 CALL dposv( '/', 0, 0, a, 1, b, 1, info )
497 CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
498 infot = 2
499 CALL dposv( 'U', -1, 0, a, 1, b, 1, info )
500 CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
501 infot = 3
502 CALL dposv( 'U', 0, -1, a, 1, b, 1, info )
503 CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
504 infot = 5
505 CALL dposv( 'U', 2, 0, a, 1, b, 2, info )
506 CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
507 infot = 7
508 CALL dposv( 'U', 2, 0, a, 2, b, 1, info )
509 CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
510*
511* DPOSVX
512*
513 srnamt = 'DPOSVX'
514 infot = 1
515 CALL dposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
516 $ rcond, r1, r2, w, iw, info )
517 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
518 infot = 2
519 CALL dposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
520 $ rcond, r1, r2, w, iw, info )
521 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
522 infot = 3
523 CALL dposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
524 $ rcond, r1, r2, w, iw, info )
525 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
526 infot = 4
527 CALL dposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
528 $ rcond, r1, r2, w, iw, info )
529 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
530 infot = 6
531 CALL dposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
532 $ rcond, r1, r2, w, iw, info )
533 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
534 infot = 8
535 CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
536 $ rcond, r1, r2, w, iw, info )
537 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
538 infot = 9
539 eq = '/'
540 CALL dposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
541 $ rcond, r1, r2, w, iw, info )
542 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
543 infot = 10
544 eq = 'Y'
545 CALL dposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
546 $ rcond, r1, r2, w, iw, info )
547 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
548 infot = 12
549 CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
550 $ rcond, r1, r2, w, iw, info )
551 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
552 infot = 14
553 CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
554 $ rcond, r1, r2, w, iw, info )
555 CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
556*
557* DPOSVXX
558*
559 n_err_bnds = 3
560 nparams = 1
561 srnamt = 'DPOSVXX'
562 infot = 1
563 CALL dposvxx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
564 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
565 $ err_bnds_c, nparams, params, w, iw, info )
566 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
567 infot = 2
568 CALL dposvxx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
569 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
570 $ err_bnds_c, nparams, params, w, iw, info )
571 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
572 infot = 3
573 CALL dposvxx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
574 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
575 $ err_bnds_c, nparams, params, w, iw, info )
576 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
577 infot = 4
578 CALL dposvxx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
579 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
580 $ err_bnds_c, nparams, params, w, iw, info )
581 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
582 infot = 6
583 CALL dposvxx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
584 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
585 $ err_bnds_c, nparams, params, w, iw, info )
586 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
587 infot = 8
588 CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
589 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
590 $ err_bnds_c, nparams, params, w, iw, info )
591 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
592 infot = 9
593 eq = '/'
594 CALL dposvxx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
595 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
596 $ err_bnds_c, nparams, params, w, iw, info )
597 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
598 infot = 10
599 eq = 'Y'
600 CALL dposvxx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
601 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
602 $ err_bnds_c, nparams, params, w, iw, info )
603 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
604 infot = 12
605 CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
606 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
607 $ err_bnds_c, nparams, params, w, iw, info )
608 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
609 infot = 14
610 CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
611 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
612 $ err_bnds_c, nparams, params, w, iw, info )
613 CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
614*
615 ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
616*
617* DPPSV
618*
619 srnamt = 'DPPSV '
620 infot = 1
621 CALL dppsv( '/', 0, 0, a, b, 1, info )
622 CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
623 infot = 2
624 CALL dppsv( 'U', -1, 0, a, b, 1, info )
625 CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
626 infot = 3
627 CALL dppsv( 'U', 0, -1, a, b, 1, info )
628 CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
629 infot = 6
630 CALL dppsv( 'U', 2, 0, a, b, 1, info )
631 CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
632*
633* DPPSVX
634*
635 srnamt = 'DPPSVX'
636 infot = 1
637 CALL dppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
638 $ r1, r2, w, iw, info )
639 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
640 infot = 2
641 CALL dppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
642 $ r1, r2, w, iw, info )
643 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
644 infot = 3
645 CALL dppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
646 $ r1, r2, w, iw, info )
647 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
648 infot = 4
649 CALL dppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
650 $ r1, r2, w, iw, info )
651 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
652 infot = 7
653 eq = '/'
654 CALL dppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
655 $ r1, r2, w, iw, info )
656 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
657 infot = 8
658 eq = 'Y'
659 CALL dppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
660 $ r1, r2, w, iw, info )
661 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
662 infot = 10
663 CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
664 $ r1, r2, w, iw, info )
665 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
666 infot = 12
667 CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
668 $ r1, r2, w, iw, info )
669 CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
670*
671 ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
672*
673* DPBSV
674*
675 srnamt = 'DPBSV '
676 infot = 1
677 CALL dpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
678 CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
679 infot = 2
680 CALL dpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
681 CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
682 infot = 3
683 CALL dpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
684 CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
685 infot = 4
686 CALL dpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
687 CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
688 infot = 6
689 CALL dpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
690 CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
691 infot = 8
692 CALL dpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
693 CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
694*
695* DPBSVX
696*
697 srnamt = 'DPBSVX'
698 infot = 1
699 CALL dpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
700 $ rcond, r1, r2, w, iw, info )
701 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
702 infot = 2
703 CALL dpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
704 $ rcond, r1, r2, w, iw, info )
705 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
706 infot = 3
707 CALL dpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
708 $ 1, rcond, r1, r2, w, iw, info )
709 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
710 infot = 4
711 CALL dpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
712 $ 1, rcond, r1, r2, w, iw, info )
713 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
714 infot = 5
715 CALL dpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
716 $ 1, rcond, r1, r2, w, iw, info )
717 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
718 infot = 7
719 CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
720 $ rcond, r1, r2, w, iw, info )
721 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
722 infot = 9
723 CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
724 $ rcond, r1, r2, w, iw, info )
725 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
726 infot = 10
727 eq = '/'
728 CALL dpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
729 $ rcond, r1, r2, w, iw, info )
730 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
731 infot = 11
732 eq = 'Y'
733 CALL dpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
734 $ rcond, r1, r2, w, iw, info )
735 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
736 infot = 13
737 CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
738 $ rcond, r1, r2, w, iw, info )
739 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
740 infot = 15
741 CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
742 $ rcond, r1, r2, w, iw, info )
743 CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
744*
745 ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
746*
747* DPTSV
748*
749 srnamt = 'DPTSV '
750 infot = 1
751 CALL dptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
752 CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
753 infot = 2
754 CALL dptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
755 CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
756 infot = 6
757 CALL dptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
758 CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
759*
760* DPTSVX
761*
762 srnamt = 'DPTSVX'
763 infot = 1
764 CALL dptsvx( '/', 0, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
765 $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
766 CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
767 infot = 2
768 CALL dptsvx( 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
769 $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
770 CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
771 infot = 3
772 CALL dptsvx( 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
773 $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
774 CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
775 infot = 9
776 CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
777 $ af( 1, 2 ), b, 1, x, 2, rcond, r1, r2, w, info )
778 CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
779 infot = 11
780 CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
781 $ af( 1, 2 ), b, 2, x, 1, rcond, r1, r2, w, info )
782 CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
783*
784 ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
785*
786* DSYSV
787*
788 srnamt = 'DSYSV '
789 infot = 1
790 CALL dsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
791 CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
792 infot = 2
793 CALL dsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
794 CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
795 infot = 3
796 CALL dsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
797 CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
798 infot = 5
799 CALL dsysv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
800 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
801 infot = 8
802 CALL dsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
803 CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
804 infot = 10
805 CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
806 CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
807 infot = 10
808 CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
809 CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
810*
811* DSYSVX
812*
813 srnamt = 'DSYSVX'
814 infot = 1
815 CALL dsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
816 $ rcond, r1, r2, w, 1, iw, info )
817 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
818 infot = 2
819 CALL dsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
820 $ rcond, r1, r2, w, 1, iw, info )
821 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
822 infot = 3
823 CALL dsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
824 $ rcond, r1, r2, w, 1, iw, info )
825 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
826 infot = 4
827 CALL dsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
828 $ rcond, r1, r2, w, 1, iw, info )
829 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
830 infot = 6
831 CALL dsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
832 $ rcond, r1, r2, w, 4, iw, info )
833 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
834 infot = 8
835 CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
836 $ rcond, r1, r2, w, 4, iw, info )
837 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
838 infot = 11
839 CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
840 $ rcond, r1, r2, w, 4, iw, info )
841 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
842 infot = 13
843 CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
844 $ rcond, r1, r2, w, 4, iw, info )
845 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
846 infot = 18
847 CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
848 $ rcond, r1, r2, w, 3, iw, info )
849 CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
850*
851* DSYSVXX
852*
853 n_err_bnds = 3
854 nparams = 1
855 srnamt = 'DSYSVXX'
856 infot = 1
857 eq = 'N'
858 CALL dsysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
859 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
860 $ err_bnds_c, nparams, params, w, iw, info )
861 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
862 infot = 2
863 CALL dsysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
864 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
865 $ err_bnds_c, nparams, params, w, iw, info )
866 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
867 infot = 3
868 CALL dsysvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
869 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
870 $ err_bnds_c, nparams, params, w, iw, info )
871 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
872 infot = 4
873 eq = '/'
874 CALL dsysvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, r, b, 1, x,
875 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
876 $ err_bnds_c, nparams, params, w, iw, info )
877 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
878 eq = 'Y'
879 infot = 6
880 CALL dsysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
881 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
882 $ err_bnds_c, nparams, params, w, iw, info )
883 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
884 infot = 8
885 CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
886 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
887 $ err_bnds_c, nparams, params, w, iw, info )
888 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
889 infot = 10
890 CALL dsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, 'A', r, b, 2, x,
891 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
892 $ err_bnds_c, nparams, params, w, iw, info )
893 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
894 infot = 11
895 eq='Y'
896 CALL dsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
897 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
898 $ err_bnds_c, nparams, params, w, iw, info )
899 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
900 infot = 11
901 eq='Y'
902 r(1) = -one
903 CALL dsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
904 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
905 $ err_bnds_c, nparams, params, w, iw, info )
906 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
907 infot = 13
908 eq = 'N'
909 CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, x,
910 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
911 $ err_bnds_c, nparams, params, w, iw, info )
912 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
913 infot = 15
914 CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
915 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
916 $ err_bnds_c, nparams, params, w, iw, info )
917 CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
918*
919 ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
920*
921* DSYSV_ROOK
922*
923 srnamt = 'DSYSV_ROOK'
924 infot = 1
925 CALL dsysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
926 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
927 infot = 2
928 CALL dsysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
929 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
930 infot = 3
931 CALL dsysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
932 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
933 infot = 5
934 CALL dsysv_rook( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
935 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
936 infot = 8
937 CALL dsysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
938 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
939 infot = 10
940 CALL dsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
941 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
942 infot = 10
943 CALL dsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
944 CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
945*
946 ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
947*
948* DSYSV_RK
949*
950* Test error exits of the driver that uses factorization
951* of a symmetric indefinite matrix with rook
952* (bounded Bunch-Kaufman) pivoting with the new storage
953* format for factors L ( or U) and D.
954*
955* L (or U) is stored in A, diagonal of D is stored on the
956* diagonal of A, subdiagonal of D is stored in a separate array E.
957*
958 srnamt = 'DSYSV_RK'
959 infot = 1
960 CALL dsysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
961 CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
962 infot = 2
963 CALL dsysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
964 CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
965 infot = 3
966 CALL dsysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
967 CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
968 infot = 5
969 CALL dsysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
970 CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
971 infot = 9
972 CALL dsysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
973 CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
974 infot = 11
975 CALL dsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
976 CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
977 infot = 11
978 CALL dsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
979 CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
980*
981 ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
982*
983* DSPSV
984*
985 srnamt = 'DSPSV '
986 infot = 1
987 CALL dspsv( '/', 0, 0, a, ip, b, 1, info )
988 CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
989 infot = 2
990 CALL dspsv( 'U', -1, 0, a, ip, b, 1, info )
991 CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
992 infot = 3
993 CALL dspsv( 'U', 0, -1, a, ip, b, 1, info )
994 CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
995 infot = 7
996 CALL dspsv( 'U', 2, 0, a, ip, b, 1, info )
997 CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
998*
999* DSPSVX
1000*
1001 srnamt = 'DSPSVX'
1002 infot = 1
1003 CALL dspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1004 $ r2, w, iw, info )
1005 CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1006 infot = 2
1007 CALL dspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1008 $ r2, w, iw, info )
1009 CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1010 infot = 3
1011 CALL dspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1012 $ r2, w, iw, info )
1013 CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1014 infot = 4
1015 CALL dspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1016 $ r2, w, iw, info )
1017 CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1018 infot = 9
1019 CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1020 $ r2, w, iw, info )
1021 CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1022 infot = 11
1023 CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1024 $ r2, w, iw, info )
1025 CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1026 END IF
1027*
1028* Print a summary line.
1029*
1030 IF( ok ) THEN
1031 WRITE( nout, fmt = 9999 )path
1032 ELSE
1033 WRITE( nout, fmt = 9998 )path
1034 END IF
1035*
1036 9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
1037 9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
1038 $ 'exits ***' )
1039*
1040 RETURN
1041*
1042* End of DERRVXX
1043*
1044 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine derrvx(path, nunit)
DERRVX
Definition derrvx.f:55
subroutine dgbsv(n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)
DGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver)
Definition dgbsv.f:162
subroutine dgbsvx(fact, trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DGBSVX computes the solution to system of linear equations A * X = B for GB matrices
Definition dgbsvx.f:369
subroutine dgbsvxx(fact, trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, equed, r, c, b, ldb, x, ldx, rcond, rpvgrw, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
DGBSVXX computes the solution to system of linear equations A * X = B for GB matrices
Definition dgbsvxx.f:560
subroutine dgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
Download DGESV + dependencies <a href="http://www.netlib.org/cgi-bin/netlibfiles....
Definition dgesv.f:124
subroutine dgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DGESVX computes the solution to system of linear equations A * X = B for GE matrices
Definition dgesvx.f:349
subroutine dgesvxx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, rpvgrw, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
DGESVXX computes the solution to system of linear equations A * X = B for GE matrices
Definition dgesvxx.f:540
subroutine dgtsv(n, nrhs, dl, d, du, b, ldb, info)
DGTSV computes the solution to system of linear equations A * X = B for GT matrices
Definition dgtsv.f:127
subroutine dgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DGTSVX computes the solution to system of linear equations A * X = B for GT matrices
Definition dgtsvx.f:293
subroutine dsysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)
DSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices
Definition dsysv_rk.f:228
subroutine dsysv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
DSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices
Definition dsysv_rook.f:204
subroutine dsysv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
DSYSV computes the solution to system of linear equations A * X = B for SY matrices
Definition dsysv.f:171
subroutine dsysvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, iwork, info)
DSYSVX computes the solution to system of linear equations A * X = B for SY matrices
Definition dsysvx.f:284
subroutine dsysvxx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, equed, s, b, ldb, x, ldx, rcond, rpvgrw, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
DSYSVXX
Definition dsysvxx.f:505
subroutine dspsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)
DSPSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition dspsv.f:162
subroutine dspsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition dspsvx.f:276
subroutine dpbsv(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
DPBSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition dpbsv.f:164
subroutine dpbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition dpbsvx.f:343
subroutine dposv(uplo, n, nrhs, a, lda, b, ldb, info)
DPOSV computes the solution to system of linear equations A * X = B for PO matrices
Definition dposv.f:130
subroutine dposvx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DPOSVX computes the solution to system of linear equations A * X = B for PO matrices
Definition dposvx.f:307
subroutine dposvxx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, rpvgrw, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
DPOSVXX computes the solution to system of linear equations A * X = B for PO matrices
Definition dposvxx.f:494
subroutine dppsv(uplo, n, nrhs, ap, b, ldb, info)
DPPSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition dppsv.f:144
subroutine dppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition dppsvx.f:311
subroutine dptsv(n, nrhs, d, e, b, ldb, info)
DPTSV computes the solution to system of linear equations A * X = B for PT matrices
Definition dptsv.f:114
subroutine dptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, info)
DPTSVX computes the solution to system of linear equations A * X = B for PT matrices
Definition dptsvx.f:228