LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
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*> \ingroup single_lin
52*
53* =====================================================================
54 SUBROUTINE serrvx( PATH, NUNIT )
55*
56* -- LAPACK test routine --
57* -- LAPACK is a software package provided by Univ. of Tennessee, --
58* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
59*
60* .. Scalar Arguments ..
61 CHARACTER*3 PATH
62 INTEGER NUNIT
63* ..
64*
65* =====================================================================
66*
67* .. Parameters ..
68 INTEGER NMAX
69 parameter( nmax = 4 )
70 REAL ONE
71 parameter( one = 1.0e+0 )
72* ..
73* .. Local Scalars ..
74 CHARACTER EQ
75 CHARACTER*2 C2
76 INTEGER I, INFO, J, N_ERR_BNDS, NPARAMS
77 REAL RCOND, RPVGRW, BERR
78* ..
79* .. Local Arrays ..
80 INTEGER IP( NMAX ), IW( NMAX )
81 REAL A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
82 $ C( NMAX ), E( NMAX ), R( NMAX ), R1( NMAX ),
83 $ R2( NMAX ), W( 2*NMAX ), X( NMAX ),
84 $ ERR_BNDS_N( NMAX, 3 ), ERR_BNDS_C( NMAX, 3 ),
85 $ PARAMS( 1 )
86* ..
87* .. External Functions ..
88 LOGICAL LSAMEN
89 EXTERNAL lsamen
90* ..
91* .. External Subroutines ..
92 EXTERNAL chkxer, sgbsv, sgbsvx, sgesv, sgesvx, sgtsv,
97* ..
98* .. Scalars in Common ..
99 LOGICAL LERR, OK
100 CHARACTER*32 SRNAMT
101 INTEGER INFOT, NOUT
102* ..
103* .. Common blocks ..
104 COMMON / infoc / infot, nout, ok, lerr
105 COMMON / srnamc / srnamt
106* ..
107* .. Intrinsic Functions ..
108 INTRINSIC real
109* ..
110* .. Executable Statements ..
111*
112 nout = nunit
113 WRITE( nout, fmt = * )
114 c2 = path( 2: 3 )
115*
116* Set the variables to innocuous values.
117*
118 DO 20 j = 1, nmax
119 DO 10 i = 1, nmax
120 a( i, j ) = 1. / real( i+j )
121 af( i, j ) = 1. / real( i+j )
122 10 CONTINUE
123 b( j ) = 0.e+0
124 e( j ) = 0.e+0
125 r1( j ) = 0.e+0
126 r2( j ) = 0.e+0
127 w( j ) = 0.e+0
128 x( j ) = 0.e+0
129 c( j ) = 0.e+0
130 r( j ) = 0.e+0
131 ip( j ) = j
132 20 CONTINUE
133 eq = ' '
134 ok = .true.
135*
136 IF( lsamen( 2, c2, 'GE' ) ) THEN
137*
138* SGESV
139*
140 srnamt = 'SGESV '
141 infot = 1
142 CALL sgesv( -1, 0, a, 1, ip, b, 1, info )
143 CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
144 infot = 2
145 CALL sgesv( 0, -1, a, 1, ip, b, 1, info )
146 CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
147 infot = 4
148 CALL sgesv( 2, 1, a, 1, ip, b, 2, info )
149 CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
150 infot = 7
151 CALL sgesv( 2, 1, a, 2, ip, b, 1, info )
152 CALL chkxer( 'SGESV ', infot, nout, lerr, ok )
153*
154* SGESVX
155*
156 srnamt = 'SGESVX'
157 infot = 1
158 CALL sgesvx( '/', '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( 'SGESVX', infot, nout, lerr, ok )
161 infot = 2
162 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
165 infot = 3
166 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
169 infot = 4
170 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
173 infot = 6
174 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
177 infot = 8
178 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
181 infot = 10
182 eq = '/'
183 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
186 infot = 11
187 eq = 'R'
188 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
191 infot = 12
192 eq = 'C'
193 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
196 infot = 14
197 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
200 infot = 16
201 CALL sgesvx( '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( 'SGESVX', infot, nout, lerr, ok )
204*
205* SGESVXX
206*
207 n_err_bnds = 3
208 nparams = 1
209 srnamt = 'SGESVXX'
210 infot = 1
211 CALL sgesvxx( '/', '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( 'SGESVXX', infot, nout, lerr, ok )
215 infot = 2
216 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
220 infot = 3
221 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
225 infot = 4
226 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
230 infot = 6
231 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
235 infot = 8
236 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
240 infot = 10
241 eq = '/'
242 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
246 infot = 11
247 eq = 'R'
248 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
252 infot = 12
253 eq = 'C'
254 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
258 infot = 14
259 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
263 infot = 16
264 CALL sgesvxx( '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( 'SGESVXX', infot, nout, lerr, ok )
268*
269 ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
270*
271* SGBSV
272*
273 srnamt = 'SGBSV '
274 infot = 1
275 CALL sgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
276 CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
277 infot = 2
278 CALL sgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
279 CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
280 infot = 3
281 CALL sgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
282 CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
283 infot = 4
284 CALL sgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
285 CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
286 infot = 6
287 CALL sgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
288 CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
289 infot = 9
290 CALL sgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
291 CALL chkxer( 'SGBSV ', infot, nout, lerr, ok )
292*
293* SGBSVX
294*
295 srnamt = 'SGBSVX'
296 infot = 1
297 CALL sgbsvx( '/', '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( 'SGBSVX', infot, nout, lerr, ok )
300 infot = 2
301 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
304 infot = 3
305 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
308 infot = 4
309 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
312 infot = 5
313 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
316 infot = 6
317 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
320 infot = 8
321 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
324 infot = 10
325 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
328 infot = 12
329 eq = '/'
330 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
333 infot = 13
334 eq = 'R'
335 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
338 infot = 14
339 eq = 'C'
340 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
343 infot = 16
344 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
347 infot = 18
348 CALL sgbsvx( '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( 'SGBSVX', infot, nout, lerr, ok )
351*
352* SGBSVXX
353*
354 n_err_bnds = 3
355 nparams = 1
356 srnamt = 'SGBSVXX'
357 infot = 1
358 CALL sgbsvxx( '/', '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( 'SGBSVXX', infot, nout, lerr, ok )
363 infot = 2
364 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
369 infot = 3
370 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
375 infot = 4
376 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
381 infot = 5
382 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
387 infot = 6
388 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
393 infot = 8
394 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
399 infot = 10
400 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
405 infot = 12
406 eq = '/'
407 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
412 infot = 13
413 eq = 'R'
414 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
419 infot = 14
420 eq = 'C'
421 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
426 infot = 15
427 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
432 infot = 16
433 CALL sgbsvxx( '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( 'SGBSVXX', infot, nout, lerr, ok )
438*
439 ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
440*
441* SGTSV
442*
443 srnamt = 'SGTSV '
444 infot = 1
445 CALL sgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
446 $ info )
447 CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
448 infot = 2
449 CALL sgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
450 $ info )
451 CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
452 infot = 7
453 CALL sgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
454 CALL chkxer( 'SGTSV ', infot, nout, lerr, ok )
455*
456* SGTSVX
457*
458 srnamt = 'SGTSVX'
459 infot = 1
460 CALL sgtsvx( '/', '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( 'SGTSVX', infot, nout, lerr, ok )
464 infot = 2
465 CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
469 infot = 3
470 CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
474 infot = 4
475 CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
479 infot = 14
480 CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
484 infot = 16
485 CALL sgtsvx( '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( 'SGTSVX', infot, nout, lerr, ok )
489*
490 ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
491*
492* SPOSV
493*
494 srnamt = 'SPOSV '
495 infot = 1
496 CALL sposv( '/', 0, 0, a, 1, b, 1, info )
497 CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
498 infot = 2
499 CALL sposv( 'U', -1, 0, a, 1, b, 1, info )
500 CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
501 infot = 3
502 CALL sposv( 'U', 0, -1, a, 1, b, 1, info )
503 CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
504 infot = 5
505 CALL sposv( 'U', 2, 0, a, 1, b, 2, info )
506 CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
507 infot = 7
508 CALL sposv( 'U', 2, 0, a, 2, b, 1, info )
509 CALL chkxer( 'SPOSV ', infot, nout, lerr, ok )
510*
511* SPOSVX
512*
513 srnamt = 'SPOSVX'
514 infot = 1
515 CALL sposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
516 $ rcond, r1, r2, w, iw, info )
517 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
518 infot = 2
519 CALL sposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
520 $ rcond, r1, r2, w, iw, info )
521 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
522 infot = 3
523 CALL sposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
524 $ rcond, r1, r2, w, iw, info )
525 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
526 infot = 4
527 CALL sposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
528 $ rcond, r1, r2, w, iw, info )
529 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
530 infot = 6
531 CALL sposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
532 $ rcond, r1, r2, w, iw, info )
533 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
534 infot = 8
535 CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
536 $ rcond, r1, r2, w, iw, info )
537 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
538 infot = 9
539 eq = '/'
540 CALL sposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
541 $ rcond, r1, r2, w, iw, info )
542 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
543 infot = 10
544 eq = 'Y'
545 CALL sposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
546 $ rcond, r1, r2, w, iw, info )
547 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
548 infot = 12
549 CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
550 $ rcond, r1, r2, w, iw, info )
551 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
552 infot = 14
553 CALL sposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
554 $ rcond, r1, r2, w, iw, info )
555 CALL chkxer( 'SPOSVX', infot, nout, lerr, ok )
556*
557* SPOSVXX
558*
559 n_err_bnds = 3
560 nparams = 1
561 srnamt = 'SPOSVXX'
562 infot = 1
563 CALL sposvxx( '/', '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( 'SPOSVXX', infot, nout, lerr, ok )
567 infot = 2
568 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
572 infot = 3
573 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
577 infot = 4
578 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
582 infot = 6
583 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
587 infot = 8
588 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
592 infot = 9
593 eq = '/'
594 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
598 infot = 10
599 eq = 'Y'
600 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
604 infot = 12
605 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
609 infot = 14
610 CALL sposvxx( '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( 'SPOSVXX', infot, nout, lerr, ok )
614*
615 ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
616*
617* SPPSV
618*
619 srnamt = 'SPPSV '
620 infot = 1
621 CALL sppsv( '/', 0, 0, a, b, 1, info )
622 CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
623 infot = 2
624 CALL sppsv( 'U', -1, 0, a, b, 1, info )
625 CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
626 infot = 3
627 CALL sppsv( 'U', 0, -1, a, b, 1, info )
628 CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
629 infot = 6
630 CALL sppsv( 'U', 2, 0, a, b, 1, info )
631 CALL chkxer( 'SPPSV ', infot, nout, lerr, ok )
632*
633* SPPSVX
634*
635 srnamt = 'SPPSVX'
636 infot = 1
637 CALL sppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
638 $ r1, r2, w, iw, info )
639 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
640 infot = 2
641 CALL sppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
642 $ r1, r2, w, iw, info )
643 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
644 infot = 3
645 CALL sppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
646 $ r1, r2, w, iw, info )
647 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
648 infot = 4
649 CALL sppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
650 $ r1, r2, w, iw, info )
651 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
652 infot = 7
653 eq = '/'
654 CALL sppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
655 $ r1, r2, w, iw, info )
656 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
657 infot = 8
658 eq = 'Y'
659 CALL sppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
660 $ r1, r2, w, iw, info )
661 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
662 infot = 10
663 CALL sppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
664 $ r1, r2, w, iw, info )
665 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
666 infot = 12
667 CALL sppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
668 $ r1, r2, w, iw, info )
669 CALL chkxer( 'SPPSVX', infot, nout, lerr, ok )
670*
671 ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
672*
673* SPBSV
674*
675 srnamt = 'SPBSV '
676 infot = 1
677 CALL spbsv( '/', 0, 0, 0, a, 1, b, 1, info )
678 CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
679 infot = 2
680 CALL spbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
681 CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
682 infot = 3
683 CALL spbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
684 CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
685 infot = 4
686 CALL spbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
687 CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
688 infot = 6
689 CALL spbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
690 CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
691 infot = 8
692 CALL spbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
693 CALL chkxer( 'SPBSV ', infot, nout, lerr, ok )
694*
695* SPBSVX
696*
697 srnamt = 'SPBSVX'
698 infot = 1
699 CALL spbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
700 $ rcond, r1, r2, w, iw, info )
701 CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
702 infot = 2
703 CALL spbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
704 $ rcond, r1, r2, w, iw, info )
705 CALL chkxer( 'SPBSVX', infot, nout, lerr, ok )
706 infot = 3
707 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
710 infot = 4
711 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
714 infot = 5
715 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
718 infot = 7
719 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
722 infot = 9
723 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
726 infot = 10
727 eq = '/'
728 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
731 infot = 11
732 eq = 'Y'
733 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
736 infot = 13
737 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
740 infot = 15
741 CALL spbsvx( '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( 'SPBSVX', infot, nout, lerr, ok )
744*
745 ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
746*
747* SPTSV
748*
749 srnamt = 'SPTSV '
750 infot = 1
751 CALL sptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
752 CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
753 infot = 2
754 CALL sptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
755 CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
756 infot = 6
757 CALL sptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
758 CALL chkxer( 'SPTSV ', infot, nout, lerr, ok )
759*
760* SPTSVX
761*
762 srnamt = 'SPTSVX'
763 infot = 1
764 CALL sptsvx( '/', 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( 'SPTSVX', infot, nout, lerr, ok )
767 infot = 2
768 CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
771 infot = 3
772 CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
775 infot = 9
776 CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
779 infot = 11
780 CALL sptsvx( '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( 'SPTSVX', infot, nout, lerr, ok )
783*
784 ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
785*
786* SSYSV
787*
788 srnamt = 'SSYSV '
789 infot = 1
790 CALL ssysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
791 CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
792 infot = 2
793 CALL ssysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
794 CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
795 infot = 3
796 CALL ssysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
797 CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
798 infot = 8
799 CALL ssysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
800 CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
801 infot = 10
802 CALL ssysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
803 CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
804 infot = 10
805 CALL ssysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
806 CALL chkxer( 'SSYSV ', infot, nout, lerr, ok )
807*
808* SSYSVX
809*
810 srnamt = 'SSYSVX'
811 infot = 1
812 CALL ssysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
813 $ rcond, r1, r2, w, 1, iw, info )
814 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
815 infot = 2
816 CALL ssysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
817 $ rcond, r1, r2, w, 1, iw, info )
818 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
819 infot = 3
820 CALL ssysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
821 $ rcond, r1, r2, w, 1, iw, info )
822 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
823 infot = 4
824 CALL ssysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
825 $ rcond, r1, r2, w, 1, iw, info )
826 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
827 infot = 6
828 CALL ssysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
829 $ rcond, r1, r2, w, 4, iw, info )
830 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
831 infot = 8
832 CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
833 $ rcond, r1, r2, w, 4, iw, info )
834 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
835 infot = 11
836 CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
837 $ rcond, r1, r2, w, 4, iw, info )
838 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
839 infot = 13
840 CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
841 $ rcond, r1, r2, w, 4, iw, info )
842 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
843 infot = 18
844 CALL ssysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
845 $ rcond, r1, r2, w, 3, iw, info )
846 CALL chkxer( 'SSYSVX', infot, nout, lerr, ok )
847*
848* SSYSVXX
849*
850 n_err_bnds = 3
851 nparams = 1
852 srnamt = 'SSYSVXX'
853 infot = 1
854 eq = 'N'
855 CALL ssysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
856 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
857 $ err_bnds_c, nparams, params, w, iw, info )
858 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
859 infot = 2
860 CALL ssysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
861 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
862 $ err_bnds_c, nparams, params, w, iw, info )
863 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
864 infot = 3
865 CALL ssysvxx( 'N', 'U', -1, 0, 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( 'SSYSVXX', infot, nout, lerr, ok )
869 infot = 4
870 eq = '/'
871 CALL ssysvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, r, b, 1, x,
872 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
873 $ err_bnds_c, nparams, params, w, iw, info )
874 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
875 eq = 'Y'
876 infot = 6
877 CALL ssysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
878 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
879 $ err_bnds_c, nparams, params, w, iw, info )
880 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
881 infot = 8
882 CALL ssysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
883 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
884 $ err_bnds_c, nparams, params, w, iw, info )
885 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
886 infot = 10
887 CALL ssysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, 'A', 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( 'SSYSVXX', infot, nout, lerr, ok )
891 infot = 11
892 eq='Y'
893 CALL ssysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
894 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
895 $ err_bnds_c, nparams, params, w, iw, info )
896 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
897 infot = 11
898 eq='Y'
899 r(1) = -one
900 CALL ssysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
901 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
902 $ err_bnds_c, nparams, params, w, iw, info )
903 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
904 infot = 13
905 eq = 'N'
906 CALL ssysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, x,
907 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
908 $ err_bnds_c, nparams, params, w, iw, info )
909 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
910 infot = 15
911 CALL ssysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
912 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
913 $ err_bnds_c, nparams, params, w, iw, info )
914 CALL chkxer( 'SSYSVXX', infot, nout, lerr, ok )
915*
916 ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
917*
918* SSYSV_ROOK
919*
920 srnamt = 'SSYSV_ROOK'
921 infot = 1
922 CALL ssysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
923 CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
924 infot = 2
925 CALL ssysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
926 CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
927 infot = 3
928 CALL ssysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
929 CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
930 infot = 8
931 CALL ssysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
932 CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
933 infot = 10
934 CALL ssysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, 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, -2, info )
938 CALL chkxer( 'SSYSV_ROOK', infot, nout, lerr, ok )
939*
940 ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
941*
942* SSYSV_RK
943*
944* Test error exits of the driver that uses factorization
945* of a symmetric indefinite matrix with rook
946* (bounded Bunch-Kaufman) pivoting with the new storage
947* format for factors L ( or U) and D.
948*
949* L (or U) is stored in A, diagonal of D is stored on the
950* diagonal of A, subdiagonal of D is stored in a separate array E.
951*
952 srnamt = 'SSYSV_RK'
953 infot = 1
954 CALL ssysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
955 CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
956 infot = 2
957 CALL ssysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
958 CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
959 infot = 3
960 CALL ssysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
961 CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
962 infot = 5
963 CALL ssysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
964 CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
965 infot = 9
966 CALL ssysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
967 CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
968 infot = 11
969 CALL ssysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, 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, -2, info )
973 CALL chkxer( 'SSYSV_RK', infot, nout, lerr, ok )
974*
975 ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
976*
977* SSPSV
978*
979 srnamt = 'SSPSV '
980 infot = 1
981 CALL sspsv( '/', 0, 0, a, ip, b, 1, info )
982 CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
983 infot = 2
984 CALL sspsv( 'U', -1, 0, a, ip, b, 1, info )
985 CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
986 infot = 3
987 CALL sspsv( 'U', 0, -1, a, ip, b, 1, info )
988 CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
989 infot = 7
990 CALL sspsv( 'U', 2, 0, a, ip, b, 1, info )
991 CALL chkxer( 'SSPSV ', infot, nout, lerr, ok )
992*
993* SSPSVX
994*
995 srnamt = 'SSPSVX'
996 infot = 1
997 CALL sspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
998 $ r2, w, iw, info )
999 CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1000 infot = 2
1001 CALL sspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1002 $ r2, w, iw, info )
1003 CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1004 infot = 3
1005 CALL sspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1006 $ r2, w, iw, info )
1007 CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1008 infot = 4
1009 CALL sspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1010 $ r2, w, iw, info )
1011 CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1012 infot = 9
1013 CALL sspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1014 $ r2, w, iw, info )
1015 CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1016 infot = 11
1017 CALL sspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1018 $ r2, w, iw, info )
1019 CALL chkxer( 'SSPSVX', infot, nout, lerr, ok )
1020 END IF
1021*
1022* Print a summary line.
1023*
1024 IF( ok ) THEN
1025 WRITE( nout, fmt = 9999 )path
1026 ELSE
1027 WRITE( nout, fmt = 9998 )path
1028 END IF
1029*
1030 9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
1031 9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
1032 $ 'exits ***' )
1033*
1034 RETURN
1035*
1036* End of SERRVXX
1037*
1038 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
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:162
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:368
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:563
subroutine sgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
Download SGESV + dependencies <a href="http://www.netlib.org/cgi-bin/netlibfiles....
Definition sgesv.f:124
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:349
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:543
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:127
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:293
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:228
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:204
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:171
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:284
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:508
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:162
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:276
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:164
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:343
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:130
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:307
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:497
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:144
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:311
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:114
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:228
subroutine serrvx(path, nunit)
SERRVX
Definition serrvx.f:55