LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
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 *> \date November 2011
52 *
53 *> \ingroup double_lin
54 *
55 * =====================================================================
56  SUBROUTINE derrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.4.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 * November 2011
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, n_err_bnds, nparams
78  DOUBLE PRECISION rcond, rpvgrw, berr
79 * ..
80 * .. Local Arrays ..
81  INTEGER ip( nmax ), iw( nmax )
82  DOUBLE PRECISION a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
83  $ c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
84  $ w( 2*nmax ), x( nmax ), err_bnds_n( nmax, 3 ),
85  $ err_bnds_c( nmax, 3 ), params( 1 )
86 * ..
87 * .. External Functions ..
88  LOGICAL lsamen
89  EXTERNAL lsamen
90 * ..
91 * .. External Subroutines ..
92  EXTERNAL chkxer, dgbsv, dgbsvx, dgesv, dgesvx, dgtsv,
96 * ..
97 * .. Scalars in Common ..
98  LOGICAL lerr, ok
99  CHARACTER*32 srnamt
100  INTEGER infot, nout
101 * ..
102 * .. Common blocks ..
103  common / infoc / infot, nout, ok, lerr
104  common / srnamc / srnamt
105 * ..
106 * .. Intrinsic Functions ..
107  INTRINSIC dble
108 * ..
109 * .. Executable Statements ..
110 *
111  nout = nunit
112  WRITE( nout, fmt = * )
113  c2 = path( 2: 3 )
114 *
115 * Set the variables to innocuous values.
116 *
117  DO 20 j = 1, nmax
118  DO 10 i = 1, nmax
119  a( i, j ) = 1.d0 / dble( i+j )
120  af( i, j ) = 1.d0 / dble( i+j )
121  10 continue
122  b( j ) = 0.d0
123  r1( j ) = 0.d0
124  r2( j ) = 0.d0
125  w( j ) = 0.d0
126  x( j ) = 0.d0
127  c( j ) = 0.d0
128  r( j ) = 0.d0
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 * DGESVXX
204 *
205  n_err_bnds = 3
206  nparams = 1
207  srnamt = 'DGESVXX'
208  infot = 1
209  CALL dgesvxx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
210  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
211  $ err_bnds_c, nparams, params, w, iw, info )
212  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
213  infot = 2
214  CALL dgesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
215  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
216  $ err_bnds_c, nparams, params, w, iw, info )
217  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
218  infot = 3
219  CALL dgesvxx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
220  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
221  $ err_bnds_c, nparams, params, w, iw, info )
222  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
223  infot = 4
224  CALL dgesvxx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
225  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
226  $ err_bnds_c, nparams, params, w, iw, info )
227  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
228  infot = 6
229  CALL dgesvxx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
230  $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
231  $ err_bnds_c, nparams, params, w, iw, info )
232  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
233  infot = 8
234  CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
235  $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
236  $ err_bnds_c, nparams, params, w, iw, info )
237  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
238  infot = 10
239  eq = '/'
240  CALL dgesvxx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
241  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
242  $ err_bnds_c, nparams, params, w, iw, info )
243  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
244  infot = 11
245  eq = 'R'
246  CALL dgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
247  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
248  $ err_bnds_c, nparams, params, w, iw, info )
249  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
250  infot = 12
251  eq = 'C'
252  CALL dgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
253  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
254  $ err_bnds_c, nparams, params, w, iw, info )
255  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
256  infot = 14
257  CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
258  $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
259  $ err_bnds_c, nparams, params, w, iw, info )
260  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
261  infot = 16
262  CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
263  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
264  $ err_bnds_c, nparams, params, w, iw, info )
265  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
266 *
267  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
268 *
269 * DGBSV
270 *
271  srnamt = 'DGBSV '
272  infot = 1
273  CALL dgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
274  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
275  infot = 2
276  CALL dgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
277  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
278  infot = 3
279  CALL dgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
280  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
281  infot = 4
282  CALL dgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
283  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
284  infot = 6
285  CALL dgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
286  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
287  infot = 9
288  CALL dgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
289  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
290 *
291 * DGBSVX
292 *
293  srnamt = 'DGBSVX'
294  infot = 1
295  CALL dgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
296  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
297  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
298  infot = 2
299  CALL dgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
300  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
301  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
302  infot = 3
303  CALL dgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
304  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
305  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
306  infot = 4
307  CALL dgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
308  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
309  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
310  infot = 5
311  CALL dgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
312  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
313  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
314  infot = 6
315  CALL dgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
316  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
317  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
318  infot = 8
319  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
320  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
321  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
322  infot = 10
323  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
324  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
325  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
326  infot = 12
327  eq = '/'
328  CALL dgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
329  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
330  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
331  infot = 13
332  eq = 'R'
333  CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
334  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
335  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
336  infot = 14
337  eq = 'C'
338  CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
339  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
340  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
341  infot = 16
342  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
343  $ b, 1, x, 2, rcond, r1, r2, w, iw, info )
344  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
345  infot = 18
346  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
347  $ b, 2, x, 1, rcond, r1, r2, w, iw, info )
348  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
349 *
350 * DGBSVXX
351 *
352  n_err_bnds = 3
353  nparams = 1
354  srnamt = 'DGBSVXX'
355  infot = 1
356  CALL dgbsvxx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
357  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
358  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
359  $ info )
360  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
361  infot = 2
362  CALL dgbsvxx( 'N', '/', 0, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
363  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
364  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
365  $ info )
366  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
367  infot = 3
368  CALL dgbsvxx( 'N', 'N', -1, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
369  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
370  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
371  $ info )
372  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
373  infot = 4
374  CALL dgbsvxx( 'N', 'N', 2, -1, 1, 0, a, 1, af, 1, ip, eq,
375  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
376  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
377  $ info )
378  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
379  infot = 5
380  CALL dgbsvxx( 'N', 'N', 2, 1, -1, 0, a, 1, af, 1, ip, eq,
381  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
382  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
383  $ info )
384  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
385  infot = 6
386  CALL dgbsvxx( 'N', 'N', 0, 1, 1, -1, a, 1, af, 1, ip, eq, r, c,
387  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
388  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
389  $ info )
390  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
391  infot = 8
392  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 2, af, 2, ip, eq, r, c,
393  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
394  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
395  $ info )
396  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
397  infot = 10
398  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 3, ip, eq, r, c,
399  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
400  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
401  $ info )
402  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
403  infot = 12
404  eq = '/'
405  CALL dgbsvxx( 'F', 'N', 0, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
406  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
407  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
408  $ info )
409  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
410  infot = 13
411  eq = 'R'
412  CALL dgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
413  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
414  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
415  $ info )
416  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
417  infot = 14
418  eq = 'C'
419  CALL dgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
420  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
421  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
422  $ info )
423  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
424  infot = 15
425  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
426  $ b, 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
427  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
428  $ info )
429  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
430  infot = 16
431  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
432  $ b, 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
433  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
434  $ info )
435  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
436 *
437  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
438 *
439 * DGTSV
440 *
441  srnamt = 'DGTSV '
442  infot = 1
443  CALL dgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
444  $ info )
445  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
446  infot = 2
447  CALL dgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
448  $ info )
449  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
450  infot = 7
451  CALL dgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
452  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
453 *
454 * DGTSVX
455 *
456  srnamt = 'DGTSVX'
457  infot = 1
458  CALL dgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
459  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
460  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
461  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
462  infot = 2
463  CALL dgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
464  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
465  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
466  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
467  infot = 3
468  CALL dgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
469  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
470  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
471  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
472  infot = 4
473  CALL dgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
474  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
475  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
476  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
477  infot = 14
478  CALL dgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
479  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
480  $ ip, b, 1, x, 2, rcond, r1, r2, w, iw, info )
481  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
482  infot = 16
483  CALL dgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
484  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
485  $ ip, b, 2, x, 1, rcond, r1, r2, w, iw, info )
486  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
487 *
488  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
489 *
490 * DPOSV
491 *
492  srnamt = 'DPOSV '
493  infot = 1
494  CALL dposv( '/', 0, 0, a, 1, b, 1, info )
495  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
496  infot = 2
497  CALL dposv( 'U', -1, 0, a, 1, b, 1, info )
498  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
499  infot = 3
500  CALL dposv( 'U', 0, -1, a, 1, b, 1, info )
501  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
502  infot = 5
503  CALL dposv( 'U', 2, 0, a, 1, b, 2, info )
504  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
505  infot = 7
506  CALL dposv( 'U', 2, 0, a, 2, b, 1, info )
507  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
508 *
509 * DPOSVX
510 *
511  srnamt = 'DPOSVX'
512  infot = 1
513  CALL dposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
514  $ rcond, r1, r2, w, iw, info )
515  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
516  infot = 2
517  CALL dposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
518  $ rcond, r1, r2, w, iw, info )
519  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
520  infot = 3
521  CALL dposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
522  $ rcond, r1, r2, w, iw, info )
523  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
524  infot = 4
525  CALL dposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
526  $ rcond, r1, r2, w, iw, info )
527  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
528  infot = 6
529  CALL dposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
530  $ rcond, r1, r2, w, iw, info )
531  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
532  infot = 8
533  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
534  $ rcond, r1, r2, w, iw, info )
535  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
536  infot = 9
537  eq = '/'
538  CALL dposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
539  $ rcond, r1, r2, w, iw, info )
540  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
541  infot = 10
542  eq = 'Y'
543  CALL dposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
544  $ rcond, r1, r2, w, iw, info )
545  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
546  infot = 12
547  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
548  $ rcond, r1, r2, w, iw, info )
549  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
550  infot = 14
551  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
552  $ rcond, r1, r2, w, iw, info )
553  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
554 *
555 * DPOSVXX
556 *
557  n_err_bnds = 3
558  nparams = 1
559  srnamt = 'DPOSVXX'
560  infot = 1
561  CALL dposvxx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
562  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
563  $ err_bnds_c, nparams, params, w, iw, info )
564  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
565  infot = 2
566  CALL dposvxx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
567  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
568  $ err_bnds_c, nparams, params, w, iw, info )
569  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
570  infot = 3
571  CALL dposvxx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
572  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
573  $ err_bnds_c, nparams, params, w, iw, info )
574  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
575  infot = 4
576  CALL dposvxx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
577  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
578  $ err_bnds_c, nparams, params, w, iw, info )
579  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
580  infot = 6
581  CALL dposvxx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
582  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
583  $ err_bnds_c, nparams, params, w, iw, info )
584  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
585  infot = 8
586  CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
587  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
588  $ err_bnds_c, nparams, params, w, iw, info )
589  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
590  infot = 9
591  eq = '/'
592  CALL dposvxx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
593  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
594  $ err_bnds_c, nparams, params, w, iw, info )
595  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
596  infot = 10
597  eq = 'Y'
598  CALL dposvxx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
599  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
600  $ err_bnds_c, nparams, params, w, iw, info )
601  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
602  infot = 12
603  CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
604  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
605  $ err_bnds_c, nparams, params, w, iw, info )
606  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
607  infot = 14
608  CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
609  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
610  $ err_bnds_c, nparams, params, w, iw, info )
611  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
612 *
613  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
614 *
615 * DPPSV
616 *
617  srnamt = 'DPPSV '
618  infot = 1
619  CALL dppsv( '/', 0, 0, a, b, 1, info )
620  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
621  infot = 2
622  CALL dppsv( 'U', -1, 0, a, b, 1, info )
623  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
624  infot = 3
625  CALL dppsv( 'U', 0, -1, a, b, 1, info )
626  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
627  infot = 6
628  CALL dppsv( 'U', 2, 0, a, b, 1, info )
629  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
630 *
631 * DPPSVX
632 *
633  srnamt = 'DPPSVX'
634  infot = 1
635  CALL dppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
636  $ r1, r2, w, iw, info )
637  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
638  infot = 2
639  CALL dppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
640  $ r1, r2, w, iw, info )
641  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
642  infot = 3
643  CALL dppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
644  $ r1, r2, w, iw, info )
645  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
646  infot = 4
647  CALL dppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
648  $ r1, r2, w, iw, info )
649  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
650  infot = 7
651  eq = '/'
652  CALL dppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
653  $ r1, r2, w, iw, info )
654  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
655  infot = 8
656  eq = 'Y'
657  CALL dppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
658  $ r1, r2, w, iw, info )
659  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
660  infot = 10
661  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
662  $ r1, r2, w, iw, info )
663  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
664  infot = 12
665  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
666  $ r1, r2, w, iw, info )
667  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
668 *
669  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
670 *
671 * DPBSV
672 *
673  srnamt = 'DPBSV '
674  infot = 1
675  CALL dpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
676  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
677  infot = 2
678  CALL dpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
679  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
680  infot = 3
681  CALL dpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
682  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
683  infot = 4
684  CALL dpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
685  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
686  infot = 6
687  CALL dpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
688  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
689  infot = 8
690  CALL dpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
691  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
692 *
693 * DPBSVX
694 *
695  srnamt = 'DPBSVX'
696  infot = 1
697  CALL dpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
698  $ rcond, r1, r2, w, iw, info )
699  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
700  infot = 2
701  CALL dpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
702  $ rcond, r1, r2, w, iw, info )
703  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
704  infot = 3
705  CALL dpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
706  $ 1, rcond, r1, r2, w, iw, info )
707  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
708  infot = 4
709  CALL dpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
710  $ 1, rcond, r1, r2, w, iw, info )
711  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
712  infot = 5
713  CALL dpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
714  $ 1, rcond, r1, r2, w, iw, info )
715  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
716  infot = 7
717  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
718  $ rcond, r1, r2, w, iw, info )
719  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
720  infot = 9
721  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
722  $ rcond, r1, r2, w, iw, info )
723  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
724  infot = 10
725  eq = '/'
726  CALL dpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
727  $ rcond, r1, r2, w, iw, info )
728  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
729  infot = 11
730  eq = 'Y'
731  CALL dpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
732  $ rcond, r1, r2, w, iw, info )
733  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
734  infot = 13
735  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
736  $ rcond, r1, r2, w, iw, info )
737  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
738  infot = 15
739  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
740  $ rcond, r1, r2, w, iw, info )
741  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
742 *
743  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
744 *
745 * DPTSV
746 *
747  srnamt = 'DPTSV '
748  infot = 1
749  CALL dptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
750  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
751  infot = 2
752  CALL dptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
753  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
754  infot = 6
755  CALL dptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
756  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
757 *
758 * DPTSVX
759 *
760  srnamt = 'DPTSVX'
761  infot = 1
762  CALL dptsvx( '/', 0, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
763  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
764  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
765  infot = 2
766  CALL dptsvx( 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
767  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
768  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
769  infot = 3
770  CALL dptsvx( 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
771  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
772  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
773  infot = 9
774  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
775  $ af( 1, 2 ), b, 1, x, 2, rcond, r1, r2, w, info )
776  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
777  infot = 11
778  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
779  $ af( 1, 2 ), b, 2, x, 1, rcond, r1, r2, w, info )
780  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
781 *
782  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
783 *
784 * DSYSV
785 *
786  srnamt = 'DSYSV '
787  infot = 1
788  CALL dsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
789  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
790  infot = 2
791  CALL dsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
792  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
793  infot = 3
794  CALL dsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
795  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
796  infot = 8
797  CALL dsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
798  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
799 *
800 * DSYSVX
801 *
802  srnamt = 'DSYSVX'
803  infot = 1
804  CALL dsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
805  $ rcond, r1, r2, w, 1, iw, info )
806  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
807  infot = 2
808  CALL dsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
809  $ rcond, r1, r2, w, 1, iw, info )
810  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
811  infot = 3
812  CALL dsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
813  $ rcond, r1, r2, w, 1, iw, info )
814  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
815  infot = 4
816  CALL dsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
817  $ rcond, r1, r2, w, 1, iw, info )
818  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
819  infot = 6
820  CALL dsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
821  $ rcond, r1, r2, w, 4, iw, info )
822  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
823  infot = 8
824  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
825  $ rcond, r1, r2, w, 4, iw, info )
826  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
827  infot = 11
828  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
829  $ rcond, r1, r2, w, 4, iw, info )
830  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
831  infot = 13
832  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
833  $ rcond, r1, r2, w, 4, iw, info )
834  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
835  infot = 18
836  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
837  $ rcond, r1, r2, w, 3, iw, info )
838  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
839 *
840 * DSYSVXX
841 *
842  n_err_bnds = 3
843  nparams = 1
844  srnamt = 'DSYSVXX'
845  infot = 1
846  eq = 'N'
847  CALL dsysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
848  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
849  $ err_bnds_c, nparams, params, w, iw, info )
850  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
851  infot = 2
852  CALL dsysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
853  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
854  $ err_bnds_c, nparams, params, w, iw, info )
855  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
856  infot = 3
857  CALL dsysvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
858  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
859  $ err_bnds_c, nparams, params, w, iw, info )
860  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
861  infot = 4
862  eq = '/'
863  CALL dsysvxx( 'N', 'U', 0, -1, 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  eq = 'Y'
868  infot = 6
869  CALL dsysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
870  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
871  $ err_bnds_c, nparams, params, w, iw, info )
872  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
873  infot = 8
874  CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
875  $ 2, 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  infot = 12
879  eq = 'N'
880  CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, 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 = 14
885  CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
886  $ 1, 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 *
890  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
891 *
892 * DSPSV
893 *
894  srnamt = 'DSPSV '
895  infot = 1
896  CALL dspsv( '/', 0, 0, a, ip, b, 1, info )
897  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
898  infot = 2
899  CALL dspsv( 'U', -1, 0, a, ip, b, 1, info )
900  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
901  infot = 3
902  CALL dspsv( 'U', 0, -1, a, ip, b, 1, info )
903  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
904  infot = 7
905  CALL dspsv( 'U', 2, 0, a, ip, b, 1, info )
906  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
907 *
908 * DSPSVX
909 *
910  srnamt = 'DSPSVX'
911  infot = 1
912  CALL dspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
913  $ r2, w, iw, info )
914  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
915  infot = 2
916  CALL dspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
917  $ r2, w, iw, info )
918  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
919  infot = 3
920  CALL dspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
921  $ r2, w, iw, info )
922  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
923  infot = 4
924  CALL dspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
925  $ r2, w, iw, info )
926  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
927  infot = 9
928  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
929  $ r2, w, iw, info )
930  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
931  infot = 11
932  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
933  $ r2, w, iw, info )
934  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
935  END IF
936 *
937 * Print a summary line.
938 *
939  IF( ok ) THEN
940  WRITE( nout, fmt = 9999 )path
941  ELSE
942  WRITE( nout, fmt = 9998 )path
943  END IF
944 *
945  9999 format( 1x, a3, ' drivers passed the tests of the error exits' )
946  9998 format( ' *** ', a3, ' drivers failed the tests of the error ',
947  $ 'exits ***' )
948 *
949  return
950 *
951 * End of DERRVX
952 *
953  END