LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
serrvx.f
Go to the documentation of this file.
1 *> \brief \b SERRVX
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 April 2012
52 *
53 *> \ingroup single_lin
54 *
55 * =====================================================================
56  SUBROUTINE serrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.4.1) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * April 2012
62 *
63 * .. Scalar Arguments ..
64  CHARACTER*3 path
65  INTEGER nunit
66 * ..
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71  INTEGER nmax
72  parameter( nmax = 4 )
73 * ..
74 * .. Local Scalars ..
75  CHARACTER eq
76  CHARACTER*2 c2
77  INTEGER i, info, j
78  REAL rcond
79 * ..
80 * .. Local Arrays ..
81  INTEGER ip( nmax ), iw( nmax )
82  REAL a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
83  $ c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
84  $ w( 2*nmax ), x( nmax )
85 * ..
86 * .. External Functions ..
87  LOGICAL lsamen
88  EXTERNAL lsamen
89 * ..
90 * .. External Subroutines ..
91  EXTERNAL chkxer, sgbsv, sgbsvx, sgesv, sgesvx, sgtsv,
94  $ ssysvx
95 * ..
96 * .. Scalars in Common ..
97  LOGICAL lerr, ok
98  CHARACTER*32 srnamt
99  INTEGER infot, nout
100 * ..
101 * .. Common blocks ..
102  common / infoc / infot, nout, ok, lerr
103  common / srnamc / srnamt
104 * ..
105 * .. Intrinsic Functions ..
106  INTRINSIC real
107 * ..
108 * .. Executable Statements ..
109 *
110  nout = nunit
111  WRITE( nout, fmt = * )
112  c2 = path( 2: 3 )
113 *
114 * Set the variables to innocuous values.
115 *
116  DO 20 j = 1, nmax
117  DO 10 i = 1, nmax
118  a( i, j ) = 1. / REAL( i+j )
119  af( i, j ) = 1. / REAL( i+j )
120  10 continue
121  b( j ) = 0.
122  r1( j ) = 0.
123  r2( j ) = 0.
124  w( j ) = 0.
125  x( j ) = 0.
126  c( j ) = 0.
127  r( j ) = 0.
128  ip( j ) = j
129  20 continue
130  eq = ' '
131  ok = .true.
132 *
133  IF( lsamen( 2, c2, 'GE' ) ) THEN
134 *
135 * SGESV
136 *
137  srnamt = 'SGESV '
138  infot = 1
139  CALL sgesv( -1, 0, a, 1, ip, b, 1, info )
140  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
141  infot = 2
142  CALL sgesv( 0, -1, a, 1, ip, b, 1, info )
143  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
144  infot = 4
145  CALL sgesv( 2, 1, a, 1, ip, b, 2, info )
146  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
147  infot = 7
148  CALL sgesv( 2, 1, a, 2, ip, b, 1, info )
149  CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
150 *
151 * SGESVX
152 *
153  srnamt = 'SGESVX'
154  infot = 1
155  CALL sgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
156  $ x, 1, rcond, r1, r2, w, iw, info )
157  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
158  infot = 2
159  CALL sgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
160  $ x, 1, rcond, r1, r2, w, iw, info )
161  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
162  infot = 3
163  CALL sgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
164  $ x, 1, rcond, r1, r2, w, iw, info )
165  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
166  infot = 4
167  CALL sgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
168  $ x, 1, rcond, r1, r2, w, iw, info )
169  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
170  infot = 6
171  CALL sgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
172  $ x, 2, rcond, r1, r2, w, iw, info )
173  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
174  infot = 8
175  CALL sgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
176  $ x, 2, rcond, r1, r2, w, iw, info )
177  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
178  infot = 10
179  eq = '/'
180  CALL sgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
181  $ x, 1, rcond, r1, r2, w, iw, info )
182  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
183  infot = 11
184  eq = 'R'
185  CALL sgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
186  $ x, 1, rcond, r1, r2, w, iw, info )
187  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
188  infot = 12
189  eq = 'C'
190  CALL sgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
191  $ x, 1, rcond, r1, r2, w, iw, info )
192  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
193  infot = 14
194  CALL sgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
195  $ x, 2, rcond, r1, r2, w, iw, info )
196  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
197  infot = 16
198  CALL sgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
199  $ x, 1, rcond, r1, r2, w, iw, info )
200  CALL chkxer( 'SGESVX', infot, nout, lerr, ok )
201 *
202  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
203 *
204 * SGBSV
205 *
206  srnamt = 'SGBSV '
207  infot = 1
208  CALL sgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
209  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
210  infot = 2
211  CALL sgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
212  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
213  infot = 3
214  CALL sgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
215  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
216  infot = 4
217  CALL sgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
218  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
219  infot = 6
220  CALL sgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
221  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
222  infot = 9
223  CALL sgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
224  CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
225 *
226 * SGBSVX
227 *
228  srnamt = 'SGBSVX'
229  infot = 1
230  CALL sgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
231  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
232  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
233  infot = 2
234  CALL sgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
235  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
236  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
237  infot = 3
238  CALL sgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
239  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
240  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
241  infot = 4
242  CALL sgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
243  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
244  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
245  infot = 5
246  CALL sgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
247  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
248  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
249  infot = 6
250  CALL sgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
251  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
252  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
253  infot = 8
254  CALL sgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
255  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
256  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
257  infot = 10
258  CALL sgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
259  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
260  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
261  infot = 12
262  eq = '/'
263  CALL sgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
264  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
265  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
266  infot = 13
267  eq = 'R'
268  CALL sgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
269  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
270  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
271  infot = 14
272  eq = 'C'
273  CALL sgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
274  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
275  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
276  infot = 16
277  CALL sgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
278  $ b, 1, x, 2, rcond, r1, r2, w, iw, info )
279  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
280  infot = 18
281  CALL sgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
282  $ b, 2, x, 1, rcond, r1, r2, w, iw, info )
283  CALL chkxer( 'SGBSVX', infot, nout, lerr, ok )
284 *
285  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
286 *
287 * SGTSV
288 *
289  srnamt = 'SGTSV '
290  infot = 1
291  CALL sgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
292  $ info )
293  CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
294  infot = 2
295  CALL sgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
296  $ info )
297  CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
298  infot = 7
299  CALL sgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
300  CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
301 *
302 * SGTSVX
303 *
304  srnamt = 'SGTSVX'
305  infot = 1
306  CALL sgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
307  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
308  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
309  CALL chkxer( 'SGTSVX', infot, nout, lerr, ok )
310  infot = 2
311  CALL sgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
312  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
313  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
314  CALL chkxer( 'SGTSVX', infot, nout, lerr, ok )
315  infot = 3
316  CALL sgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
317  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
318  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
319  CALL chkxer( 'SGTSVX', infot, nout, lerr, ok )
320  infot = 4
321  CALL sgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
322  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
323  $ ip, b, 1, x, 1, rcond, r1, r2, w, iw, info )
324  CALL chkxer( 'SGTSVX', infot, nout, lerr, ok )
325  infot = 14
326  CALL sgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
327  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
328  $ ip, b, 1, x, 2, rcond, r1, r2, w, iw, info )
329  CALL chkxer( 'SGTSVX', infot, nout, lerr, ok )
330  infot = 16
331  CALL sgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
332  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
333  $ ip, b, 2, x, 1, rcond, r1, r2, w, iw, info )
334  CALL chkxer( 'SGTSVX', infot, nout, lerr, ok )
335 *
336  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
337 *
338 * SPOSV
339 *
340  srnamt = 'SPOSV '
341  infot = 1
342  CALL sposv( '/', 0, 0, a, 1, b, 1, info )
343  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
344  infot = 2
345  CALL sposv( 'U', -1, 0, a, 1, b, 1, info )
346  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
347  infot = 3
348  CALL sposv( 'U', 0, -1, a, 1, b, 1, info )
349  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
350  infot = 5
351  CALL sposv( 'U', 2, 0, a, 1, b, 2, info )
352  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
353  infot = 7
354  CALL sposv( 'U', 2, 0, a, 2, b, 1, info )
355  CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
356 *
357 * SPOSVX
358 *
359  srnamt = 'SPOSVX'
360  infot = 1
361  CALL sposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
362  $ rcond, r1, r2, w, iw, info )
363  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
364  infot = 2
365  CALL sposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
366  $ rcond, r1, r2, w, iw, info )
367  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
368  infot = 3
369  CALL sposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
370  $ rcond, r1, r2, w, iw, info )
371  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
372  infot = 4
373  CALL sposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
374  $ rcond, r1, r2, w, iw, info )
375  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
376  infot = 6
377  CALL sposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
378  $ rcond, r1, r2, w, iw, info )
379  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
380  infot = 8
381  CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
382  $ rcond, r1, r2, w, iw, info )
383  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
384  infot = 9
385  eq = '/'
386  CALL sposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
387  $ rcond, r1, r2, w, iw, info )
388  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
389  infot = 10
390  eq = 'Y'
391  CALL sposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
392  $ rcond, r1, r2, w, iw, info )
393  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
394  infot = 12
395  CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
396  $ rcond, r1, r2, w, iw, info )
397  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
398  infot = 14
399  CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
400  $ rcond, r1, r2, w, iw, info )
401  CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
402 *
403  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
404 *
405 * SPPSV
406 *
407  srnamt = 'SPPSV '
408  infot = 1
409  CALL sppsv( '/', 0, 0, a, b, 1, info )
410  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
411  infot = 2
412  CALL sppsv( 'U', -1, 0, a, b, 1, info )
413  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
414  infot = 3
415  CALL sppsv( 'U', 0, -1, a, b, 1, info )
416  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
417  infot = 6
418  CALL sppsv( 'U', 2, 0, a, b, 1, info )
419  CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
420 *
421 * SPPSVX
422 *
423  srnamt = 'SPPSVX'
424  infot = 1
425  CALL sppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
426  $ r1, r2, w, iw, info )
427  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
428  infot = 2
429  CALL sppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
430  $ r1, r2, w, iw, info )
431  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
432  infot = 3
433  CALL sppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
434  $ r1, r2, w, iw, info )
435  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
436  infot = 4
437  CALL sppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
438  $ r1, r2, w, iw, info )
439  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
440  infot = 7
441  eq = '/'
442  CALL sppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
443  $ r1, r2, w, iw, info )
444  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
445  infot = 8
446  eq = 'Y'
447  CALL sppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
448  $ r1, r2, w, iw, info )
449  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
450  infot = 10
451  CALL sppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
452  $ r1, r2, w, iw, info )
453  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
454  infot = 12
455  CALL sppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
456  $ r1, r2, w, iw, info )
457  CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
458 *
459  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
460 *
461 * SPBSV
462 *
463  srnamt = 'SPBSV '
464  infot = 1
465  CALL spbsv( '/', 0, 0, 0, a, 1, b, 1, info )
466  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
467  infot = 2
468  CALL spbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
469  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
470  infot = 3
471  CALL spbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
472  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
473  infot = 4
474  CALL spbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
475  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
476  infot = 6
477  CALL spbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
478  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
479  infot = 8
480  CALL spbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
481  CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
482 *
483 * SPBSVX
484 *
485  srnamt = 'SPBSVX'
486  infot = 1
487  CALL spbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
488  $ rcond, r1, r2, w, iw, info )
489  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
490  infot = 2
491  CALL spbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
492  $ rcond, r1, r2, w, iw, info )
493  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
494  infot = 3
495  CALL spbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
496  $ 1, rcond, r1, r2, w, iw, info )
497  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
498  infot = 4
499  CALL spbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
500  $ 1, rcond, r1, r2, w, iw, info )
501  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
502  infot = 5
503  CALL spbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
504  $ 1, rcond, r1, r2, w, iw, info )
505  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
506  infot = 7
507  CALL spbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
508  $ rcond, r1, r2, w, iw, info )
509  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
510  infot = 9
511  CALL spbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
512  $ rcond, r1, r2, w, iw, info )
513  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
514  infot = 10
515  eq = '/'
516  CALL spbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
517  $ rcond, r1, r2, w, iw, info )
518  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
519  infot = 11
520  eq = 'Y'
521  CALL spbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
522  $ rcond, r1, r2, w, iw, info )
523  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
524  infot = 13
525  CALL spbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
526  $ rcond, r1, r2, w, iw, info )
527  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
528  infot = 15
529  CALL spbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
530  $ rcond, r1, r2, w, iw, info )
531  CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
532 *
533  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
534 *
535 * SPTSV
536 *
537  srnamt = 'SPTSV '
538  infot = 1
539  CALL sptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
540  CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
541  infot = 2
542  CALL sptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
543  CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
544  infot = 6
545  CALL sptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
546  CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
547 *
548 * SPTSVX
549 *
550  srnamt = 'SPTSVX'
551  infot = 1
552  CALL sptsvx( '/', 0, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
553  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
554  CALL chkxer( 'SPTSVX', infot, nout, lerr, ok )
555  infot = 2
556  CALL sptsvx( 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
557  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
558  CALL chkxer( 'SPTSVX', infot, nout, lerr, ok )
559  infot = 3
560  CALL sptsvx( 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
561  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
562  CALL chkxer( 'SPTSVX', infot, nout, lerr, ok )
563  infot = 9
564  CALL sptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
565  $ af( 1, 2 ), b, 1, x, 2, rcond, r1, r2, w, info )
566  CALL chkxer( 'SPTSVX', infot, nout, lerr, ok )
567  infot = 11
568  CALL sptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
569  $ af( 1, 2 ), b, 2, x, 1, rcond, r1, r2, w, info )
570  CALL chkxer( 'SPTSVX', infot, nout, lerr, ok )
571 *
572  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
573 *
574 * SSYSV
575 *
576  srnamt = 'SSYSV '
577  infot = 1
578  CALL ssysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
579  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
580  infot = 2
581  CALL ssysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
582  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
583  infot = 3
584  CALL ssysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
585  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
586  infot = 8
587  CALL ssysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
588  CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
589 *
590 * SSYSVX
591 *
592  srnamt = 'SSYSVX'
593  infot = 1
594  CALL ssysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
595  $ rcond, r1, r2, w, 1, iw, info )
596  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
597  infot = 2
598  CALL ssysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
599  $ rcond, r1, r2, w, 1, iw, info )
600  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
601  infot = 3
602  CALL ssysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
603  $ rcond, r1, r2, w, 1, iw, info )
604  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
605  infot = 4
606  CALL ssysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
607  $ rcond, r1, r2, w, 1, iw, info )
608  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
609  infot = 6
610  CALL ssysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
611  $ rcond, r1, r2, w, 4, iw, info )
612  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
613  infot = 8
614  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
615  $ rcond, r1, r2, w, 4, iw, info )
616  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
617  infot = 11
618  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
619  $ rcond, r1, r2, w, 4, iw, info )
620  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
621  infot = 13
622  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
623  $ rcond, r1, r2, w, 4, iw, info )
624  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
625  infot = 18
626  CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
627  $ rcond, r1, r2, w, 3, iw, info )
628  CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
629 *
630  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
631 *
632 * SSPSV
633 *
634  srnamt = 'SSPSV '
635  infot = 1
636  CALL sspsv( '/', 0, 0, a, ip, b, 1, info )
637  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
638  infot = 2
639  CALL sspsv( 'U', -1, 0, a, ip, b, 1, info )
640  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
641  infot = 3
642  CALL sspsv( 'U', 0, -1, a, ip, b, 1, info )
643  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
644  infot = 7
645  CALL sspsv( 'U', 2, 0, a, ip, b, 1, info )
646  CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
647 *
648 * SSPSVX
649 *
650  srnamt = 'SSPSVX'
651  infot = 1
652  CALL sspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
653  $ r2, w, iw, info )
654  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
655  infot = 2
656  CALL sspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
657  $ r2, w, iw, info )
658  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
659  infot = 3
660  CALL sspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
661  $ r2, w, iw, info )
662  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
663  infot = 4
664  CALL sspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
665  $ r2, w, iw, info )
666  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
667  infot = 9
668  CALL sspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
669  $ r2, w, iw, info )
670  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
671  infot = 11
672  CALL sspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
673  $ r2, w, iw, info )
674  CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
675  END IF
676 *
677 * Print a summary line.
678 *
679  IF( ok ) THEN
680  WRITE( nout, fmt = 9999 )path
681  ELSE
682  WRITE( nout, fmt = 9998 )path
683  END IF
684 *
685  9999 format( 1x, a3, ' drivers passed the tests of the error exits' )
686  9998 format( ' *** ', a3, ' drivers failed the tests of the error ',
687  $ 'exits ***' )
688 *
689  return
690 *
691 * End of SERRVX
692 *
693  END