LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
derrvx.f
Go to the documentation of this file.
1 *> \brief \b DERRVX
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 *> \date December 2016
52 *
53 *> \ingroup double_lin
54 *
55 * =====================================================================
56  SUBROUTINE derrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.7.0) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * December 2016
62 *
63 * .. Scalar Arguments ..
64  CHARACTER*3 PATH
65  INTEGER NUNIT
66 * ..
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71  INTEGER NMAX
72  parameter ( nmax = 4 )
73 * ..
74 * .. Local Scalars ..
75  CHARACTER EQ
76  CHARACTER*2 C2
77  INTEGER I, INFO, J
78  DOUBLE PRECISION RCOND
79 * ..
80 * .. Local Arrays ..
81  INTEGER IP( nmax ), IW( nmax )
82  DOUBLE PRECISION A( nmax, nmax ), AF( nmax, nmax ), B( nmax ),
83  $ c( nmax ), e( nmax ), r( nmax ), r1( nmax ),
84  $ r2( nmax ), w( 2*nmax ), x( nmax )
85 * ..
86 * .. External Functions ..
87  LOGICAL LSAMEN
88  EXTERNAL lsamen
89 * ..
90 * .. External Subroutines ..
91  EXTERNAL chkxer, dgbsv, dgbsvx, dgesv, dgesvx, dgtsv,
95 * ..
96 * .. Scalars in Common ..
97  LOGICAL LERR, OK
98  CHARACTER*32 SRNAMT
99  INTEGER INFOT, NOUT
100 * ..
101 * .. Common blocks ..
102  COMMON / infoc / infot, nout, ok, lerr
103  COMMON / srnamc / srnamt
104 * ..
105 * .. Intrinsic Functions ..
106  INTRINSIC dble
107 * ..
108 * .. Executable Statements ..
109 *
110  nout = nunit
111  WRITE( nout, fmt = * )
112  c2 = path( 2: 3 )
113 *
114 * Set the variables to innocuous values.
115 *
116  DO 20 j = 1, nmax
117  DO 10 i = 1, nmax
118  a( i, j ) = 1.d0 / dble( i+j )
119  af( i, j ) = 1.d0 / dble( i+j )
120  10 CONTINUE
121  b( j ) = 0.d+0
122  e( j ) = 0.d+0
123  r1( j ) = 0.d+0
124  r2( j ) = 0.d+0
125  w( j ) = 0.d+0
126  x( j ) = 0.d+0
127  c( j ) = 0.d+0
128  r( j ) = 0.d+0
129  ip( j ) = j
130  20 CONTINUE
131  eq = ' '
132  ok = .true.
133 *
134  IF( lsamen( 2, c2, 'GE' ) ) THEN
135 *
136 * DGESV
137 *
138  srnamt = 'DGESV '
139  infot = 1
140  CALL dgesv( -1, 0, a, 1, ip, b, 1, info )
141  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
142  infot = 2
143  CALL dgesv( 0, -1, a, 1, ip, b, 1, info )
144  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
145  infot = 4
146  CALL dgesv( 2, 1, a, 1, ip, b, 2, info )
147  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
148  infot = 7
149  CALL dgesv( 2, 1, a, 2, ip, b, 1, info )
150  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
151 *
152 * DGESVX
153 *
154  srnamt = 'DGESVX'
155  infot = 1
156  CALL dgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
157  $ x, 1, rcond, r1, r2, w, iw, info )
158  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
159  infot = 2
160  CALL dgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
161  $ x, 1, rcond, r1, r2, w, iw, info )
162  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
163  infot = 3
164  CALL dgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
165  $ x, 1, rcond, r1, r2, w, iw, info )
166  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
167  infot = 4
168  CALL dgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
169  $ x, 1, rcond, r1, r2, w, iw, info )
170  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
171  infot = 6
172  CALL dgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
173  $ x, 2, rcond, r1, r2, w, iw, info )
174  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
175  infot = 8
176  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
177  $ x, 2, rcond, r1, r2, w, iw, info )
178  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
179  infot = 10
180  eq = '/'
181  CALL dgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
182  $ x, 1, rcond, r1, r2, w, iw, info )
183  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
184  infot = 11
185  eq = 'R'
186  CALL dgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
187  $ x, 1, rcond, r1, r2, w, iw, info )
188  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
189  infot = 12
190  eq = 'C'
191  CALL dgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
192  $ x, 1, rcond, r1, r2, w, iw, info )
193  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
194  infot = 14
195  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
196  $ x, 2, rcond, r1, r2, w, iw, info )
197  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
198  infot = 16
199  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
200  $ x, 1, rcond, r1, r2, w, iw, info )
201  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
202 *
203  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
204 *
205 * DGBSV
206 *
207  srnamt = 'DGBSV '
208  infot = 1
209  CALL dgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
210  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
211  infot = 2
212  CALL dgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
213  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
214  infot = 3
215  CALL dgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
216  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
217  infot = 4
218  CALL dgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
219  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
220  infot = 6
221  CALL dgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
222  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
223  infot = 9
224  CALL dgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
225  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
226 *
227 * DGBSVX
228 *
229  srnamt = 'DGBSVX'
230  infot = 1
231  CALL dgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
232  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
233  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
234  infot = 2
235  CALL dgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
236  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
237  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
238  infot = 3
239  CALL dgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
240  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
241  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
242  infot = 4
243  CALL dgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
244  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
245  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
246  infot = 5
247  CALL dgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
248  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
249  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
250  infot = 6
251  CALL dgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
252  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
253  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
254  infot = 8
255  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
256  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
257  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
258  infot = 10
259  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
260  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
261  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
262  infot = 12
263  eq = '/'
264  CALL dgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
265  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
266  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
267  infot = 13
268  eq = 'R'
269  CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
270  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
271  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
272  infot = 14
273  eq = 'C'
274  CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
275  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
276  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
277  infot = 16
278  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
279  $ b, 1, x, 2, rcond, r1, r2, w, iw, info )
280  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
281  infot = 18
282  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
283  $ b, 2, x, 1, rcond, r1, r2, w, iw, info )
284  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
285 *
286  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
287 *
288 * DGTSV
289 *
290  srnamt = 'DGTSV '
291  infot = 1
292  CALL dgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
293  $ info )
294  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
295  infot = 2
296  CALL dgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
297  $ info )
298  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
299  infot = 7
300  CALL dgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
301  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
302 *
303 * DGTSVX
304 *
305  srnamt = 'DGTSVX'
306  infot = 1
307  CALL dgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
308  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
309  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
310  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
311  infot = 2
312  CALL dgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
313  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
314  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
315  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
316  infot = 3
317  CALL dgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
318  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
319  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
320  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
321  infot = 4
322  CALL dgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
323  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
324  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
325  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
326  infot = 14
327  CALL dgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
328  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
329  $ ip, b, 1, x, 2, rcond, r1, r2, w, iw, info )
330  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
331  infot = 16
332  CALL dgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
333  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
334  $ ip, b, 2, x, 1, rcond, r1, r2, w, iw, info )
335  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
336 *
337  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
338 *
339 * DPOSV
340 *
341  srnamt = 'DPOSV '
342  infot = 1
343  CALL dposv( '/', 0, 0, a, 1, b, 1, info )
344  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
345  infot = 2
346  CALL dposv( 'U', -1, 0, a, 1, b, 1, info )
347  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
348  infot = 3
349  CALL dposv( 'U', 0, -1, a, 1, b, 1, info )
350  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
351  infot = 5
352  CALL dposv( 'U', 2, 0, a, 1, b, 2, info )
353  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
354  infot = 7
355  CALL dposv( 'U', 2, 0, a, 2, b, 1, info )
356  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
357 *
358 * DPOSVX
359 *
360  srnamt = 'DPOSVX'
361  infot = 1
362  CALL dposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
363  $ rcond, r1, r2, w, iw, info )
364  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
365  infot = 2
366  CALL dposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
367  $ rcond, r1, r2, w, iw, info )
368  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
369  infot = 3
370  CALL dposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
371  $ rcond, r1, r2, w, iw, info )
372  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
373  infot = 4
374  CALL dposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
375  $ rcond, r1, r2, w, iw, info )
376  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
377  infot = 6
378  CALL dposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
379  $ rcond, r1, r2, w, iw, info )
380  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
381  infot = 8
382  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
383  $ rcond, r1, r2, w, iw, info )
384  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
385  infot = 9
386  eq = '/'
387  CALL dposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
388  $ rcond, r1, r2, w, iw, info )
389  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
390  infot = 10
391  eq = 'Y'
392  CALL dposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
393  $ rcond, r1, r2, w, iw, info )
394  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
395  infot = 12
396  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
397  $ rcond, r1, r2, w, iw, info )
398  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
399  infot = 14
400  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
401  $ rcond, r1, r2, w, iw, info )
402  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
403 *
404  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
405 *
406 * DPPSV
407 *
408  srnamt = 'DPPSV '
409  infot = 1
410  CALL dppsv( '/', 0, 0, a, b, 1, info )
411  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
412  infot = 2
413  CALL dppsv( 'U', -1, 0, a, b, 1, info )
414  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
415  infot = 3
416  CALL dppsv( 'U', 0, -1, a, b, 1, info )
417  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
418  infot = 6
419  CALL dppsv( 'U', 2, 0, a, b, 1, info )
420  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
421 *
422 * DPPSVX
423 *
424  srnamt = 'DPPSVX'
425  infot = 1
426  CALL dppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
427  $ r1, r2, w, iw, info )
428  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
429  infot = 2
430  CALL dppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
431  $ r1, r2, w, iw, info )
432  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
433  infot = 3
434  CALL dppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
435  $ r1, r2, w, iw, info )
436  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
437  infot = 4
438  CALL dppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
439  $ r1, r2, w, iw, info )
440  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
441  infot = 7
442  eq = '/'
443  CALL dppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
444  $ r1, r2, w, iw, info )
445  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
446  infot = 8
447  eq = 'Y'
448  CALL dppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
449  $ r1, r2, w, iw, info )
450  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
451  infot = 10
452  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
453  $ r1, r2, w, iw, info )
454  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
455  infot = 12
456  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
457  $ r1, r2, w, iw, info )
458  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
459 *
460  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
461 *
462 * DPBSV
463 *
464  srnamt = 'DPBSV '
465  infot = 1
466  CALL dpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
467  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
468  infot = 2
469  CALL dpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
470  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
471  infot = 3
472  CALL dpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
473  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
474  infot = 4
475  CALL dpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
476  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
477  infot = 6
478  CALL dpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
479  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
480  infot = 8
481  CALL dpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
482  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
483 *
484 * DPBSVX
485 *
486  srnamt = 'DPBSVX'
487  infot = 1
488  CALL dpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
489  $ rcond, r1, r2, w, iw, info )
490  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
491  infot = 2
492  CALL dpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
493  $ rcond, r1, r2, w, iw, info )
494  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
495  infot = 3
496  CALL dpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
497  $ 1, rcond, r1, r2, w, iw, info )
498  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
499  infot = 4
500  CALL dpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
501  $ 1, rcond, r1, r2, w, iw, info )
502  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
503  infot = 5
504  CALL dpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
505  $ 1, rcond, r1, r2, w, iw, info )
506  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
507  infot = 7
508  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
509  $ rcond, r1, r2, w, iw, info )
510  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
511  infot = 9
512  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
513  $ rcond, r1, r2, w, iw, info )
514  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
515  infot = 10
516  eq = '/'
517  CALL dpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
518  $ rcond, r1, r2, w, iw, info )
519  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
520  infot = 11
521  eq = 'Y'
522  CALL dpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
523  $ rcond, r1, r2, w, iw, info )
524  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
525  infot = 13
526  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
527  $ rcond, r1, r2, w, iw, info )
528  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
529  infot = 15
530  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
531  $ rcond, r1, r2, w, iw, info )
532  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
533 *
534  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
535 *
536 * DPTSV
537 *
538  srnamt = 'DPTSV '
539  infot = 1
540  CALL dptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
541  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
542  infot = 2
543  CALL dptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
544  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
545  infot = 6
546  CALL dptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
547  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
548 *
549 * DPTSVX
550 *
551  srnamt = 'DPTSVX'
552  infot = 1
553  CALL dptsvx( '/', 0, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
554  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
555  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
556  infot = 2
557  CALL dptsvx( 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
558  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
559  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
560  infot = 3
561  CALL dptsvx( 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
562  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
563  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
564  infot = 9
565  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
566  $ af( 1, 2 ), b, 1, x, 2, rcond, r1, r2, w, info )
567  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
568  infot = 11
569  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
570  $ af( 1, 2 ), b, 2, x, 1, rcond, r1, r2, w, info )
571  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
572 *
573  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
574 *
575 * DSYSV
576 *
577  srnamt = 'DSYSV '
578  infot = 1
579  CALL dsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
580  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
581  infot = 2
582  CALL dsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
583  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
584  infot = 3
585  CALL dsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
586  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
587  infot = 5
588  CALL dsysv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
589  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
590  infot = 8
591  CALL dsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
592  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
593  infot = 10
594  CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
595  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
596  infot = 10
597  CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
598  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
599 *
600 * DSYSVX
601 *
602  srnamt = 'DSYSVX'
603  infot = 1
604  CALL dsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
605  $ rcond, r1, r2, w, 1, iw, info )
606  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
607  infot = 2
608  CALL dsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
609  $ rcond, r1, r2, w, 1, iw, info )
610  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
611  infot = 3
612  CALL dsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
613  $ rcond, r1, r2, w, 1, iw, info )
614  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
615  infot = 4
616  CALL dsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
617  $ rcond, r1, r2, w, 1, iw, info )
618  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
619  infot = 6
620  CALL dsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
621  $ rcond, r1, r2, w, 4, iw, info )
622  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
623  infot = 8
624  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
625  $ rcond, r1, r2, w, 4, iw, info )
626  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
627  infot = 11
628  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
629  $ rcond, r1, r2, w, 4, iw, info )
630  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
631  infot = 13
632  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
633  $ rcond, r1, r2, w, 4, iw, info )
634  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
635  infot = 18
636  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
637  $ rcond, r1, r2, w, 3, iw, info )
638  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
639 *
640  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
641 *
642 * DSYSV_ROOK
643 *
644  srnamt = 'DSYSV_ROOK'
645  infot = 1
646  CALL dsysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
647  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
648  infot = 2
649  CALL dsysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
650  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
651  infot = 3
652  CALL dsysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
653  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
654  infot = 5
655  CALL dsysv_rook( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
656  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
657  infot = 8
658  CALL dsysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
659  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
660  infot = 10
661  CALL dsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
662  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
663  infot = 10
664  CALL dsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
665  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
666 *
667  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
668 *
669 * DSYSV_RK
670 *
671 * Test error exits of the driver that uses factorization
672 * of a symmetric indefinite matrix with rook
673 * (bounded Bunch-Kaufman) pivoting with the new storage
674 * format for factors L ( or U) and D.
675 *
676 * L (or U) is stored in A, diagonal of D is stored on the
677 * diagonal of A, subdiagonal of D is stored in a separate array E.
678 *
679  srnamt = 'DSYSV_RK'
680  infot = 1
681  CALL dsysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
682  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
683  infot = 2
684  CALL dsysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
685  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
686  infot = 3
687  CALL dsysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
688  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
689  infot = 5
690  CALL dsysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
691  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
692  infot = 9
693  CALL dsysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
694  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
695  infot = 11
696  CALL dsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
697  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
698  infot = 11
699  CALL dsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
700  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
701 *
702  ELSE IF( lsamen( 2, c2, 'SA' ) ) THEN
703 *
704 * DSYSV_AA
705 *
706  srnamt = 'DSYSV_AA'
707  infot = 1
708  CALL dsysv_aa( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
709  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
710  infot = 2
711  CALL dsysv_aa( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
712  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
713  infot = 3
714  CALL dsysv_aa( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
715  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
716  infot = 8
717  CALL dsysv_aa( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
718  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
719 *
720  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
721 *
722 * DSPSV
723 *
724  srnamt = 'DSPSV '
725  infot = 1
726  CALL dspsv( '/', 0, 0, a, ip, b, 1, info )
727  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
728  infot = 2
729  CALL dspsv( 'U', -1, 0, a, ip, b, 1, info )
730  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
731  infot = 3
732  CALL dspsv( 'U', 0, -1, a, ip, b, 1, info )
733  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
734  infot = 7
735  CALL dspsv( 'U', 2, 0, a, ip, b, 1, info )
736  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
737 *
738 * DSPSVX
739 *
740  srnamt = 'DSPSVX'
741  infot = 1
742  CALL dspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
743  $ r2, w, iw, info )
744  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
745  infot = 2
746  CALL dspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
747  $ r2, w, iw, info )
748  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
749  infot = 3
750  CALL dspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
751  $ r2, w, iw, info )
752  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
753  infot = 4
754  CALL dspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
755  $ r2, w, iw, info )
756  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
757  infot = 9
758  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
759  $ r2, w, iw, info )
760  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
761  infot = 11
762  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
763  $ r2, w, iw, info )
764  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
765  END IF
766 *
767 * Print a summary line.
768 *
769  IF( ok ) THEN
770  WRITE( nout, fmt = 9999 )path
771  ELSE
772  WRITE( nout, fmt = 9998 )path
773  END IF
774 *
775  9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
776  9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
777  $ 'exits ***' )
778 *
779  RETURN
780 *
781 * End of DERRVX
782 *
783  END
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:129
subroutine dsysv_aa(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
DSYSV_AA computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: dsysv_aa.f:166
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:279
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:132
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:164
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
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:351
subroutine dgesv(N, NRHS, A, LDA, IPIV, B, LDB, INFO)
DGESV computes the solution to system of linear equations A * X = B for GE matrices ...
Definition: dgesv.f:124
subroutine derrvx(PATH, NUNIT)
DERRVX
Definition: derrvx.f:57
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:345
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:371
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:295
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:286
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:206
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:164
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:146
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:309
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:230
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:314
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:230
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:166
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:116
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:173