OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
serrpox.f
Go to the documentation of this file.
1*> \brief \b SERRPOX
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 SERRPO( 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*> SERRPO tests the error exits for the REAL routines
25*> for symmetric positive definite matrices.
26*>
27*> Note that this file is used only when the XBLAS are available,
28*> otherwise serrpo.f defines this subroutine.
29*> \endverbatim
30*
31* Arguments:
32* ==========
33*
34*> \param[in] PATH
35*> \verbatim
36*> PATH is CHARACTER*3
37*> The LAPACK path name for the routines to be tested.
38*> \endverbatim
39*>
40*> \param[in] NUNIT
41*> \verbatim
42*> NUNIT is INTEGER
43*> The unit number for output.
44*> \endverbatim
45*
46* Authors:
47* ========
48*
49*> \author Univ. of Tennessee
50*> \author Univ. of California Berkeley
51*> \author Univ. of Colorado Denver
52*> \author NAG Ltd.
53*
54*> \ingroup single_lin
55*
56* =====================================================================
57 SUBROUTINE serrpo( PATH, NUNIT )
58*
59* -- LAPACK test routine --
60* -- LAPACK is a software package provided by Univ. of Tennessee, --
61* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
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, N_ERR_BNDS, NPARAMS
78 REAL ANRM, RCOND, BERR
79* ..
80* .. Local Arrays ..
81 INTEGER IW( NMAX )
82 REAL A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
83 $ R1( NMAX ), R2( NMAX ), W( 3*NMAX ), X( NMAX ),
84 $ S( NMAX ), ERR_BNDS_N( NMAX, 3 ),
85 $ ERR_BNDS_C( NMAX, 3 ), PARAMS( 1 )
86* ..
87* .. External Functions ..
88 LOGICAL LSAMEN
89 EXTERNAL lsamen
90* ..
91* .. External Subroutines ..
92 EXTERNAL alaesm, chkxer, spbcon, spbequ, spbrfs, spbtf2,
96* ..
97* .. Scalars in Common ..
98 LOGICAL LERR, OK
99 CHARACTER*32 SRNAMT
100 INTEGER INFOT, NOUT
101* ..
102* .. Common blocks ..
103 COMMON / infoc / infot, nout, ok, lerr
104 COMMON / srnamc / srnamt
105* ..
106* .. Intrinsic Functions ..
107 INTRINSIC real
108* ..
109* .. Executable Statements ..
110*
111 nout = nunit
112 WRITE( nout, fmt = * )
113 c2 = path( 2: 3 )
114*
115* Set the variables to innocuous values.
116*
117 DO 20 j = 1, nmax
118 DO 10 i = 1, nmax
119 a( i, j ) = 1. / real( i+j )
120 af( i, j ) = 1. / real( i+j )
121 10 CONTINUE
122 b( j ) = 0.
123 r1( j ) = 0.
124 r2( j ) = 0.
125 w( j ) = 0.
126 x( j ) = 0.
127 s( j ) = 0.
128 iw( j ) = j
129 20 CONTINUE
130 ok = .true.
131*
132 IF( lsamen( 2, c2, 'PO' ) ) THEN
133*
134* Test error exits of the routines that use the Cholesky
135* decomposition of a symmetric positive definite matrix.
136*
137* SPOTRF
138*
139 srnamt = 'SPOTRF'
140 infot = 1
141 CALL spotrf( '/', 0, a, 1, info )
142 CALL chkxer( 'SPOTRF', infot, nout, lerr, ok )
143 infot = 2
144 CALL spotrf( 'U', -1, a, 1, info )
145 CALL chkxer( 'SPOTRF', infot, nout, lerr, ok )
146 infot = 4
147 CALL spotrf( 'U', 2, a, 1, info )
148 CALL chkxer( 'SPOTRF', infot, nout, lerr, ok )
149*
150* SPOTF2
151*
152 srnamt = 'SPOTF2'
153 infot = 1
154 CALL spotf2( '/', 0, a, 1, info )
155 CALL chkxer( 'SPOTF2', infot, nout, lerr, ok )
156 infot = 2
157 CALL spotf2( 'U', -1, a, 1, info )
158 CALL chkxer( 'SPOTF2', infot, nout, lerr, ok )
159 infot = 4
160 CALL spotf2( 'U', 2, a, 1, info )
161 CALL chkxer( 'SPOTF2', infot, nout, lerr, ok )
162*
163* SPOTRI
164*
165 srnamt = 'SPOTRI'
166 infot = 1
167 CALL spotri( '/', 0, a, 1, info )
168 CALL chkxer( 'SPOTRI', infot, nout, lerr, ok )
169 infot = 2
170 CALL spotri( 'U', -1, a, 1, info )
171 CALL chkxer( 'SPOTRI', infot, nout, lerr, ok )
172 infot = 4
173 CALL spotri( 'U', 2, a, 1, info )
174 CALL chkxer( 'SPOTRI', infot, nout, lerr, ok )
175*
176* SPOTRS
177*
178 srnamt = 'spotrs'
179 INFOT = 1
180 CALL SPOTRS( '/', 0, 0, A, 1, B, 1, INFO )
181 CALL CHKXER( 'spotrs', INFOT, NOUT, LERR, OK )
182 INFOT = 2
183 CALL SPOTRS( 'u', -1, 0, A, 1, B, 1, INFO )
184 CALL CHKXER( 'spotrs', INFOT, NOUT, LERR, OK )
185 INFOT = 3
186 CALL SPOTRS( 'u', 0, -1, A, 1, B, 1, INFO )
187 CALL CHKXER( 'spotrs', INFOT, NOUT, LERR, OK )
188 INFOT = 5
189 CALL SPOTRS( 'u', 2, 1, A, 1, B, 2, INFO )
190 CALL CHKXER( 'spotrs', INFOT, NOUT, LERR, OK )
191 INFOT = 7
192 CALL SPOTRS( 'u', 2, 1, A, 2, B, 1, INFO )
193 CALL CHKXER( 'spotrs', INFOT, NOUT, LERR, OK )
194*
195* SPORFS
196*
197 SRNAMT = 'sporfs'
198 INFOT = 1
199 CALL SPORFS( '/', 0, 0, A, 1, AF, 1, B, 1, X, 1, R1, R2, W, IW,
200 $ INFO )
201 CALL CHKXER( 'sporfs', INFOT, NOUT, LERR, OK )
202 INFOT = 2
203 CALL SPORFS( 'u', -1, 0, A, 1, AF, 1, B, 1, X, 1, R1, R2, W,
204 $ IW, INFO )
205 CALL CHKXER( 'sporfs', INFOT, NOUT, LERR, OK )
206 INFOT = 3
207 CALL SPORFS( 'u', 0, -1, A, 1, AF, 1, B, 1, X, 1, R1, R2, W,
208 $ IW, INFO )
209 CALL CHKXER( 'sporfs', INFOT, NOUT, LERR, OK )
210 INFOT = 5
211 CALL SPORFS( 'u', 2, 1, A, 1, AF, 2, B, 2, X, 2, R1, R2, W, IW,
212 $ INFO )
213 CALL CHKXER( 'sporfs', INFOT, NOUT, LERR, OK )
214 INFOT = 7
215 CALL SPORFS( 'u', 2, 1, A, 2, AF, 1, B, 2, X, 2, R1, R2, W, IW,
216 $ INFO )
217 CALL CHKXER( 'sporfs', INFOT, NOUT, LERR, OK )
218 INFOT = 9
219 CALL SPORFS( 'u', 2, 1, A, 2, AF, 2, B, 1, X, 2, R1, R2, W, IW,
220 $ INFO )
221 CALL CHKXER( 'sporfs', INFOT, NOUT, LERR, OK )
222 INFOT = 11
223 CALL SPORFS( 'u', 2, 1, A, 2, AF, 2, B, 2, X, 1, R1, R2, W, IW,
224 $ INFO )
225 CALL CHKXER( 'sporfs', INFOT, NOUT, LERR, OK )
226*
227* SPORFSX
228*
229 N_ERR_BNDS = 3
230 NPARAMS = 0
231 SRNAMT = 'sporfsx'
232 INFOT = 1
233 CALL SPORFSX( '/', EQ, 0, 0, A, 1, AF, 1, S, B, 1, X, 1,
234 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
235 $ PARAMS, W, IW, INFO )
236 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
237 INFOT = 2
238 CALL SPORFSX( 'u', "/", -1, 0, A, 1, AF, 1, S, B, 1, X, 1,
239 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
240 $ PARAMS, W, IW, INFO )
241 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
242 EQ = 'n'
243 INFOT = 3
244 CALL SPORFSX( 'u', EQ, -1, 0, A, 1, AF, 1, S, B, 1, X, 1,
245 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
246 $ PARAMS, W, IW, INFO )
247 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
248 INFOT = 4
249 CALL SPORFSX( 'u', EQ, 0, -1, A, 1, AF, 1, S, B, 1, X, 1,
250 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
251 $ PARAMS, W, IW, INFO )
252 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
253 INFOT = 6
254 CALL SPORFSX( 'u', EQ, 2, 1, A, 1, AF, 2, S, B, 2, X, 2,
255 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
256 $ PARAMS, W, IW, INFO )
257 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
258 INFOT = 8
259 CALL SPORFSX( 'u', EQ, 2, 1, A, 2, AF, 1, S, B, 2, X, 2,
260 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
261 $ PARAMS, W, IW, INFO )
262 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
263 INFOT = 11
264 CALL SPORFSX( 'u', EQ, 2, 1, A, 2, AF, 2, S, B, 1, X, 2,
265 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
266 $ PARAMS, W, IW, INFO )
267 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
268 INFOT = 13
269 CALL SPORFSX( 'u', EQ, 2, 1, A, 2, AF, 2, S, B, 2, X, 1,
270 $ RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N, ERR_BNDS_C, NPARAMS,
271 $ PARAMS, W, IW, INFO )
272 CALL CHKXER( 'sporfsx', INFOT, NOUT, LERR, OK )
273*
274* SPOCON
275*
276 SRNAMT = 'spocon'
277 INFOT = 1
278 CALL SPOCON( '/', 0, A, 1, ANRM, RCOND, W, IW, INFO )
279 CALL CHKXER( 'spocon', INFOT, NOUT, LERR, OK )
280 INFOT = 2
281 CALL SPOCON( 'u', -1, A, 1, ANRM, RCOND, W, IW, INFO )
282 CALL CHKXER( 'spocon', INFOT, NOUT, LERR, OK )
283 INFOT = 4
284 CALL SPOCON( 'u', 2, A, 1, ANRM, RCOND, W, IW, INFO )
285 CALL CHKXER( 'spocon', INFOT, NOUT, LERR, OK )
286*
287* SPOEQU
288*
289 SRNAMT = 'spoequ'
290 INFOT = 1
291 CALL SPOEQU( -1, A, 1, R1, RCOND, ANRM, INFO )
292 CALL CHKXER( 'spoequ', INFOT, NOUT, LERR, OK )
293 INFOT = 3
294 CALL SPOEQU( 2, A, 1, R1, RCOND, ANRM, INFO )
295 CALL CHKXER( 'spoequ', INFOT, NOUT, LERR, OK )
296*
297* SPOEQUB
298*
299 SRNAMT = 'spoequb'
300 INFOT = 1
301 CALL SPOEQUB( -1, A, 1, R1, RCOND, ANRM, INFO )
302 CALL CHKXER( 'spoequb', INFOT, NOUT, LERR, OK )
303 INFOT = 3
304 CALL SPOEQUB( 2, A, 1, R1, RCOND, ANRM, INFO )
305 CALL CHKXER( 'spoequb', INFOT, NOUT, LERR, OK )
306*
307 ELSE IF( LSAMEN( 2, C2, 'pp' ) ) THEN
308*
309* Test error exits of the routines that use the Cholesky
310* decomposition of a symmetric positive definite packed matrix.
311*
312* SPPTRF
313*
314 SRNAMT = 'spptrf'
315 INFOT = 1
316 CALL SPPTRF( '/', 0, A, INFO )
317 CALL CHKXER( 'spptrf', INFOT, NOUT, LERR, OK )
318 INFOT = 2
319 CALL SPPTRF( 'u', -1, A, INFO )
320 CALL CHKXER( 'spptrf', INFOT, NOUT, LERR, OK )
321*
322* SPPTRI
323*
324 SRNAMT = 'spptri'
325 INFOT = 1
326 CALL SPPTRI( '/', 0, A, INFO )
327 CALL CHKXER( 'spptri', INFOT, NOUT, LERR, OK )
328 INFOT = 2
329 CALL SPPTRI( 'u', -1, A, INFO )
330 CALL CHKXER( 'spptri', INFOT, NOUT, LERR, OK )
331*
332* SPPTRS
333*
334 SRNAMT = 'spptrs'
335 INFOT = 1
336 CALL SPPTRS( '/', 0, 0, A, B, 1, INFO )
337 CALL CHKXER( 'spptrs', INFOT, NOUT, LERR, OK )
338 INFOT = 2
339 CALL SPPTRS( 'u', -1, 0, A, B, 1, INFO )
340 CALL CHKXER( 'spptrs', INFOT, NOUT, LERR, OK )
341 INFOT = 3
342 CALL SPPTRS( 'u', 0, -1, A, B, 1, INFO )
343 CALL CHKXER( 'spptrs', INFOT, NOUT, LERR, OK )
344 INFOT = 6
345 CALL SPPTRS( 'u', 2, 1, A, B, 1, INFO )
346 CALL CHKXER( 'spptrs', INFOT, NOUT, LERR, OK )
347*
348* SPPRFS
349*
350 SRNAMT = 'spprfs'
351 INFOT = 1
352 CALL SPPRFS( '/', 0, 0, A, AF, B, 1, X, 1, R1, R2, W, IW,
353 $ INFO )
354 CALL CHKXER( 'spprfs', INFOT, NOUT, LERR, OK )
355 INFOT = 2
356 CALL SPPRFS( 'u', -1, 0, A, AF, B, 1, X, 1, R1, R2, W, IW,
357 $ INFO )
358 CALL CHKXER( 'spprfs', INFOT, NOUT, LERR, OK )
359 INFOT = 3
360 CALL SPPRFS( 'u', 0, -1, A, AF, B, 1, X, 1, R1, R2, W, IW,
361 $ INFO )
362 CALL CHKXER( 'spprfs', INFOT, NOUT, LERR, OK )
363 INFOT = 7
364 CALL SPPRFS( 'u', 2, 1, A, AF, B, 1, X, 2, R1, R2, W, IW,
365 $ INFO )
366 CALL CHKXER( 'spprfs', INFOT, NOUT, LERR, OK )
367 INFOT = 9
368 CALL SPPRFS( 'u', 2, 1, A, AF, B, 2, X, 1, R1, R2, W, IW,
369 $ INFO )
370 CALL CHKXER( 'spprfs', INFOT, NOUT, LERR, OK )
371*
372* SPPCON
373*
374 SRNAMT = 'sppcon'
375 INFOT = 1
376 CALL SPPCON( '/', 0, A, ANRM, RCOND, W, IW, INFO )
377 CALL CHKXER( 'sppcon', INFOT, NOUT, LERR, OK )
378 INFOT = 2
379 CALL SPPCON( 'u', -1, A, ANRM, RCOND, W, IW, INFO )
380 CALL CHKXER( 'sppcon', INFOT, NOUT, LERR, OK )
381*
382* SPPEQU
383*
384 SRNAMT = 'sppequ'
385 INFOT = 1
386 CALL SPPEQU( '/', 0, A, R1, RCOND, ANRM, INFO )
387 CALL CHKXER( 'sppequ', INFOT, NOUT, LERR, OK )
388 INFOT = 2
389 CALL SPPEQU( 'u', -1, A, R1, RCOND, ANRM, INFO )
390 CALL CHKXER( 'sppequ', INFOT, NOUT, LERR, OK )
391*
392 ELSE IF( LSAMEN( 2, C2, 'pb' ) ) THEN
393*
394* Test error exits of the routines that use the Cholesky
395* decomposition of a symmetric positive definite band matrix.
396*
397* SPBTRF
398*
399 SRNAMT = 'spbtrf'
400 INFOT = 1
401 CALL SPBTRF( '/', 0, 0, a, 1, info )
402 CALL chkxer( 'SPBTRF', infot, nout, lerr, ok )
403 infot = 2
404 CALL spbtrf( 'U', -1, 0, a, 1, info )
405 CALL chkxer( 'SPBTRF', infot, nout, lerr, ok )
406 infot = 3
407 CALL spbtrf( 'U', 1, -1, a, 1, info )
408 CALL chkxer( 'SPBTRF', infot, nout, lerr, ok )
409 infot = 5
410 CALL spbtrf( 'U', 2, 1, a, 1, info )
411 CALL chkxer( 'SPBTRF', infot, nout, lerr, ok )
412*
413* SPBTF2
414*
415 srnamt = 'SPBTF2'
416 infot = 1
417 CALL spbtf2( '/', 0, 0, a, 1, info )
418 CALL chkxer( 'SPBTF2', infot, nout, lerr, ok )
419 infot = 2
420 CALL spbtf2( 'U', -1, 0, a, 1, info )
421 CALL chkxer( 'spbtf2', INFOT, NOUT, LERR, OK )
422 INFOT = 3
423 CALL SPBTF2( 'u', 1, -1, A, 1, INFO )
424 CALL CHKXER( 'spbtf2', INFOT, NOUT, LERR, OK )
425 INFOT = 5
426 CALL SPBTF2( 'u', 2, 1, A, 1, INFO )
427 CALL CHKXER( 'spbtf2', INFOT, NOUT, LERR, OK )
428*
429* SPBTRS
430*
431 SRNAMT = 'spbtrs'
432 INFOT = 1
433 CALL SPBTRS( '/', 0, 0, 0, A, 1, B, 1, INFO )
434 CALL CHKXER( 'spbtrs', INFOT, NOUT, LERR, OK )
435 INFOT = 2
436 CALL SPBTRS( 'u', -1, 0, 0, A, 1, B, 1, INFO )
437 CALL CHKXER( 'spbtrs', INFOT, NOUT, LERR, OK )
438 INFOT = 3
439 CALL SPBTRS( 'u', 1, -1, 0, A, 1, B, 1, INFO )
440 CALL CHKXER( 'spbtrs', INFOT, NOUT, LERR, OK )
441 INFOT = 4
442 CALL SPBTRS( 'u', 0, 0, -1, A, 1, B, 1, INFO )
443 CALL CHKXER( 'spbtrs', INFOT, NOUT, LERR, OK )
444 INFOT = 6
445 CALL SPBTRS( 'u', 2, 1, 1, A, 1, B, 1, INFO )
446 CALL CHKXER( 'spbtrs', INFOT, NOUT, LERR, OK )
447 INFOT = 8
448 CALL SPBTRS( 'u', 2, 0, 1, A, 1, B, 1, INFO )
449 CALL CHKXER( 'spbtrs', INFOT, NOUT, LERR, OK )
450*
451* SPBRFS
452*
453 SRNAMT = 'spbrfs'
454 INFOT = 1
455 CALL SPBRFS( '/', 0, 0, 0, A, 1, AF, 1, B, 1, X, 1, R1, R2, W,
456 $ IW, INFO )
457 CALL CHKXER( 'spbrfs', INFOT, NOUT, LERR, OK )
458 INFOT = 2
459 CALL SPBRFS( 'u', -1, 0, 0, A, 1, AF, 1, B, 1, X, 1, R1, R2, W,
460 $ IW, INFO )
461 CALL CHKXER( 'spbrfs', INFOT, NOUT, LERR, OK )
462 INFOT = 3
463 CALL SPBRFS( 'u', 1, -1, 0, A, 1, AF, 1, B, 1, X, 1, R1, R2, W,
464 $ IW, INFO )
465 CALL CHKXER( 'spbrfs', INFOT, NOUT, LERR, OK )
466 INFOT = 4
467 CALL SPBRFS( 'u', 0, 0, -1, A, 1, AF, 1, B, 1, X, 1, R1, R2, W,
468 $ IW, INFO )
469 CALL CHKXER( 'spbrfs', INFOT, NOUT, LERR, OK )
470 INFOT = 6
471 CALL SPBRFS( 'u', 2, 1, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w,
472 $ iw, info )
473 CALL chkxer( 'SPBRFS', infot, nout, lerr, ok )
474 infot = 8
475 CALL spbrfs( 'U', 2, 1, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w,
476 $ iw, info )
477 CALL chkxer( 'SPBRFS', infot, nout, lerr, ok )
478 infot = 10
479 CALL spbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 1, x, 2, r1, r2, w,
480 $ iw, info )
481 CALL chkxer( 'SPBRFS', infot, nout, lerr, ok )
482 infot = 12
483 CALL spbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 2, x, 1, r1, r2, w,
484 $ iw, info )
485 CALL chkxer( 'SPBRFS', infot, nout, lerr, ok )
486*
487* SPBCON
488*
489 srnamt = 'SPBCON'
490 infot = 1
491 CALL spbcon( '/', 0, 0, a, 1, anrm, rcond, w, iw, info )
492 CALL chkxer( 'SPBCON', infot, nout, lerr, ok )
493 infot = 2
494 CALL spbcon( 'U', -1, 0, a, 1, anrm, rcond, w, iw, info )
495 CALL chkxer( 'SPBCON', infot, nout, lerr, ok )
496 infot = 3
497 CALL spbcon( 'U', 1, -1, a, 1, anrm, rcond, w, iw, info )
498 CALL chkxer( 'spbcon', INFOT, NOUT, LERR, OK )
499 INFOT = 5
500 CALL SPBCON( 'u', 2, 1, A, 1, ANRM, RCOND, W, IW, INFO )
501 CALL CHKXER( 'spbcon', INFOT, NOUT, LERR, OK )
502*
503* SPBEQU
504*
505 SRNAMT = 'spbequ'
506 INFOT = 1
507 CALL SPBEQU( '/', 0, 0, A, 1, R1, RCOND, ANRM, INFO )
508 CALL CHKXER( 'spbequ', INFOT, NOUT, LERR, OK )
509 INFOT = 2
510 CALL SPBEQU( 'u', -1, 0, A, 1, R1, RCOND, ANRM, INFO )
511 CALL CHKXER( 'spbequ', INFOT, NOUT, LERR, OK )
512 INFOT = 3
513 CALL SPBEQU( 'u', 1, -1, A, 1, R1, RCOND, ANRM, INFO )
514 CALL CHKXER( 'spbequ', INFOT, NOUT, LERR, OK )
515 INFOT = 5
516 CALL SPBEQU( 'u', 2, 1, A, 1, R1, RCOND, ANRM, INFO )
517 CALL CHKXER( 'spbequ', INFOT, NOUT, LERR, OK )
518 END IF
519*
520* Print a summary line.
521*
522 CALL ALAESM( PATH, OK, NOUT )
523*
524 RETURN
525*
526* End of SERRPOX
527*
528 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3196
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine spbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
SPBTRS
Definition spbtrs.f:121
subroutine spbtf2(uplo, n, kd, ab, ldab, info)
SPBTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite band matrix (un...
Definition spbtf2.f:142
subroutine spptrf(uplo, n, ap, info)
SPPTRF
Definition spptrf.f:119
subroutine spptrs(uplo, n, nrhs, ap, b, ldb, info)
SPPTRS
Definition spptrs.f:108
subroutine spptri(uplo, n, ap, info)
SPPTRI
Definition spptri.f:93
subroutine spbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)
SPBEQU
Definition spbequ.f:129
subroutine sppequ(uplo, n, ap, s, scond, amax, info)
SPPEQU
Definition sppequ.f:116
subroutine spbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, iwork, info)
SPBCON
Definition spbcon.f:132
subroutine sppcon(uplo, n, ap, anorm, rcond, work, iwork, info)
SPPCON
Definition sppcon.f:118
subroutine spbtrf(uplo, n, kd, ab, ldab, info)
SPBTRF
Definition spbtrf.f:142
subroutine spbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPBRFS
Definition spbrfs.f:189
subroutine spprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPPRFS
Definition spprfs.f:171
subroutine sporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPORFS
Definition sporfs.f:183
subroutine spotf2(uplo, n, a, lda, info)
SPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition spotf2.f:109
subroutine spotrs(uplo, n, nrhs, a, lda, b, ldb, info)
SPOTRS
Definition spotrs.f:110
subroutine spocon(uplo, n, a, lda, anorm, rcond, work, iwork, info)
SPOCON
Definition spocon.f:121
subroutine spoequb(n, a, lda, s, scond, amax, info)
SPOEQUB
Definition spoequb.f:118
subroutine sporfsx(uplo, equed, n, nrhs, a, lda, af, ldaf, s, b, ldb, x, ldx, rcond, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, iwork, info)
SPORFSX
Definition sporfsx.f:394
subroutine spoequ(n, a, lda, s, scond, amax, info)
SPOEQU
Definition spoequ.f:112
subroutine spotri(uplo, n, a, lda, info)
SPOTRI
Definition spotri.f:95
subroutine spotrf(uplo, n, a, lda, info)
SPOTRF
Definition spotrf.f:107
subroutine serrpo(path, nunit)
SERRPO
Definition serrpo.f:55