LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zerrpox.f
Go to the documentation of this file.
1*> \brief \b ZERRPOX
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 ZERRPO( 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*> ZERRPO tests the error exits for the COMPLEX*16 routines
25*> for Hermitian positive definite matrices.
26*>
27*> Note that this file is used only when the XBLAS are available,
28*> otherwise zerrpo.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 complex16_lin
55*
56* =====================================================================
57 SUBROUTINE zerrpo( 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 DOUBLE PRECISION ANRM, RCOND, BERR
79* ..
80* .. Local Arrays ..
81 DOUBLE PRECISION S( NMAX ), R( NMAX ), R1( NMAX ), R2( NMAX ),
82 $ ERR_BNDS_N( NMAX, 3 ), ERR_BNDS_C( NMAX, 3 ),
83 $ PARAMS( 1 )
84 COMPLEX*16 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, zpbcon, zpbequ, zpbrfs, zpbtf2,
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 dble, dcmplx
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 ) = dcmplx( 1.d0 / dble( i+j ),
120 $ -1.d0 / dble( i+j ) )
121 af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
122 $ -1.d0 / dble( i+j ) )
123 10 CONTINUE
124 b( j ) = 0.d0
125 r1( j ) = 0.d0
126 r2( j ) = 0.d0
127 w( j ) = 0.d0
128 x( j ) = 0.d0
129 s( j ) = 0.d0
130 20 CONTINUE
131 anrm = 1.d0
132 ok = .true.
133*
134* Test error exits of the routines that use the Cholesky
135* decomposition of a Hermitian positive definite matrix.
136*
137 IF( lsamen( 2, c2, 'PO' ) ) THEN
138*
139* ZPOTRF
140*
141 srnamt = 'ZPOTRF'
142 infot = 1
143 CALL zpotrf( '/', 0, a, 1, info )
144 CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
145 infot = 2
146 CALL zpotrf( 'U', -1, a, 1, info )
147 CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
148 infot = 4
149 CALL zpotrf( 'U', 2, a, 1, info )
150 CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
151*
152* ZPOTF2
153*
154 srnamt = 'ZPOTF2'
155 infot = 1
156 CALL zpotf2( '/', 0, a, 1, info )
157 CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
158 infot = 2
159 CALL zpotf2( 'U', -1, a, 1, info )
160 CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
161 infot = 4
162 CALL zpotf2( 'U', 2, a, 1, info )
163 CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
164*
165* ZPOTRI
166*
167 srnamt = 'ZPOTRI'
168 infot = 1
169 CALL zpotri( '/', 0, a, 1, info )
170 CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
171 infot = 2
172 CALL zpotri( 'U', -1, a, 1, info )
173 CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
174 infot = 4
175 CALL zpotri( 'U', 2, a, 1, info )
176 CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
177*
178* ZPOTRS
179*
180 srnamt = 'ZPOTRS'
181 infot = 1
182 CALL zpotrs( '/', 0, 0, a, 1, b, 1, info )
183 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
184 infot = 2
185 CALL zpotrs( 'U', -1, 0, a, 1, b, 1, info )
186 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
187 infot = 3
188 CALL zpotrs( 'U', 0, -1, a, 1, b, 1, info )
189 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
190 infot = 5
191 CALL zpotrs( 'U', 2, 1, a, 1, b, 2, info )
192 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
193 infot = 7
194 CALL zpotrs( 'U', 2, 1, a, 2, b, 1, info )
195 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
196*
197* ZPORFS
198*
199 srnamt = 'ZPORFS'
200 infot = 1
201 CALL zporfs( '/', 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
202 $ info )
203 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
204 infot = 2
205 CALL zporfs( 'U', -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
206 $ info )
207 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
208 infot = 3
209 CALL zporfs( 'U', 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
210 $ info )
211 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
212 infot = 5
213 CALL zporfs( 'U', 2, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w, r,
214 $ info )
215 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
216 infot = 7
217 CALL zporfs( 'U', 2, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w, r,
218 $ info )
219 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
220 infot = 9
221 CALL zporfs( 'U', 2, 1, a, 2, af, 2, b, 1, x, 2, r1, r2, w, r,
222 $ info )
223 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
224 infot = 11
225 CALL zporfs( 'U', 2, 1, a, 2, af, 2, b, 2, x, 1, r1, r2, w, r,
226 $ info )
227 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
228*
229* ZPORFSX
230*
231 n_err_bnds = 3
232 nparams = 0
233 srnamt = 'ZPORFSX'
234 infot = 1
235 CALL zporfsx( '/', eq, 0, 0, a, 1, af, 1, s, b, 1, x, 1,
236 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
237 $ params, w, r, info )
238 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
239 infot = 2
240 CALL zporfsx( 'U', "/", -1, 0, a, 1, af, 1, s, b, 1, x, 1,
241 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
242 $ params, w, r, info )
243 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
244 eq = 'N'
245 infot = 3
246 CALL zporfsx( 'U', eq, -1, 0, a, 1, af, 1, s, b, 1, x, 1,
247 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
248 $ params, w, r, info )
249 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
250 infot = 4
251 CALL zporfsx( 'U', eq, 0, -1, a, 1, af, 1, s, b, 1, x, 1,
252 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
253 $ params, w, r, info )
254 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
255 infot = 6
256 CALL zporfsx( 'U', eq, 2, 1, a, 1, af, 2, s, b, 2, x, 2,
257 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
258 $ params, w, r, info )
259 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
260 infot = 8
261 CALL zporfsx( 'U', eq, 2, 1, a, 2, af, 1, s, b, 2, x, 2,
262 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
263 $ params, w, r, info )
264 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
265 infot = 11
266 CALL zporfsx( 'U', eq, 2, 1, a, 2, af, 2, s, b, 1, x, 2,
267 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
268 $ params, w, r, info )
269 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
270 infot = 13
271 CALL zporfsx( 'U', eq, 2, 1, a, 2, af, 2, s, b, 2, x, 1,
272 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
273 $ params, w, r, info )
274 CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
275*
276* ZPOCON
277*
278 srnamt = 'ZPOCON'
279 infot = 1
280 CALL zpocon( '/', 0, a, 1, anrm, rcond, w, r, info )
281 CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
282 infot = 2
283 CALL zpocon( 'U', -1, a, 1, anrm, rcond, w, r, info )
284 CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
285 infot = 4
286 CALL zpocon( 'U', 2, a, 1, anrm, rcond, w, r, info )
287 CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
288 infot = 5
289 CALL zpocon( 'U', 1, a, 1, -anrm, rcond, w, r, info )
290 CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
291*
292* ZPOEQU
293*
294 srnamt = 'ZPOEQU'
295 infot = 1
296 CALL zpoequ( -1, a, 1, r1, rcond, anrm, info )
297 CALL chkxer( 'ZPOEQU', infot, nout, lerr, ok )
298 infot = 3
299 CALL zpoequ( 2, a, 1, r1, rcond, anrm, info )
300 CALL chkxer( 'ZPOEQU', infot, nout, lerr, ok )
301*
302* ZPOEQUB
303*
304 srnamt = 'ZPOEQUB'
305 infot = 1
306 CALL zpoequb( -1, a, 1, r1, rcond, anrm, info )
307 CALL chkxer( 'ZPOEQUB', infot, nout, lerr, ok )
308 infot = 3
309 CALL zpoequb( 2, a, 1, r1, rcond, anrm, info )
310 CALL chkxer( 'ZPOEQUB', infot, nout, lerr, ok )
311*
312* Test error exits of the routines that use the Cholesky
313* decomposition of a Hermitian positive definite packed matrix.
314*
315 ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
316*
317* ZPPTRF
318*
319 srnamt = 'ZPPTRF'
320 infot = 1
321 CALL zpptrf( '/', 0, a, info )
322 CALL chkxer( 'ZPPTRF', infot, nout, lerr, ok )
323 infot = 2
324 CALL zpptrf( 'U', -1, a, info )
325 CALL chkxer( 'ZPPTRF', infot, nout, lerr, ok )
326*
327* ZPPTRI
328*
329 srnamt = 'ZPPTRI'
330 infot = 1
331 CALL zpptri( '/', 0, a, info )
332 CALL chkxer( 'ZPPTRI', infot, nout, lerr, ok )
333 infot = 2
334 CALL zpptri( 'U', -1, a, info )
335 CALL chkxer( 'ZPPTRI', infot, nout, lerr, ok )
336*
337* ZPPTRS
338*
339 srnamt = 'ZPPTRS'
340 infot = 1
341 CALL zpptrs( '/', 0, 0, a, b, 1, info )
342 CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
343 infot = 2
344 CALL zpptrs( 'U', -1, 0, a, b, 1, info )
345 CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
346 infot = 3
347 CALL zpptrs( 'U', 0, -1, a, b, 1, info )
348 CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
349 infot = 6
350 CALL zpptrs( 'U', 2, 1, a, b, 1, info )
351 CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
352*
353* ZPPRFS
354*
355 srnamt = 'ZPPRFS'
356 infot = 1
357 CALL zpprfs( '/', 0, 0, a, af, b, 1, x, 1, r1, r2, w, r, info )
358 CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
359 infot = 2
360 CALL zpprfs( 'U', -1, 0, a, af, b, 1, x, 1, r1, r2, w, r,
361 $ info )
362 CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
363 infot = 3
364 CALL zpprfs( 'U', 0, -1, a, af, b, 1, x, 1, r1, r2, w, r,
365 $ info )
366 CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
367 infot = 7
368 CALL zpprfs( 'U', 2, 1, a, af, b, 1, x, 2, r1, r2, w, r, info )
369 CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
370 infot = 9
371 CALL zpprfs( 'U', 2, 1, a, af, b, 2, x, 1, r1, r2, w, r, info )
372 CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
373*
374* ZPPCON
375*
376 srnamt = 'ZPPCON'
377 infot = 1
378 CALL zppcon( '/', 0, a, anrm, rcond, w, r, info )
379 CALL chkxer( 'ZPPCON', infot, nout, lerr, ok )
380 infot = 2
381 CALL zppcon( 'U', -1, a, anrm, rcond, w, r, info )
382 CALL chkxer( 'ZPPCON', infot, nout, lerr, ok )
383 infot = 4
384 CALL zppcon( 'U', 1, a, -anrm, rcond, w, r, info )
385 CALL chkxer( 'ZPPCON', infot, nout, lerr, ok )
386*
387* ZPPEQU
388*
389 srnamt = 'ZPPEQU'
390 infot = 1
391 CALL zppequ( '/', 0, a, r1, rcond, anrm, info )
392 CALL chkxer( 'ZPPEQU', infot, nout, lerr, ok )
393 infot = 2
394 CALL zppequ( 'U', -1, a, r1, rcond, anrm, info )
395 CALL chkxer( 'ZPPEQU', infot, nout, lerr, ok )
396*
397* Test error exits of the routines that use the Cholesky
398* decomposition of a Hermitian positive definite band matrix.
399*
400 ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
401*
402* ZPBTRF
403*
404 srnamt = 'ZPBTRF'
405 infot = 1
406 CALL zpbtrf( '/', 0, 0, a, 1, info )
407 CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
408 infot = 2
409 CALL zpbtrf( 'U', -1, 0, a, 1, info )
410 CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
411 infot = 3
412 CALL zpbtrf( 'U', 1, -1, a, 1, info )
413 CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
414 infot = 5
415 CALL zpbtrf( 'U', 2, 1, a, 1, info )
416 CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
417*
418* ZPBTF2
419*
420 srnamt = 'ZPBTF2'
421 infot = 1
422 CALL zpbtf2( '/', 0, 0, a, 1, info )
423 CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
424 infot = 2
425 CALL zpbtf2( 'U', -1, 0, a, 1, info )
426 CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
427 infot = 3
428 CALL zpbtf2( 'U', 1, -1, a, 1, info )
429 CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
430 infot = 5
431 CALL zpbtf2( 'U', 2, 1, a, 1, info )
432 CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
433*
434* ZPBTRS
435*
436 srnamt = 'ZPBTRS'
437 infot = 1
438 CALL zpbtrs( '/', 0, 0, 0, a, 1, b, 1, info )
439 CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
440 infot = 2
441 CALL zpbtrs( 'U', -1, 0, 0, a, 1, b, 1, info )
442 CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
443 infot = 3
444 CALL zpbtrs( 'U', 1, -1, 0, a, 1, b, 1, info )
445 CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
446 infot = 4
447 CALL zpbtrs( 'U', 0, 0, -1, a, 1, b, 1, info )
448 CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
449 infot = 6
450 CALL zpbtrs( 'U', 2, 1, 1, a, 1, b, 1, info )
451 CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
452 infot = 8
453 CALL zpbtrs( 'U', 2, 0, 1, a, 1, b, 1, info )
454 CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
455*
456* ZPBRFS
457*
458 srnamt = 'ZPBRFS'
459 infot = 1
460 CALL zpbrfs( '/', 0, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
461 $ r, info )
462 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
463 infot = 2
464 CALL zpbrfs( 'U', -1, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
465 $ r, info )
466 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
467 infot = 3
468 CALL zpbrfs( 'U', 1, -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
469 $ r, info )
470 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
471 infot = 4
472 CALL zpbrfs( 'U', 0, 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
473 $ r, info )
474 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
475 infot = 6
476 CALL zpbrfs( 'U', 2, 1, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w,
477 $ r, info )
478 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
479 infot = 8
480 CALL zpbrfs( 'U', 2, 1, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w,
481 $ r, info )
482 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
483 infot = 10
484 CALL zpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 1, x, 2, r1, r2, w,
485 $ r, info )
486 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
487 infot = 12
488 CALL zpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 2, x, 1, r1, r2, w,
489 $ r, info )
490 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
491*
492* ZPBCON
493*
494 srnamt = 'ZPBCON'
495 infot = 1
496 CALL zpbcon( '/', 0, 0, a, 1, anrm, rcond, w, r, info )
497 CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
498 infot = 2
499 CALL zpbcon( 'U', -1, 0, a, 1, anrm, rcond, w, r, info )
500 CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
501 infot = 3
502 CALL zpbcon( 'U', 1, -1, a, 1, anrm, rcond, w, r, info )
503 CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
504 infot = 5
505 CALL zpbcon( 'U', 2, 1, a, 1, anrm, rcond, w, r, info )
506 CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
507 infot = 6
508 CALL zpbcon( 'U', 1, 0, a, 1, -anrm, rcond, w, r, info )
509 CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
510*
511* ZPBEQU
512*
513 srnamt = 'ZPBEQU'
514 infot = 1
515 CALL zpbequ( '/', 0, 0, a, 1, r1, rcond, anrm, info )
516 CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
517 infot = 2
518 CALL zpbequ( 'U', -1, 0, a, 1, r1, rcond, anrm, info )
519 CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
520 infot = 3
521 CALL zpbequ( 'U', 1, -1, a, 1, r1, rcond, anrm, info )
522 CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
523 infot = 5
524 CALL zpbequ( 'U', 2, 1, a, 1, r1, rcond, anrm, info )
525 CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
526 END IF
527*
528* Print a summary line.
529*
530 CALL alaesm( path, ok, nout )
531*
532 RETURN
533*
534* End of ZERRPOX
535*
536 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine zpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, rwork, info)
ZPBCON
Definition zpbcon.f:133
subroutine zpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)
ZPBEQU
Definition zpbequ.f:130
subroutine zpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZPBRFS
Definition zpbrfs.f:189
subroutine zpbtf2(uplo, n, kd, ab, ldab, info)
ZPBTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite band matrix (un...
Definition zpbtf2.f:142
subroutine zpbtrf(uplo, n, kd, ab, ldab, info)
ZPBTRF
Definition zpbtrf.f:142
subroutine zpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
ZPBTRS
Definition zpbtrs.f:121
subroutine zpocon(uplo, n, a, lda, anorm, rcond, work, rwork, info)
ZPOCON
Definition zpocon.f:121
subroutine zpoequ(n, a, lda, s, scond, amax, info)
ZPOEQU
Definition zpoequ.f:113
subroutine zpoequb(n, a, lda, s, scond, amax, info)
ZPOEQUB
Definition zpoequb.f:119
subroutine zporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZPORFS
Definition zporfs.f:183
subroutine zporfsx(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)
ZPORFSX
Definition zporfsx.f:393
subroutine zpotf2(uplo, n, a, lda, info)
ZPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition zpotf2.f:109
subroutine zpotrf(uplo, n, a, lda, info)
ZPOTRF
Definition zpotrf.f:107
subroutine zpotri(uplo, n, a, lda, info)
ZPOTRI
Definition zpotri.f:95
subroutine zpotrs(uplo, n, nrhs, a, lda, b, ldb, info)
ZPOTRS
Definition zpotrs.f:110
subroutine zppcon(uplo, n, ap, anorm, rcond, work, rwork, info)
ZPPCON
Definition zppcon.f:118
subroutine zppequ(uplo, n, ap, s, scond, amax, info)
ZPPEQU
Definition zppequ.f:117
subroutine zpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZPPRFS
Definition zpprfs.f:171
subroutine zpptrf(uplo, n, ap, info)
ZPPTRF
Definition zpptrf.f:119
subroutine zpptri(uplo, n, ap, info)
ZPPTRI
Definition zpptri.f:93
subroutine zpptrs(uplo, n, nrhs, ap, b, ldb, info)
ZPPTRS
Definition zpptrs.f:108
subroutine zerrpo(path, nunit)
ZERRPO
Definition zerrpo.f:55