LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
serrvxx.f
Go to the documentation of this file.
1 *> \brief \b SERRVXX
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 SERRVX( 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 *> SERRVX tests the error exits for the REAL 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 single_lin
54 *
55 * =====================================================================
56  SUBROUTINE serrvx( 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.0e+0 )
75 * ..
76 * .. Local Scalars ..
77  CHARACTER eq
78  CHARACTER*2 c2
79  INTEGER i, info, j, n_err_bnds, nparams
80  REAL rcond, rpvgrw, berr
81 * ..
82 * .. Local Arrays ..
83  INTEGER ip( nmax ), iw( nmax )
84  REAL 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, sgbsv, sgbsvx, sgesv, sgesvx, sgtsv,
99  $ sposvxx, sgbsvxx
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 real
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. / REAL( i+j )
124  af( i, j ) = 1. / REAL( i+j )
125  10 CONTINUE
126  b( j ) = 0.e+0
127  e( j ) = 0.e+0
128  r1( j ) = 0.e+0
129  r2( j ) = 0.e+0
130  w( j ) = 0.e+0
131  x( j ) = 0.e+0
132  c( j ) = 0.e+0
133  r( j ) = 0.e+0
134  ip( j ) = j
135  20 CONTINUE
136  eq = ' '
137  ok = .true.
138 *
139  IF( lsamen( 2, c2, 'GE' ) ) THEN
140 *
141 * SGESV
142 *
143  srnamt = 'SGESV '
144  infot = 1
145  CALL sgesv( -1, 0, a, 1, ip, b, 1, info )
146  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
147  infot = 2
148  CALL sgesv( 0, -1, a, 1, ip, b, 1, info )
149  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
150  infot = 4
151  CALL sgesv( 2, 1, a, 1, ip, b, 2, info )
152  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
153  infot = 7
154  CALL sgesv( 2, 1, a, 2, ip, b, 1, info )
155  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
156 *
157 * SGESVX
158 *
159  srnamt = 'SGESVX'
160  infot = 1
161  CALL sgesvx( '/', '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( 'SGESVX', infot, nout, lerr, ok )
164  infot = 2
165  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
168  infot = 3
169  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
172  infot = 4
173  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
176  infot = 6
177  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
180  infot = 8
181  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
184  infot = 10
185  eq = '/'
186  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
189  infot = 11
190  eq = 'R'
191  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
194  infot = 12
195  eq = 'C'
196  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
199  infot = 14
200  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
203  infot = 16
204  CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
207 *
208 * SGESVXX
209 *
210  n_err_bnds = 3
211  nparams = 1
212  srnamt = 'SGESVXX'
213  infot = 1
214  CALL sgesvxx( '/', '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( 'SGESVXX', infot, nout, lerr, ok )
218  infot = 2
219  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
223  infot = 3
224  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
228  infot = 4
229  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
233  infot = 6
234  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
238  infot = 8
239  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
243  infot = 10
244  eq = '/'
245  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
249  infot = 11
250  eq = 'R'
251  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
255  infot = 12
256  eq = 'C'
257  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
261  infot = 14
262  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
266  infot = 16
267  CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
271 *
272  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
273 *
274 * SGBSV
275 *
276  srnamt = 'SGBSV '
277  infot = 1
278  CALL sgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
279  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
280  infot = 2
281  CALL sgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
282  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
283  infot = 3
284  CALL sgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
285  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
286  infot = 4
287  CALL sgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
288  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
289  infot = 6
290  CALL sgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
291  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
292  infot = 9
293  CALL sgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
294  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
295 *
296 * SGBSVX
297 *
298  srnamt = 'SGBSVX'
299  infot = 1
300  CALL sgbsvx( '/', '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( 'SGBSVX', infot, nout, lerr, ok )
303  infot = 2
304  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
307  infot = 3
308  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
311  infot = 4
312  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
315  infot = 5
316  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
319  infot = 6
320  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
323  infot = 8
324  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
327  infot = 10
328  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
331  infot = 12
332  eq = '/'
333  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
336  infot = 13
337  eq = 'R'
338  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
341  infot = 14
342  eq = 'C'
343  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
346  infot = 16
347  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
350  infot = 18
351  CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
354 *
355 * SGBSVXX
356 *
357  n_err_bnds = 3
358  nparams = 1
359  srnamt = 'SGBSVXX'
360  infot = 1
361  CALL sgbsvxx( '/', '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( 'SGBSVXX', infot, nout, lerr, ok )
366  infot = 2
367  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
372  infot = 3
373  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
378  infot = 4
379  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
384  infot = 5
385  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
390  infot = 6
391  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
396  infot = 8
397  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
402  infot = 10
403  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
408  infot = 12
409  eq = '/'
410  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
415  infot = 13
416  eq = 'R'
417  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
422  infot = 14
423  eq = 'C'
424  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
429  infot = 15
430  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
435  infot = 16
436  CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
441 *
442  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
443 *
444 * SGTSV
445 *
446  srnamt = 'SGTSV '
447  infot = 1
448  CALL sgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
449  $ info )
450  CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
451  infot = 2
452  CALL sgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
453  $ info )
454  CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
455  infot = 7
456  CALL sgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
457  CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
458 *
459 * SGTSVX
460 *
461  srnamt = 'SGTSVX'
462  infot = 1
463  CALL sgtsvx( '/', '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( 'SGTSVX', infot, nout, lerr, ok )
467  infot = 2
468  CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
472  infot = 3
473  CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
477  infot = 4
478  CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
482  infot = 14
483  CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
487  infot = 16
488  CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
492 *
493  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
494 *
495 * SPOSV
496 *
497  srnamt = 'SPOSV '
498  infot = 1
499  CALL sposv( '/', 0, 0, a, 1, b, 1, info )
500  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
501  infot = 2
502  CALL sposv( 'U', -1, 0, a, 1, b, 1, info )
503  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
504  infot = 3
505  CALL sposv( 'U', 0, -1, a, 1, b, 1, info )
506  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
507  infot = 5
508  CALL sposv( 'U', 2, 0, a, 1, b, 2, info )
509  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
510  infot = 7
511  CALL sposv( 'U', 2, 0, a, 2, b, 1, info )
512  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
513 *
514 * SPOSVX
515 *
516  srnamt = 'SPOSVX'
517  infot = 1
518  CALL sposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
519  $ rcond, r1, r2, w, iw, info )
520  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
521  infot = 2
522  CALL sposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
523  $ rcond, r1, r2, w, iw, info )
524  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
525  infot = 3
526  CALL sposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
527  $ rcond, r1, r2, w, iw, info )
528  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
529  infot = 4
530  CALL sposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
531  $ rcond, r1, r2, w, iw, info )
532  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
533  infot = 6
534  CALL sposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
535  $ rcond, r1, r2, w, iw, info )
536  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
537  infot = 8
538  CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
539  $ rcond, r1, r2, w, iw, info )
540  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
541  infot = 9
542  eq = '/'
543  CALL sposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
544  $ rcond, r1, r2, w, iw, info )
545  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
546  infot = 10
547  eq = 'Y'
548  CALL sposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
549  $ rcond, r1, r2, w, iw, info )
550  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
551  infot = 12
552  CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
553  $ rcond, r1, r2, w, iw, info )
554  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
555  infot = 14
556  CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
557  $ rcond, r1, r2, w, iw, info )
558  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
559 *
560 * SPOSVXX
561 *
562  n_err_bnds = 3
563  nparams = 1
564  srnamt = 'SPOSVXX'
565  infot = 1
566  CALL sposvxx( '/', '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( 'SPOSVXX', infot, nout, lerr, ok )
570  infot = 2
571  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
575  infot = 3
576  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
580  infot = 4
581  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
585  infot = 6
586  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
590  infot = 8
591  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
595  infot = 9
596  eq = '/'
597  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
601  infot = 10
602  eq = 'Y'
603  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
607  infot = 12
608  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
612  infot = 14
613  CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
617 *
618  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
619 *
620 * SPPSV
621 *
622  srnamt = 'SPPSV '
623  infot = 1
624  CALL sppsv( '/', 0, 0, a, b, 1, info )
625  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
626  infot = 2
627  CALL sppsv( 'U', -1, 0, a, b, 1, info )
628  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
629  infot = 3
630  CALL sppsv( 'U', 0, -1, a, b, 1, info )
631  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
632  infot = 6
633  CALL sppsv( 'U', 2, 0, a, b, 1, info )
634  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
635 *
636 * SPPSVX
637 *
638  srnamt = 'SPPSVX'
639  infot = 1
640  CALL sppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
641  $ r1, r2, w, iw, info )
642  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
643  infot = 2
644  CALL sppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
645  $ r1, r2, w, iw, info )
646  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
647  infot = 3
648  CALL sppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
649  $ r1, r2, w, iw, info )
650  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
651  infot = 4
652  CALL sppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
653  $ r1, r2, w, iw, info )
654  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
655  infot = 7
656  eq = '/'
657  CALL sppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
658  $ r1, r2, w, iw, info )
659  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
660  infot = 8
661  eq = 'Y'
662  CALL sppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
663  $ r1, r2, w, iw, info )
664  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
665  infot = 10
666  CALL sppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
667  $ r1, r2, w, iw, info )
668  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
669  infot = 12
670  CALL sppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
671  $ r1, r2, w, iw, info )
672  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
673 *
674  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
675 *
676 * SPBSV
677 *
678  srnamt = 'SPBSV '
679  infot = 1
680  CALL spbsv( '/', 0, 0, 0, a, 1, b, 1, info )
681  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
682  infot = 2
683  CALL spbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
684  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
685  infot = 3
686  CALL spbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
687  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
688  infot = 4
689  CALL spbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
690  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
691  infot = 6
692  CALL spbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
693  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
694  infot = 8
695  CALL spbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
696  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
697 *
698 * SPBSVX
699 *
700  srnamt = 'SPBSVX'
701  infot = 1
702  CALL spbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
703  $ rcond, r1, r2, w, iw, info )
704  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
705  infot = 2
706  CALL spbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
707  $ rcond, r1, r2, w, iw, info )
708  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
709  infot = 3
710  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
713  infot = 4
714  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
717  infot = 5
718  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
721  infot = 7
722  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
725  infot = 9
726  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
729  infot = 10
730  eq = '/'
731  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
734  infot = 11
735  eq = 'Y'
736  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
739  infot = 13
740  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
743  infot = 15
744  CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
747 *
748  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
749 *
750 * SPTSV
751 *
752  srnamt = 'SPTSV '
753  infot = 1
754  CALL sptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
755  CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
756  infot = 2
757  CALL sptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
758  CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
759  infot = 6
760  CALL sptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
761  CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
762 *
763 * SPTSVX
764 *
765  srnamt = 'SPTSVX'
766  infot = 1
767  CALL sptsvx( '/', 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( 'SPTSVX', infot, nout, lerr, ok )
770  infot = 2
771  CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
774  infot = 3
775  CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
778  infot = 9
779  CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
782  infot = 11
783  CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
786 *
787  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
788 *
789 * SSYSV
790 *
791  srnamt = 'SSYSV '
792  infot = 1
793  CALL ssysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
794  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
795  infot = 2
796  CALL ssysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
797  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
798  infot = 3
799  CALL ssysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
800  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
801  infot = 8
802  CALL ssysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
803  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
804  infot = 10
805  CALL ssysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
806  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
807  infot = 10
808  CALL ssysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
809  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
810 *
811 * SSYSVX
812 *
813  srnamt = 'SSYSVX'
814  infot = 1
815  CALL ssysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
816  $ rcond, r1, r2, w, 1, iw, info )
817  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
818  infot = 2
819  CALL ssysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
820  $ rcond, r1, r2, w, 1, iw, info )
821  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
822  infot = 3
823  CALL ssysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
824  $ rcond, r1, r2, w, 1, iw, info )
825  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
826  infot = 4
827  CALL ssysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
828  $ rcond, r1, r2, w, 1, iw, info )
829  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
830  infot = 6
831  CALL ssysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
832  $ rcond, r1, r2, w, 4, iw, info )
833  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
834  infot = 8
835  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
836  $ rcond, r1, r2, w, 4, iw, info )
837  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
838  infot = 11
839  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
840  $ rcond, r1, r2, w, 4, iw, info )
841  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
842  infot = 13
843  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
844  $ rcond, r1, r2, w, 4, iw, info )
845  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
846  infot = 18
847  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
848  $ rcond, r1, r2, w, 3, iw, info )
849  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
850 *
851 * SSYSVXX
852 *
853  n_err_bnds = 3
854  nparams = 1
855  srnamt = 'SSYSVXX'
856  infot = 1
857  eq = 'N'
858  CALL ssysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
859  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
860  $ err_bnds_c, nparams, params, w, iw, info )
861  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
862  infot = 2
863  CALL ssysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
864  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
865  $ err_bnds_c, nparams, params, w, iw, info )
866  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
867  infot = 3
868  CALL ssysvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
869  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
870  $ err_bnds_c, nparams, params, w, iw, info )
871  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
872  infot = 4
873  eq = '/'
874  CALL ssysvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, r, b, 1, x,
875  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
876  $ err_bnds_c, nparams, params, w, iw, info )
877  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
878  eq = 'Y'
879  infot = 6
880  CALL ssysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
881  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
882  $ err_bnds_c, nparams, params, w, iw, info )
883  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
884  infot = 8
885  CALL ssysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
886  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
887  $ err_bnds_c, nparams, params, w, iw, info )
888  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
889  infot = 10
890  CALL ssysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, 'A', r, b, 2, x,
891  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
892  $ err_bnds_c, nparams, params, w, iw, info )
893  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
894  infot = 11
895  eq='Y'
896  CALL ssysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
897  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
898  $ err_bnds_c, nparams, params, w, iw, info )
899  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
900  infot = 11
901  eq='Y'
902  r(1) = -one
903  CALL ssysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
904  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
905  $ err_bnds_c, nparams, params, w, iw, info )
906  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
907  infot = 13
908  eq = 'N'
909  CALL ssysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, x,
910  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
911  $ err_bnds_c, nparams, params, w, iw, info )
912  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
913  infot = 15
914  CALL ssysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
915  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
916  $ err_bnds_c, nparams, params, w, iw, info )
917  CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
918 *
919  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
920 *
921 * SSYSV_ROOK
922 *
923  srnamt = 'SSYSV_ROOK'
924  infot = 1
925  CALL ssysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
926  CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
927  infot = 2
928  CALL ssysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
929  CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
930  infot = 3
931  CALL ssysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
932  CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
933  infot = 8
934  CALL ssysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
935  CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
936  infot = 10
937  CALL ssysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
938  CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
939  infot = 10
940  CALL ssysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
941  CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
942 *
943  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
944 *
945 * SSYSV_RK
946 *
947 * Test error exits of the driver that uses factorization
948 * of a symmetric indefinite matrix with rook
949 * (bounded Bunch-Kaufman) pivoting with the new storage
950 * format for factors L ( or U) and D.
951 *
952 * L (or U) is stored in A, diagonal of D is stored on the
953 * diagonal of A, subdiagonal of D is stored in a separate array E.
954 *
955  srnamt = 'SSYSV_RK'
956  infot = 1
957  CALL ssysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
958  CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
959  infot = 2
960  CALL ssysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
961  CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
962  infot = 3
963  CALL ssysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
964  CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
965  infot = 5
966  CALL ssysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
967  CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
968  infot = 9
969  CALL ssysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
970  CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
971  infot = 11
972  CALL ssysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
973  CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
974  infot = 11
975  CALL ssysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
976  CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
977 *
978  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
979 *
980 * SSPSV
981 *
982  srnamt = 'SSPSV '
983  infot = 1
984  CALL sspsv( '/', 0, 0, a, ip, b, 1, info )
985  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
986  infot = 2
987  CALL sspsv( 'U', -1, 0, a, ip, b, 1, info )
988  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
989  infot = 3
990  CALL sspsv( 'U', 0, -1, a, ip, b, 1, info )
991  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
992  infot = 7
993  CALL sspsv( 'U', 2, 0, a, ip, b, 1, info )
994  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
995 *
996 * SSPSVX
997 *
998  srnamt = 'SSPSVX'
999  infot = 1
1000  CALL sspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1001  $ r2, w, iw, info )
1002  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1003  infot = 2
1004  CALL sspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1005  $ r2, w, iw, info )
1006  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1007  infot = 3
1008  CALL sspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1009  $ r2, w, iw, info )
1010  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1011  infot = 4
1012  CALL sspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1013  $ r2, w, iw, info )
1014  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1015  infot = 9
1016  CALL sspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1017  $ r2, w, iw, info )
1018  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1019  infot = 11
1020  CALL sspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1021  $ r2, w, iw, info )
1022  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1023  END IF
1024 *
1025 * Print a summary line.
1026 *
1027  IF( ok ) THEN
1028  WRITE( nout, fmt = 9999 )path
1029  ELSE
1030  WRITE( nout, fmt = 9998 )path
1031  END IF
1032 *
1033  9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
1034  9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
1035  $ 'exits ***' )
1036 *
1037  RETURN
1038 *
1039 * End of SERRVX
1040 *
1041  END
subroutine sposvxx(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)
SPOSVXX computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: sposvxx.f:499
subroutine sspsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
SSPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: sspsv.f:164
subroutine sgesv(N, NRHS, A, LDA, IPIV, B, LDB, INFO)
SGESV computes the solution to system of linear equations A * X = B for GE matrices (simple driver) ...
Definition: sgesv.f:124
subroutine sgbsv(N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
SGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver) ...
Definition: sgbsv.f:164
subroutine sgbsvx(FACT, TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SGBSVX computes the solution to system of linear equations A * X = B for GB matrices ...
Definition: sgbsvx.f:370
subroutine sgbsvxx(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)
SGBSVXX computes the solution to system of linear equations A * X = B for GB matrices ...
Definition: sgbsvxx.f:565
subroutine ssysvxx(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)
SSYSVXX
Definition: ssysvxx.f:510
subroutine ssysvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, IWORK, INFO)
SSYSVX computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: ssysvx.f:286
subroutine spbsv(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO)
SPBSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: spbsv.f:166
subroutine sptsv(N, NRHS, D, E, B, LDB, INFO)
SPTSV computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: sptsv.f:116
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine sgesvx(FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SGESVX computes the solution to system of linear equations A * X = B for GE matrices ...
Definition: sgesvx.f:351
subroutine sspsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: sspsvx.f:279
subroutine sptsvx(FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, INFO)
SPTSVX computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: sptsvx.f:230
subroutine sppsv(UPLO, N, NRHS, AP, B, LDB, INFO)
SPPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: sppsv.f:146
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
subroutine sposv(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
SPOSV computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: sposv.f:132
subroutine sppsvx(FACT, UPLO, N, NRHS, AP, AFP, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: sppsvx.f:314
subroutine sgesvxx(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)
SGESVXX computes the solution to system of linear equations A * X = B for GE matrices ...
Definition: sgesvxx.f:545
subroutine ssysv_rk(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, WORK, LWORK, INFO)
SSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: ssysv_rk.f:230
subroutine serrvx(PATH, NUNIT)
SERRVX
Definition: serrvx.f:57
subroutine ssysv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
SSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: ssysv_rook.f:206
subroutine ssysv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
SSYSV computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: ssysv.f:173
subroutine spbsvx(FACT, UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: spbsvx.f:345
subroutine sgtsvx(FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SGTSVX computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: sgtsvx.f:295
subroutine sposvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SPOSVX computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: sposvx.f:309
subroutine sgtsv(N, NRHS, DL, D, DU, B, LDB, INFO)
SGTSV computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: sgtsv.f:129