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