LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
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 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  REAL one
74  parameter ( one = 1.0d+0 )
75 * ..
76 * .. Local Scalars ..
77  CHARACTER eq
78  CHARACTER*2 c2
79  INTEGER i, info, j, n_err_bnds, nparams
80  DOUBLE PRECISION rcond, rpvgrw, berr
81 * ..
82 * .. Local Arrays ..
83  INTEGER ip( nmax ), iw( nmax )
84  DOUBLE PRECISION a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
85  $ c( nmax ), e( nmax ), r( nmax ), r1( nmax ),
86  $ r2( nmax ), w( 2*nmax ), x( nmax ),
87  $ err_bnds_n( nmax, 3 ), err_bnds_c( nmax, 3 ),
88  $ params( 1 )
89 * ..
90 * .. External Functions ..
91  LOGICAL lsamen
92  EXTERNAL lsamen
93 * ..
94 * .. External Subroutines ..
95  EXTERNAL chkxer, dgbsv, dgbsvx, dgesv, dgesvx, dgtsv,
99  $ dposvxx, dgbsvxx
100 * ..
101 * .. Scalars in Common ..
102  LOGICAL lerr, ok
103  CHARACTER*32 srnamt
104  INTEGER infot, nout
105 * ..
106 * .. Common blocks ..
107  COMMON / infoc / infot, nout, ok, lerr
108  COMMON / srnamc / srnamt
109 * ..
110 * .. Intrinsic Functions ..
111  INTRINSIC dble
112 * ..
113 * .. Executable Statements ..
114 *
115  nout = nunit
116  WRITE( nout, fmt = * )
117  c2 = path( 2: 3 )
118 *
119 * Set the variables to innocuous values.
120 *
121  DO 20 j = 1, nmax
122  DO 10 i = 1, nmax
123  a( i, j ) = 1.d0 / dble( i+j )
124  af( i, j ) = 1.d0 / dble( i+j )
125  10 CONTINUE
126  b( j ) = 0.d+0
127  e( j ) = 0.d+0
128  r1( j ) = 0.d+0
129  r2( j ) = 0.d+0
130  w( j ) = 0.d+0
131  x( j ) = 0.d+0
132  c( j ) = 0.d+0
133  r( j ) = 0.d+0
134  ip( j ) = j
135  20 CONTINUE
136  eq = ' '
137  ok = .true.
138 *
139  IF( lsamen( 2, c2, 'GE' ) ) THEN
140 *
141 * DGESV
142 *
143  srnamt = 'DGESV '
144  infot = 1
145  CALL dgesv( -1, 0, a, 1, ip, b, 1, info )
146  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
147  infot = 2
148  CALL dgesv( 0, -1, a, 1, ip, b, 1, info )
149  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
150  infot = 4
151  CALL dgesv( 2, 1, a, 1, ip, b, 2, info )
152  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
153  infot = 7
154  CALL dgesv( 2, 1, a, 2, ip, b, 1, info )
155  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
156 *
157 * DGESVX
158 *
159  srnamt = 'DGESVX'
160  infot = 1
161  CALL dgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
162  $ x, 1, rcond, r1, r2, w, iw, info )
163  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
164  infot = 2
165  CALL dgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
166  $ x, 1, rcond, r1, r2, w, iw, info )
167  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
168  infot = 3
169  CALL dgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
170  $ x, 1, rcond, r1, r2, w, iw, info )
171  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
172  infot = 4
173  CALL dgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
174  $ x, 1, rcond, r1, r2, w, iw, info )
175  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
176  infot = 6
177  CALL dgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
178  $ x, 2, rcond, r1, r2, w, iw, info )
179  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
180  infot = 8
181  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
182  $ x, 2, rcond, r1, r2, w, iw, info )
183  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
184  infot = 10
185  eq = '/'
186  CALL dgesvx( 'F', 'N', 0, 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 = 11
190  eq = 'R'
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 = 12
195  eq = 'C'
196  CALL dgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
197  $ x, 1, rcond, r1, r2, w, iw, info )
198  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
199  infot = 14
200  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
201  $ x, 2, rcond, r1, r2, w, iw, info )
202  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
203  infot = 16
204  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
205  $ x, 1, rcond, r1, r2, w, iw, info )
206  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
207 *
208 * DGESVXX
209 *
210  n_err_bnds = 3
211  nparams = 1
212  srnamt = 'DGESVXX'
213  infot = 1
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 = 2
219  CALL dgesvxx( 'N', '/', 0, 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 = 3
224  CALL dgesvxx( 'N', 'N', -1, 0, 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 = 4
229  CALL dgesvxx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
230  $ x, 1, 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 = 6
234  CALL dgesvxx( 'N', 'N', 2, 1, a, 1, af, 2, 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 = 8
239  CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
240  $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
241  $ err_bnds_c, nparams, params, w, iw, info )
242  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
243  infot = 10
244  eq = '/'
245  CALL dgesvxx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
246  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
247  $ err_bnds_c, nparams, params, w, iw, info )
248  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
249  infot = 11
250  eq = 'R'
251  CALL dgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
252  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
253  $ err_bnds_c, nparams, params, w, iw, info )
254  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
255  infot = 12
256  eq = 'C'
257  CALL dgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
258  $ x, 1, 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 = 14
262  CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
263  $ x, 2, 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  infot = 16
267  CALL dgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
268  $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
269  $ err_bnds_c, nparams, params, w, iw, info )
270  CALL chkxer( 'DGESVXX', infot, nout, lerr, ok )
271 *
272  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
273 *
274 * DGBSV
275 *
276  srnamt = 'DGBSV '
277  infot = 1
278  CALL dgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
279  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
280  infot = 2
281  CALL dgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
282  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
283  infot = 3
284  CALL dgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
285  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
286  infot = 4
287  CALL dgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
288  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
289  infot = 6
290  CALL dgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
291  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
292  infot = 9
293  CALL dgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
294  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
295 *
296 * DGBSVX
297 *
298  srnamt = 'DGBSVX'
299  infot = 1
300  CALL dgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
301  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
302  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
303  infot = 2
304  CALL dgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
305  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
306  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
307  infot = 3
308  CALL dgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
309  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
310  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
311  infot = 4
312  CALL dgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
313  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
314  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
315  infot = 5
316  CALL dgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
317  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
318  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
319  infot = 6
320  CALL dgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
321  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
322  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
323  infot = 8
324  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
325  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
326  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
327  infot = 10
328  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, 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 = 12
332  eq = '/'
333  CALL dgbsvx( 'F', 'N', 0, 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 = 13
337  eq = 'R'
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 = 14
342  eq = 'C'
343  CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
344  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
345  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
346  infot = 16
347  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
348  $ b, 1, x, 2, rcond, r1, r2, w, iw, info )
349  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
350  infot = 18
351  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
352  $ b, 2, x, 1, rcond, r1, r2, w, iw, info )
353  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
354 *
355 * DGBSVXX
356 *
357  n_err_bnds = 3
358  nparams = 1
359  srnamt = 'DGBSVXX'
360  infot = 1
361  CALL dgbsvxx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
362  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
363  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
364  $ info )
365  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
366  infot = 2
367  CALL dgbsvxx( 'N', '/', 0, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
368  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
369  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
370  $ info )
371  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
372  infot = 3
373  CALL dgbsvxx( 'N', 'N', -1, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
374  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
375  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
376  $ info )
377  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
378  infot = 4
379  CALL dgbsvxx( 'N', 'N', 2, -1, 1, 0, a, 1, af, 1, ip, eq,
380  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
381  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
382  $ info )
383  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
384  infot = 5
385  CALL dgbsvxx( 'N', 'N', 2, 1, -1, 0, a, 1, af, 1, ip, eq,
386  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
387  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
388  $ info )
389  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
390  infot = 6
391  CALL dgbsvxx( 'N', 'N', 0, 1, 1, -1, a, 1, af, 1, ip, eq, r, c,
392  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
393  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
394  $ info )
395  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
396  infot = 8
397  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 2, af, 2, ip, eq, r, c,
398  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
399  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
400  $ info )
401  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
402  infot = 10
403  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 3, ip, eq, r, c,
404  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
405  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
406  $ info )
407  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
408  infot = 12
409  eq = '/'
410  CALL dgbsvxx( 'F', 'N', 0, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
411  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
412  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
413  $ info )
414  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
415  infot = 13
416  eq = 'R'
417  CALL dgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
418  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
419  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
420  $ info )
421  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
422  infot = 14
423  eq = 'C'
424  CALL dgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
425  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
426  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
427  $ info )
428  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
429  infot = 15
430  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
431  $ b, 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
432  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
433  $ info )
434  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
435  infot = 16
436  CALL dgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
437  $ b, 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
438  $ err_bnds_n, err_bnds_c, nparams, params, w, iw,
439  $ info )
440  CALL chkxer( 'DGBSVXX', infot, nout, lerr, ok )
441 *
442  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
443 *
444 * DGTSV
445 *
446  srnamt = 'DGTSV '
447  infot = 1
448  CALL dgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
449  $ info )
450  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
451  infot = 2
452  CALL dgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
453  $ info )
454  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
455  infot = 7
456  CALL dgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
457  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
458 *
459 * DGTSVX
460 *
461  srnamt = 'DGTSVX'
462  infot = 1
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 = 2
468  CALL dgtsvx( 'N', '/', 0, 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 = 3
473  CALL dgtsvx( 'N', 'N', -1, 0, 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 = 4
478  CALL dgtsvx( 'N', 'N', 0, -1, 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, 1, rcond, r1, r2, w, iw, info )
481  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
482  infot = 14
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, 1, x, 2, rcond, r1, r2, w, iw, info )
486  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
487  infot = 16
488  CALL dgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
489  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
490  $ ip, b, 2, x, 1, rcond, r1, r2, w, iw, info )
491  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
492 *
493  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
494 *
495 * DPOSV
496 *
497  srnamt = 'DPOSV '
498  infot = 1
499  CALL dposv( '/', 0, 0, a, 1, b, 1, info )
500  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
501  infot = 2
502  CALL dposv( 'U', -1, 0, a, 1, b, 1, info )
503  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
504  infot = 3
505  CALL dposv( 'U', 0, -1, a, 1, b, 1, info )
506  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
507  infot = 5
508  CALL dposv( 'U', 2, 0, a, 1, b, 2, info )
509  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
510  infot = 7
511  CALL dposv( 'U', 2, 0, a, 2, b, 1, info )
512  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
513 *
514 * DPOSVX
515 *
516  srnamt = 'DPOSVX'
517  infot = 1
518  CALL dposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
519  $ rcond, r1, r2, w, iw, info )
520  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
521  infot = 2
522  CALL dposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
523  $ rcond, r1, r2, w, iw, info )
524  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
525  infot = 3
526  CALL dposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
527  $ rcond, r1, r2, w, iw, info )
528  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
529  infot = 4
530  CALL dposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
531  $ rcond, r1, r2, w, iw, info )
532  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
533  infot = 6
534  CALL dposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
535  $ rcond, r1, r2, w, iw, info )
536  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
537  infot = 8
538  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
539  $ rcond, r1, r2, w, iw, info )
540  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
541  infot = 9
542  eq = '/'
543  CALL dposvx( 'F', 'U', 0, 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 = 10
547  eq = 'Y'
548  CALL dposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
549  $ rcond, r1, r2, w, iw, info )
550  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
551  infot = 12
552  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
553  $ rcond, r1, r2, w, iw, info )
554  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
555  infot = 14
556  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
557  $ rcond, r1, r2, w, iw, info )
558  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
559 *
560 * DPOSVXX
561 *
562  n_err_bnds = 3
563  nparams = 1
564  srnamt = 'DPOSVXX'
565  infot = 1
566  CALL dposvxx( '/', 'U', 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 = 2
571  CALL dposvxx( 'N', '/', 0, 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 = 3
576  CALL dposvxx( 'N', 'U', -1, 0, 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 = 4
581  CALL dposvxx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
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 = 6
586  CALL dposvxx( 'N', 'U', 2, 0, a, 1, af, 2, 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 = 8
591  CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
592  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
593  $ err_bnds_c, nparams, params, w, iw, info )
594  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
595  infot = 9
596  eq = '/'
597  CALL dposvxx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
598  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
599  $ err_bnds_c, nparams, params, w, iw, info )
600  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
601  infot = 10
602  eq = 'Y'
603  CALL dposvxx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
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 = 12
608  CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
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  infot = 14
613  CALL dposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
614  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
615  $ err_bnds_c, nparams, params, w, iw, info )
616  CALL chkxer( 'DPOSVXX', infot, nout, lerr, ok )
617 *
618  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
619 *
620 * DPPSV
621 *
622  srnamt = 'DPPSV '
623  infot = 1
624  CALL dppsv( '/', 0, 0, a, b, 1, info )
625  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
626  infot = 2
627  CALL dppsv( 'U', -1, 0, a, b, 1, info )
628  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
629  infot = 3
630  CALL dppsv( 'U', 0, -1, a, b, 1, info )
631  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
632  infot = 6
633  CALL dppsv( 'U', 2, 0, a, b, 1, info )
634  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
635 *
636 * DPPSVX
637 *
638  srnamt = 'DPPSVX'
639  infot = 1
640  CALL dppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
641  $ r1, r2, w, iw, info )
642  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
643  infot = 2
644  CALL dppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
645  $ r1, r2, w, iw, info )
646  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
647  infot = 3
648  CALL dppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
649  $ r1, r2, w, iw, info )
650  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
651  infot = 4
652  CALL dppsvx( 'N', 'U', 0, -1, 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 = 7
656  eq = '/'
657  CALL dppsvx( 'F', 'U', 0, 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 = 8
661  eq = 'Y'
662  CALL dppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
663  $ r1, r2, w, iw, info )
664  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
665  infot = 10
666  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
667  $ r1, r2, w, iw, info )
668  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
669  infot = 12
670  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
671  $ r1, r2, w, iw, info )
672  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
673 *
674  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
675 *
676 * DPBSV
677 *
678  srnamt = 'DPBSV '
679  infot = 1
680  CALL dpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
681  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
682  infot = 2
683  CALL dpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
684  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
685  infot = 3
686  CALL dpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
687  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
688  infot = 4
689  CALL dpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
690  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
691  infot = 6
692  CALL dpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
693  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
694  infot = 8
695  CALL dpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
696  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
697 *
698 * DPBSVX
699 *
700  srnamt = 'DPBSVX'
701  infot = 1
702  CALL dpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
703  $ rcond, r1, r2, w, iw, info )
704  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
705  infot = 2
706  CALL dpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
707  $ rcond, r1, r2, w, iw, info )
708  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
709  infot = 3
710  CALL dpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
711  $ 1, rcond, r1, r2, w, iw, info )
712  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
713  infot = 4
714  CALL dpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
715  $ 1, rcond, r1, r2, w, iw, info )
716  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
717  infot = 5
718  CALL dpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
719  $ 1, rcond, r1, r2, w, iw, info )
720  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
721  infot = 7
722  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
723  $ rcond, r1, r2, w, iw, info )
724  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
725  infot = 9
726  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
727  $ rcond, r1, r2, w, iw, info )
728  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
729  infot = 10
730  eq = '/'
731  CALL dpbsvx( 'F', 'U', 0, 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 = 11
735  eq = 'Y'
736  CALL dpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
737  $ rcond, r1, r2, w, iw, info )
738  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
739  infot = 13
740  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
741  $ rcond, r1, r2, w, iw, info )
742  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
743  infot = 15
744  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
745  $ rcond, r1, r2, w, iw, info )
746  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
747 *
748  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
749 *
750 * DPTSV
751 *
752  srnamt = 'DPTSV '
753  infot = 1
754  CALL dptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
755  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
756  infot = 2
757  CALL dptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
758  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
759  infot = 6
760  CALL dptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
761  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
762 *
763 * DPTSVX
764 *
765  srnamt = 'DPTSVX'
766  infot = 1
767  CALL dptsvx( '/', 0, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
768  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
769  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
770  infot = 2
771  CALL dptsvx( 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
772  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
773  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
774  infot = 3
775  CALL dptsvx( 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
776  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
777  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
778  infot = 9
779  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
780  $ af( 1, 2 ), b, 1, x, 2, rcond, r1, r2, w, info )
781  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
782  infot = 11
783  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
784  $ af( 1, 2 ), b, 2, x, 1, rcond, r1, r2, w, info )
785  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
786 *
787  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
788 *
789 * DSYSV
790 *
791  srnamt = 'DSYSV '
792  infot = 1
793  CALL dsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
794  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
795  infot = 2
796  CALL dsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
797  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
798  infot = 3
799  CALL dsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
800  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
801  infot = 5
802  CALL dsysv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
803  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
804  infot = 8
805  CALL dsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
806  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
807  infot = 10
808  CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
809  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
810  infot = 10
811  CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
812  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
813 *
814 * DSYSVX
815 *
816  srnamt = 'DSYSVX'
817  infot = 1
818  CALL dsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
819  $ rcond, r1, r2, w, 1, iw, info )
820  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
821  infot = 2
822  CALL dsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
823  $ rcond, r1, r2, w, 1, iw, info )
824  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
825  infot = 3
826  CALL dsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
827  $ rcond, r1, r2, w, 1, iw, info )
828  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
829  infot = 4
830  CALL dsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
831  $ rcond, r1, r2, w, 1, iw, info )
832  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
833  infot = 6
834  CALL dsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
835  $ rcond, r1, r2, w, 4, iw, info )
836  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
837  infot = 8
838  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
839  $ rcond, r1, r2, w, 4, iw, info )
840  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
841  infot = 11
842  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
843  $ rcond, r1, r2, w, 4, iw, info )
844  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
845  infot = 13
846  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
847  $ rcond, r1, r2, w, 4, iw, info )
848  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
849  infot = 18
850  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
851  $ rcond, r1, r2, w, 3, iw, info )
852  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
853 *
854 * DSYSVXX
855 *
856  n_err_bnds = 3
857  nparams = 1
858  srnamt = 'DSYSVXX'
859  infot = 1
860  eq = 'N'
861  CALL dsysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
862  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
863  $ err_bnds_c, nparams, params, w, iw, info )
864  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
865  infot = 2
866  CALL dsysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
867  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
868  $ err_bnds_c, nparams, params, w, iw, info )
869  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
870  infot = 3
871  CALL dsysvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
872  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
873  $ err_bnds_c, nparams, params, w, iw, info )
874  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
875  infot = 4
876  eq = '/'
877  CALL dsysvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, r, b, 1, x,
878  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
879  $ err_bnds_c, nparams, params, w, iw, info )
880  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
881  eq = 'Y'
882  infot = 6
883  CALL dsysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
884  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
885  $ err_bnds_c, nparams, params, w, iw, info )
886  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
887  infot = 8
888  CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
889  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
890  $ err_bnds_c, nparams, params, w, iw, info )
891  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
892  infot = 10
893  CALL dsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, 'A', r, b, 2, x,
894  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
895  $ err_bnds_c, nparams, params, w, iw, info )
896  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
897  infot = 11
898  eq='Y'
899  CALL dsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
900  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
901  $ err_bnds_c, nparams, params, w, iw, info )
902  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
903  infot = 11
904  eq='Y'
905  r(1) = -one
906  CALL dsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
907  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
908  $ err_bnds_c, nparams, params, w, iw, info )
909  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
910  infot = 13
911  eq = 'N'
912  CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, x,
913  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
914  $ err_bnds_c, nparams, params, w, iw, info )
915  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
916  infot = 15
917  CALL dsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
918  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
919  $ err_bnds_c, nparams, params, w, iw, info )
920  CALL chkxer( 'DSYSVXX', infot, nout, lerr, ok )
921 *
922  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
923 *
924 * DSYSV_ROOK
925 *
926  srnamt = 'DSYSV_ROOK'
927  infot = 1
928  CALL dsysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
929  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
930  infot = 2
931  CALL dsysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
932  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
933  infot = 3
934  CALL dsysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
935  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
936  infot = 5
937  CALL dsysv_rook( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
938  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
939  infot = 8
940  CALL dsysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, 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, 0, info )
944  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
945  infot = 10
946  CALL dsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
947  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
948 *
949  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
950 *
951 * DSYSV_RK
952 *
953 * Test error exits of the driver that uses factorization
954 * of a symmetric indefinite matrix with rook
955 * (bounded Bunch-Kaufman) pivoting with the new storage
956 * format for factors L ( or U) and D.
957 *
958 * L (or U) is stored in A, diagonal of D is stored on the
959 * diagonal of A, subdiagonal of D is stored in a separate array E.
960 *
961  srnamt = 'DSYSV_RK'
962  infot = 1
963  CALL dsysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
964  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
965  infot = 2
966  CALL dsysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
967  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
968  infot = 3
969  CALL dsysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
970  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
971  infot = 5
972  CALL dsysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
973  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
974  infot = 9
975  CALL dsysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, 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, 0, info )
979  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
980  infot = 11
981  CALL dsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
982  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
983 *
984  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
985 *
986 * DSPSV
987 *
988  srnamt = 'DSPSV '
989  infot = 1
990  CALL dspsv( '/', 0, 0, a, ip, b, 1, info )
991  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
992  infot = 2
993  CALL dspsv( 'U', -1, 0, a, ip, b, 1, info )
994  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
995  infot = 3
996  CALL dspsv( 'U', 0, -1, a, ip, b, 1, info )
997  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
998  infot = 7
999  CALL dspsv( 'U', 2, 0, a, ip, b, 1, info )
1000  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
1001 *
1002 * DSPSVX
1003 *
1004  srnamt = 'DSPSVX'
1005  infot = 1
1006  CALL dspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1007  $ r2, w, iw, info )
1008  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1009  infot = 2
1010  CALL dspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1011  $ r2, w, iw, info )
1012  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1013  infot = 3
1014  CALL dspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1015  $ r2, w, iw, info )
1016  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1017  infot = 4
1018  CALL dspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1019  $ r2, w, iw, info )
1020  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1021  infot = 9
1022  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1023  $ r2, w, iw, info )
1024  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1025  infot = 11
1026  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1027  $ r2, w, iw, info )
1028  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
1029  END IF
1030 *
1031 * Print a summary line.
1032 *
1033  IF( ok ) THEN
1034  WRITE( nout, fmt = 9999 )path
1035  ELSE
1036  WRITE( nout, fmt = 9998 )path
1037  END IF
1038 *
1039  9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
1040  9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
1041  $ 'exits ***' )
1042 *
1043  RETURN
1044 *
1045 * End of DERRVX
1046 *
1047  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 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 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:542
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
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
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:562
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 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:507
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
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:496