LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
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 alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine spbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, iwork, info)
SPBCON
Definition spbcon.f:132
subroutine spbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)
SPBEQU
Definition spbequ.f:129
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 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 spbtrf(uplo, n, kd, ab, ldab, info)
SPBTRF
Definition spbtrf.f:142
subroutine spbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
SPBTRS
Definition spbtrs.f:121
subroutine spocon(uplo, n, a, lda, anorm, rcond, work, iwork, info)
SPOCON
Definition spocon.f:121
subroutine spoequ(n, a, lda, s, scond, amax, info)
SPOEQU
Definition spoequ.f:112
subroutine spoequb(n, a, lda, s, scond, amax, info)
SPOEQUB
Definition spoequb.f:118
subroutine sporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPORFS
Definition sporfs.f:183
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 spotf2(uplo, n, a, lda, info)
SPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition spotf2.f:109
subroutine spotrf(uplo, n, a, lda, info)
SPOTRF
Definition spotrf.f:107
subroutine spotri(uplo, n, a, lda, info)
SPOTRI
Definition spotri.f:95
subroutine spotrs(uplo, n, nrhs, a, lda, b, ldb, info)
SPOTRS
Definition spotrs.f:110
subroutine sppcon(uplo, n, ap, anorm, rcond, work, iwork, info)
SPPCON
Definition sppcon.f:118
subroutine sppequ(uplo, n, ap, s, scond, amax, info)
SPPEQU
Definition sppequ.f:116
subroutine spprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)
SPPRFS
Definition spprfs.f:171
subroutine spptrf(uplo, n, ap, info)
SPPTRF
Definition spptrf.f:119
subroutine spptri(uplo, n, ap, info)
SPPTRI
Definition spptri.f:93
subroutine spptrs(uplo, n, nrhs, ap, b, ldb, info)
SPPTRS
Definition spptrs.f:108
subroutine serrpo(path, nunit)
SERRPO
Definition serrpo.f:55