LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cerrpox.f
Go to the documentation of this file.
1*> \brief \b CERRPOX
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 CERRPO( 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*> CERRPO tests the error exits for the COMPLEX routines
25*> for Hermitian positive definite matrices.
26*>
27*> Note that this file is used only when the XBLAS are available,
28*> otherwise cerrpo.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 complex_lin
55*
56* =====================================================================
57 SUBROUTINE cerrpo( 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 REAL S( NMAX ), R( NMAX ), R1( NMAX ), R2( NMAX ),
82 $ ERR_BNDS_N( NMAX, 3 ), ERR_BNDS_C( NMAX, 3 ),
83 $ PARAMS( 1 )
84 COMPLEX A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
85 $ W( 2*NMAX ), X( NMAX )
86* ..
87* .. External Functions ..
88 LOGICAL LSAMEN
89 EXTERNAL lsamen
90* ..
91* .. External Subroutines ..
92 EXTERNAL alaesm, chkxer, cpbcon, cpbequ, cpbrfs, cpbtf2,
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 cmplx, 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 ) = cmplx( 1. / real( i+j ), -1. / real( i+j ) )
120 af( i, j ) = cmplx( 1. / real( 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 20 CONTINUE
129 anrm = 1.
130 ok = .true.
131*
132* Test error exits of the routines that use the Cholesky
133* decomposition of a Hermitian positive definite matrix.
134*
135 IF( lsamen( 2, c2, 'PO' ) ) THEN
136*
137* CPOTRF
138*
139 srnamt = 'CPOTRF'
140 infot = 1
141 CALL cpotrf( '/', 0, a, 1, info )
142 CALL chkxer( 'CPOTRF', infot, nout, lerr, ok )
143 infot = 2
144 CALL cpotrf( 'U', -1, a, 1, info )
145 CALL chkxer( 'CPOTRF', infot, nout, lerr, ok )
146 infot = 4
147 CALL cpotrf( 'U', 2, a, 1, info )
148 CALL chkxer( 'CPOTRF', infot, nout, lerr, ok )
149*
150* CPOTF2
151*
152 srnamt = 'CPOTF2'
153 infot = 1
154 CALL cpotf2( '/', 0, a, 1, info )
155 CALL chkxer( 'CPOTF2', infot, nout, lerr, ok )
156 infot = 2
157 CALL cpotf2( 'U', -1, a, 1, info )
158 CALL chkxer( 'CPOTF2', infot, nout, lerr, ok )
159 infot = 4
160 CALL cpotf2( 'U', 2, a, 1, info )
161 CALL chkxer( 'CPOTF2', infot, nout, lerr, ok )
162*
163* CPOTRI
164*
165 srnamt = 'CPOTRI'
166 infot = 1
167 CALL cpotri( '/', 0, a, 1, info )
168 CALL chkxer( 'CPOTRI', infot, nout, lerr, ok )
169 infot = 2
170 CALL cpotri( 'U', -1, a, 1, info )
171 CALL chkxer( 'CPOTRI', infot, nout, lerr, ok )
172 infot = 4
173 CALL cpotri( 'U', 2, a, 1, info )
174 CALL chkxer( 'CPOTRI', infot, nout, lerr, ok )
175*
176* CPOTRS
177*
178 srnamt = 'CPOTRS'
179 infot = 1
180 CALL cpotrs( '/', 0, 0, a, 1, b, 1, info )
181 CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
182 infot = 2
183 CALL cpotrs( 'U', -1, 0, a, 1, b, 1, info )
184 CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
185 infot = 3
186 CALL cpotrs( 'U', 0, -1, a, 1, b, 1, info )
187 CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
188 infot = 5
189 CALL cpotrs( 'U', 2, 1, a, 1, b, 2, info )
190 CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
191 infot = 7
192 CALL cpotrs( 'U', 2, 1, a, 2, b, 1, info )
193 CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
194*
195* CPORFS
196*
197 srnamt = 'CPORFS'
198 infot = 1
199 CALL cporfs( '/', 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
200 $ info )
201 CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
202 infot = 2
203 CALL cporfs( 'U', -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
204 $ info )
205 CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
206 infot = 3
207 CALL cporfs( 'U', 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
208 $ info )
209 CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
210 infot = 5
211 CALL cporfs( 'U', 2, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w, r,
212 $ info )
213 CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
214 infot = 7
215 CALL cporfs( 'U', 2, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w, r,
216 $ info )
217 CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
218 infot = 9
219 CALL cporfs( 'U', 2, 1, a, 2, af, 2, b, 1, x, 2, r1, r2, w, r,
220 $ info )
221 CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
222 infot = 11
223 CALL cporfs( 'U', 2, 1, a, 2, af, 2, b, 2, x, 1, r1, r2, w, r,
224 $ info )
225 CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
226*
227* CPORFSX
228*
229 n_err_bnds = 3
230 nparams = 0
231 srnamt = 'CPORFSX'
232 infot = 1
233 CALL cporfsx( '/', 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, r, info )
236 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
237 infot = 2
238 CALL cporfsx( '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, r, info )
241 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
242 eq = 'N'
243 infot = 3
244 CALL cporfsx( '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, r, info )
247 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
248 infot = 4
249 CALL cporfsx( '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, r, info )
252 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
253 infot = 6
254 CALL cporfsx( '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, r, info )
257 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
258 infot = 8
259 CALL cporfsx( '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, r, info )
262 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
263 infot = 11
264 CALL cporfsx( '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, r, info )
267 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
268 infot = 13
269 CALL cporfsx( '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, r, info )
272 CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
273*
274* CPOCON
275*
276 srnamt = 'CPOCON'
277 infot = 1
278 CALL cpocon( '/', 0, a, 1, anrm, rcond, w, r, info )
279 CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
280 infot = 2
281 CALL cpocon( 'U', -1, a, 1, anrm, rcond, w, r, info )
282 CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
283 infot = 4
284 CALL cpocon( 'U', 2, a, 1, anrm, rcond, w, r, info )
285 CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
286 infot = 5
287 CALL cpocon( 'U', 1, a, 1, -anrm, rcond, w, r, info )
288 CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
289*
290* CPOEQU
291*
292 srnamt = 'CPOEQU'
293 infot = 1
294 CALL cpoequ( -1, a, 1, r1, rcond, anrm, info )
295 CALL chkxer( 'CPOEQU', infot, nout, lerr, ok )
296 infot = 3
297 CALL cpoequ( 2, a, 1, r1, rcond, anrm, info )
298 CALL chkxer( 'CPOEQU', infot, nout, lerr, ok )
299*
300* CPOEQUB
301*
302 srnamt = 'CPOEQUB'
303 infot = 1
304 CALL cpoequb( -1, a, 1, r1, rcond, anrm, info )
305 CALL chkxer( 'CPOEQUB', infot, nout, lerr, ok )
306 infot = 3
307 CALL cpoequb( 2, a, 1, r1, rcond, anrm, info )
308 CALL chkxer( 'CPOEQUB', infot, nout, lerr, ok )
309*
310* Test error exits of the routines that use the Cholesky
311* decomposition of a Hermitian positive definite packed matrix.
312*
313 ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
314*
315* CPPTRF
316*
317 srnamt = 'CPPTRF'
318 infot = 1
319 CALL cpptrf( '/', 0, a, info )
320 CALL chkxer( 'CPPTRF', infot, nout, lerr, ok )
321 infot = 2
322 CALL cpptrf( 'U', -1, a, info )
323 CALL chkxer( 'CPPTRF', infot, nout, lerr, ok )
324*
325* CPPTRI
326*
327 srnamt = 'CPPTRI'
328 infot = 1
329 CALL cpptri( '/', 0, a, info )
330 CALL chkxer( 'CPPTRI', infot, nout, lerr, ok )
331 infot = 2
332 CALL cpptri( 'U', -1, a, info )
333 CALL chkxer( 'CPPTRI', infot, nout, lerr, ok )
334*
335* CPPTRS
336*
337 srnamt = 'CPPTRS'
338 infot = 1
339 CALL cpptrs( '/', 0, 0, a, b, 1, info )
340 CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
341 infot = 2
342 CALL cpptrs( 'U', -1, 0, a, b, 1, info )
343 CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
344 infot = 3
345 CALL cpptrs( 'U', 0, -1, a, b, 1, info )
346 CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
347 infot = 6
348 CALL cpptrs( 'U', 2, 1, a, b, 1, info )
349 CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
350*
351* CPPRFS
352*
353 srnamt = 'CPPRFS'
354 infot = 1
355 CALL cpprfs( '/', 0, 0, a, af, b, 1, x, 1, r1, r2, w, r, info )
356 CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
357 infot = 2
358 CALL cpprfs( 'U', -1, 0, a, af, b, 1, x, 1, r1, r2, w, r,
359 $ info )
360 CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
361 infot = 3
362 CALL cpprfs( 'U', 0, -1, a, af, b, 1, x, 1, r1, r2, w, r,
363 $ info )
364 CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
365 infot = 7
366 CALL cpprfs( 'U', 2, 1, a, af, b, 1, x, 2, r1, r2, w, r, info )
367 CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
368 infot = 9
369 CALL cpprfs( 'U', 2, 1, a, af, b, 2, x, 1, r1, r2, w, r, info )
370 CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
371*
372* CPPCON
373*
374 srnamt = 'CPPCON'
375 infot = 1
376 CALL cppcon( '/', 0, a, anrm, rcond, w, r, info )
377 CALL chkxer( 'CPPCON', infot, nout, lerr, ok )
378 infot = 2
379 CALL cppcon( 'U', -1, a, anrm, rcond, w, r, info )
380 CALL chkxer( 'CPPCON', infot, nout, lerr, ok )
381 infot = 4
382 CALL cppcon( 'U', 1, a, -anrm, rcond, w, r, info )
383 CALL chkxer( 'CPPCON', infot, nout, lerr, ok )
384*
385* CPPEQU
386*
387 srnamt = 'CPPEQU'
388 infot = 1
389 CALL cppequ( '/', 0, a, r1, rcond, anrm, info )
390 CALL chkxer( 'CPPEQU', infot, nout, lerr, ok )
391 infot = 2
392 CALL cppequ( 'U', -1, a, r1, rcond, anrm, info )
393 CALL chkxer( 'CPPEQU', infot, nout, lerr, ok )
394*
395* Test error exits of the routines that use the Cholesky
396* decomposition of a Hermitian positive definite band matrix.
397*
398 ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
399*
400* CPBTRF
401*
402 srnamt = 'CPBTRF'
403 infot = 1
404 CALL cpbtrf( '/', 0, 0, a, 1, info )
405 CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
406 infot = 2
407 CALL cpbtrf( 'U', -1, 0, a, 1, info )
408 CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
409 infot = 3
410 CALL cpbtrf( 'U', 1, -1, a, 1, info )
411 CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
412 infot = 5
413 CALL cpbtrf( 'U', 2, 1, a, 1, info )
414 CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
415*
416* CPBTF2
417*
418 srnamt = 'CPBTF2'
419 infot = 1
420 CALL cpbtf2( '/', 0, 0, a, 1, info )
421 CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
422 infot = 2
423 CALL cpbtf2( 'U', -1, 0, a, 1, info )
424 CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
425 infot = 3
426 CALL cpbtf2( 'U', 1, -1, a, 1, info )
427 CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
428 infot = 5
429 CALL cpbtf2( 'U', 2, 1, a, 1, info )
430 CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
431*
432* CPBTRS
433*
434 srnamt = 'CPBTRS'
435 infot = 1
436 CALL cpbtrs( '/', 0, 0, 0, a, 1, b, 1, info )
437 CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
438 infot = 2
439 CALL cpbtrs( 'U', -1, 0, 0, a, 1, b, 1, info )
440 CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
441 infot = 3
442 CALL cpbtrs( 'U', 1, -1, 0, a, 1, b, 1, info )
443 CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
444 infot = 4
445 CALL cpbtrs( 'U', 0, 0, -1, a, 1, b, 1, info )
446 CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
447 infot = 6
448 CALL cpbtrs( 'U', 2, 1, 1, a, 1, b, 1, info )
449 CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
450 infot = 8
451 CALL cpbtrs( 'U', 2, 0, 1, a, 1, b, 1, info )
452 CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
453*
454* CPBRFS
455*
456 srnamt = 'CPBRFS'
457 infot = 1
458 CALL cpbrfs( '/', 0, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
459 $ r, info )
460 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
461 infot = 2
462 CALL cpbrfs( 'U', -1, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
463 $ r, info )
464 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
465 infot = 3
466 CALL cpbrfs( 'U', 1, -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
467 $ r, info )
468 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
469 infot = 4
470 CALL cpbrfs( 'U', 0, 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
471 $ r, info )
472 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
473 infot = 6
474 CALL cpbrfs( 'U', 2, 1, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w,
475 $ r, info )
476 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
477 infot = 8
478 CALL cpbrfs( 'U', 2, 1, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w,
479 $ r, info )
480 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
481 infot = 10
482 CALL cpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 1, x, 2, r1, r2, w,
483 $ r, info )
484 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
485 infot = 12
486 CALL cpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 2, x, 1, r1, r2, w,
487 $ r, info )
488 CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
489*
490* CPBCON
491*
492 srnamt = 'CPBCON'
493 infot = 1
494 CALL cpbcon( '/', 0, 0, a, 1, anrm, rcond, w, r, info )
495 CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
496 infot = 2
497 CALL cpbcon( 'U', -1, 0, a, 1, anrm, rcond, w, r, info )
498 CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
499 infot = 3
500 CALL cpbcon( 'U', 1, -1, a, 1, anrm, rcond, w, r, info )
501 CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
502 infot = 5
503 CALL cpbcon( 'U', 2, 1, a, 1, anrm, rcond, w, r, info )
504 CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
505 infot = 6
506 CALL cpbcon( 'U', 1, 0, a, 1, -anrm, rcond, w, r, info )
507 CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
508*
509* CPBEQU
510*
511 srnamt = 'CPBEQU'
512 infot = 1
513 CALL cpbequ( '/', 0, 0, a, 1, r1, rcond, anrm, info )
514 CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
515 infot = 2
516 CALL cpbequ( 'U', -1, 0, a, 1, r1, rcond, anrm, info )
517 CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
518 infot = 3
519 CALL cpbequ( 'U', 1, -1, a, 1, r1, rcond, anrm, info )
520 CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
521 infot = 5
522 CALL cpbequ( 'U', 2, 1, a, 1, r1, rcond, anrm, info )
523 CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
524 END IF
525*
526* Print a summary line.
527*
528 CALL alaesm( path, ok, nout )
529*
530 RETURN
531*
532* End of CERRPOX
533*
534 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine cerrpo(path, nunit)
CERRPO
Definition cerrpo.f:55
subroutine cpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, rwork, info)
CPBCON
Definition cpbcon.f:133
subroutine cpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)
CPBEQU
Definition cpbequ.f:130
subroutine cpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CPBRFS
Definition cpbrfs.f:189
subroutine cpbtf2(uplo, n, kd, ab, ldab, info)
CPBTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite band matrix (un...
Definition cpbtf2.f:142
subroutine cpbtrf(uplo, n, kd, ab, ldab, info)
CPBTRF
Definition cpbtrf.f:142
subroutine cpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
CPBTRS
Definition cpbtrs.f:121
subroutine cpocon(uplo, n, a, lda, anorm, rcond, work, rwork, info)
CPOCON
Definition cpocon.f:121
subroutine cpoequ(n, a, lda, s, scond, amax, info)
CPOEQU
Definition cpoequ.f:113
subroutine cpoequb(n, a, lda, s, scond, amax, info)
CPOEQUB
Definition cpoequb.f:119
subroutine cporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CPORFS
Definition cporfs.f:183
subroutine cporfsx(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, rwork, info)
CPORFSX
Definition cporfsx.f:393
subroutine cpotf2(uplo, n, a, lda, info)
CPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition cpotf2.f:109
subroutine cpotrf(uplo, n, a, lda, info)
CPOTRF
Definition cpotrf.f:107
subroutine cpotri(uplo, n, a, lda, info)
CPOTRI
Definition cpotri.f:95
subroutine cpotrs(uplo, n, nrhs, a, lda, b, ldb, info)
CPOTRS
Definition cpotrs.f:110
subroutine cppcon(uplo, n, ap, anorm, rcond, work, rwork, info)
CPPCON
Definition cppcon.f:118
subroutine cppequ(uplo, n, ap, s, scond, amax, info)
CPPEQU
Definition cppequ.f:117
subroutine cpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CPPRFS
Definition cpprfs.f:171
subroutine cpptrf(uplo, n, ap, info)
CPPTRF
Definition cpptrf.f:119
subroutine cpptri(uplo, n, ap, info)
CPPTRI
Definition cpptri.f:93
subroutine cpptrs(uplo, n, nrhs, ap, b, ldb, info)
CPPTRS
Definition cpptrs.f:108