LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 *> \date November 2015
55 *
56 *> \ingroup complex_lin
57 *
58 * =====================================================================
59  SUBROUTINE cerrpo( PATH, NUNIT )
60 *
61 * -- LAPACK test routine (version 3.6.0) --
62 * -- LAPACK is a software package provided by Univ. of Tennessee, --
63 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
64 * November 2015
65 *
66 * .. Scalar Arguments ..
67  CHARACTER*3 path
68  INTEGER nunit
69 * ..
70 *
71 * =====================================================================
72 *
73 * .. Parameters ..
74  INTEGER nmax
75  parameter ( nmax = 4 )
76 * ..
77 * .. Local Scalars ..
78  CHARACTER eq
79  CHARACTER*2 c2
80  INTEGER i, info, j, n_err_bnds, nparams
81  REAL anrm, rcond, berr
82 * ..
83 * .. Local Arrays ..
84  REAL s( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
85  $ err_bnds_n( nmax, 3 ), err_bnds_c( nmax, 3 ),
86  $ params( 1 )
87  COMPLEX a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
88  $ w( 2*nmax ), x( nmax )
89 * ..
90 * .. External Functions ..
91  LOGICAL lsamen
92  EXTERNAL lsamen
93 * ..
94 * .. External Subroutines ..
95  EXTERNAL alaesm, chkxer, cpbcon, cpbequ, cpbrfs, cpbtf2,
99 * ..
100 * .. Scalars in Common ..
101  LOGICAL lerr, ok
102  CHARACTER*32 srnamt
103  INTEGER infot, nout
104 * ..
105 * .. Common blocks ..
106  COMMON / infoc / infot, nout, ok, lerr
107  COMMON / srnamc / srnamt
108 * ..
109 * .. Intrinsic Functions ..
110  INTRINSIC cmplx, real
111 * ..
112 * .. Executable Statements ..
113 *
114  nout = nunit
115  WRITE( nout, fmt = * )
116  c2 = path( 2: 3 )
117 *
118 * Set the variables to innocuous values.
119 *
120  DO 20 j = 1, nmax
121  DO 10 i = 1, nmax
122  a( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
123  af( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
124  10 CONTINUE
125  b( j ) = 0.
126  r1( j ) = 0.
127  r2( j ) = 0.
128  w( j ) = 0.
129  x( j ) = 0.
130  s( j ) = 0.
131  20 CONTINUE
132  anrm = 1.
133  ok = .true.
134 *
135 * Test error exits of the routines that use the Cholesky
136 * decomposition of a Hermitian positive definite matrix.
137 *
138  IF( lsamen( 2, c2, 'PO' ) ) THEN
139 *
140 * CPOTRF
141 *
142  srnamt = 'CPOTRF'
143  infot = 1
144  CALL cpotrf( '/', 0, a, 1, info )
145  CALL chkxer( 'CPOTRF', infot, nout, lerr, ok )
146  infot = 2
147  CALL cpotrf( 'U', -1, a, 1, info )
148  CALL chkxer( 'CPOTRF', infot, nout, lerr, ok )
149  infot = 4
150  CALL cpotrf( 'U', 2, a, 1, info )
151  CALL chkxer( 'CPOTRF', infot, nout, lerr, ok )
152 *
153 * CPOTF2
154 *
155  srnamt = 'CPOTF2'
156  infot = 1
157  CALL cpotf2( '/', 0, a, 1, info )
158  CALL chkxer( 'CPOTF2', infot, nout, lerr, ok )
159  infot = 2
160  CALL cpotf2( 'U', -1, a, 1, info )
161  CALL chkxer( 'CPOTF2', infot, nout, lerr, ok )
162  infot = 4
163  CALL cpotf2( 'U', 2, a, 1, info )
164  CALL chkxer( 'CPOTF2', infot, nout, lerr, ok )
165 *
166 * CPOTRI
167 *
168  srnamt = 'CPOTRI'
169  infot = 1
170  CALL cpotri( '/', 0, a, 1, info )
171  CALL chkxer( 'CPOTRI', infot, nout, lerr, ok )
172  infot = 2
173  CALL cpotri( 'U', -1, a, 1, info )
174  CALL chkxer( 'CPOTRI', infot, nout, lerr, ok )
175  infot = 4
176  CALL cpotri( 'U', 2, a, 1, info )
177  CALL chkxer( 'CPOTRI', infot, nout, lerr, ok )
178 *
179 * CPOTRS
180 *
181  srnamt = 'CPOTRS'
182  infot = 1
183  CALL cpotrs( '/', 0, 0, a, 1, b, 1, info )
184  CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
185  infot = 2
186  CALL cpotrs( 'U', -1, 0, a, 1, b, 1, info )
187  CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
188  infot = 3
189  CALL cpotrs( 'U', 0, -1, a, 1, b, 1, info )
190  CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
191  infot = 5
192  CALL cpotrs( 'U', 2, 1, a, 1, b, 2, info )
193  CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
194  infot = 7
195  CALL cpotrs( 'U', 2, 1, a, 2, b, 1, info )
196  CALL chkxer( 'CPOTRS', infot, nout, lerr, ok )
197 *
198 * CPORFS
199 *
200  srnamt = 'CPORFS'
201  infot = 1
202  CALL cporfs( '/', 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
203  $ info )
204  CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
205  infot = 2
206  CALL cporfs( 'U', -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
207  $ info )
208  CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
209  infot = 3
210  CALL cporfs( 'U', 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
211  $ info )
212  CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
213  infot = 5
214  CALL cporfs( 'U', 2, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w, r,
215  $ info )
216  CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
217  infot = 7
218  CALL cporfs( 'U', 2, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w, r,
219  $ info )
220  CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
221  infot = 9
222  CALL cporfs( 'U', 2, 1, a, 2, af, 2, b, 1, x, 2, r1, r2, w, r,
223  $ info )
224  CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
225  infot = 11
226  CALL cporfs( 'U', 2, 1, a, 2, af, 2, b, 2, x, 1, r1, r2, w, r,
227  $ info )
228  CALL chkxer( 'CPORFS', infot, nout, lerr, ok )
229 *
230 * CPORFSX
231 *
232  n_err_bnds = 3
233  nparams = 0
234  srnamt = 'CPORFSX'
235  infot = 1
236  CALL cporfsx( '/', eq, 0, 0, a, 1, af, 1, s, b, 1, x, 1,
237  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
238  $ params, w, r, info )
239  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
240  infot = 2
241  CALL cporfsx( 'U', '/', -1, 0, a, 1, af, 1, s, b, 1, x, 1,
242  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
243  $ params, w, r, info )
244  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
245  eq = 'N'
246  infot = 3
247  CALL cporfsx( 'U', eq, -1, 0, a, 1, af, 1, s, b, 1, x, 1,
248  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
249  $ params, w, r, info )
250  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
251  infot = 4
252  CALL cporfsx( 'U', eq, 0, -1, a, 1, af, 1, s, b, 1, x, 1,
253  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
254  $ params, w, r, info )
255  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
256  infot = 6
257  CALL cporfsx( 'U', eq, 2, 1, a, 1, af, 2, s, b, 2, x, 2,
258  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
259  $ params, w, r, info )
260  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
261  infot = 8
262  CALL cporfsx( 'U', eq, 2, 1, a, 2, af, 1, s, b, 2, x, 2,
263  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
264  $ params, w, r, info )
265  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
266  infot = 11
267  CALL cporfsx( 'U', eq, 2, 1, a, 2, af, 2, s, b, 1, x, 2,
268  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
269  $ params, w, r, info )
270  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
271  infot = 13
272  CALL cporfsx( 'U', eq, 2, 1, a, 2, af, 2, s, b, 2, x, 1,
273  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
274  $ params, w, r, info )
275  CALL chkxer( 'CPORFSX', infot, nout, lerr, ok )
276 *
277 * CPOCON
278 *
279  srnamt = 'CPOCON'
280  infot = 1
281  CALL cpocon( '/', 0, a, 1, anrm, rcond, w, r, info )
282  CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
283  infot = 2
284  CALL cpocon( 'U', -1, a, 1, anrm, rcond, w, r, info )
285  CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
286  infot = 4
287  CALL cpocon( 'U', 2, a, 1, anrm, rcond, w, r, info )
288  CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
289  infot = 5
290  CALL cpocon( 'U', 1, a, 1, -anrm, rcond, w, r, info )
291  CALL chkxer( 'CPOCON', infot, nout, lerr, ok )
292 *
293 * CPOEQU
294 *
295  srnamt = 'CPOEQU'
296  infot = 1
297  CALL cpoequ( -1, a, 1, r1, rcond, anrm, info )
298  CALL chkxer( 'CPOEQU', infot, nout, lerr, ok )
299  infot = 3
300  CALL cpoequ( 2, a, 1, r1, rcond, anrm, info )
301  CALL chkxer( 'CPOEQU', infot, nout, lerr, ok )
302 *
303 * CPOEQUB
304 *
305  srnamt = 'CPOEQUB'
306  infot = 1
307  CALL cpoequb( -1, a, 1, r1, rcond, anrm, info )
308  CALL chkxer( 'CPOEQUB', infot, nout, lerr, ok )
309  infot = 3
310  CALL cpoequb( 2, a, 1, r1, rcond, anrm, info )
311  CALL chkxer( 'CPOEQUB', infot, nout, lerr, ok )
312 *
313 * Test error exits of the routines that use the Cholesky
314 * decomposition of a Hermitian positive definite packed matrix.
315 *
316  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
317 *
318 * CPPTRF
319 *
320  srnamt = 'CPPTRF'
321  infot = 1
322  CALL cpptrf( '/', 0, a, info )
323  CALL chkxer( 'CPPTRF', infot, nout, lerr, ok )
324  infot = 2
325  CALL cpptrf( 'U', -1, a, info )
326  CALL chkxer( 'CPPTRF', infot, nout, lerr, ok )
327 *
328 * CPPTRI
329 *
330  srnamt = 'CPPTRI'
331  infot = 1
332  CALL cpptri( '/', 0, a, info )
333  CALL chkxer( 'CPPTRI', infot, nout, lerr, ok )
334  infot = 2
335  CALL cpptri( 'U', -1, a, info )
336  CALL chkxer( 'CPPTRI', infot, nout, lerr, ok )
337 *
338 * CPPTRS
339 *
340  srnamt = 'CPPTRS'
341  infot = 1
342  CALL cpptrs( '/', 0, 0, a, b, 1, info )
343  CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
344  infot = 2
345  CALL cpptrs( 'U', -1, 0, a, b, 1, info )
346  CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
347  infot = 3
348  CALL cpptrs( 'U', 0, -1, a, b, 1, info )
349  CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
350  infot = 6
351  CALL cpptrs( 'U', 2, 1, a, b, 1, info )
352  CALL chkxer( 'CPPTRS', infot, nout, lerr, ok )
353 *
354 * CPPRFS
355 *
356  srnamt = 'CPPRFS'
357  infot = 1
358  CALL cpprfs( '/', 0, 0, a, af, b, 1, x, 1, r1, r2, w, r, info )
359  CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
360  infot = 2
361  CALL cpprfs( 'U', -1, 0, a, af, b, 1, x, 1, r1, r2, w, r,
362  $ info )
363  CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
364  infot = 3
365  CALL cpprfs( 'U', 0, -1, a, af, b, 1, x, 1, r1, r2, w, r,
366  $ info )
367  CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
368  infot = 7
369  CALL cpprfs( 'U', 2, 1, a, af, b, 1, x, 2, r1, r2, w, r, info )
370  CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
371  infot = 9
372  CALL cpprfs( 'U', 2, 1, a, af, b, 2, x, 1, r1, r2, w, r, info )
373  CALL chkxer( 'CPPRFS', infot, nout, lerr, ok )
374 *
375 * CPPCON
376 *
377  srnamt = 'CPPCON'
378  infot = 1
379  CALL cppcon( '/', 0, a, anrm, rcond, w, r, info )
380  CALL chkxer( 'CPPCON', infot, nout, lerr, ok )
381  infot = 2
382  CALL cppcon( 'U', -1, a, anrm, rcond, w, r, info )
383  CALL chkxer( 'CPPCON', infot, nout, lerr, ok )
384  infot = 4
385  CALL cppcon( 'U', 1, a, -anrm, rcond, w, r, info )
386  CALL chkxer( 'CPPCON', infot, nout, lerr, ok )
387 *
388 * CPPEQU
389 *
390  srnamt = 'CPPEQU'
391  infot = 1
392  CALL cppequ( '/', 0, a, r1, rcond, anrm, info )
393  CALL chkxer( 'CPPEQU', infot, nout, lerr, ok )
394  infot = 2
395  CALL cppequ( 'U', -1, a, r1, rcond, anrm, info )
396  CALL chkxer( 'CPPEQU', infot, nout, lerr, ok )
397 *
398 * Test error exits of the routines that use the Cholesky
399 * decomposition of a Hermitian positive definite band matrix.
400 *
401  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
402 *
403 * CPBTRF
404 *
405  srnamt = 'CPBTRF'
406  infot = 1
407  CALL cpbtrf( '/', 0, 0, a, 1, info )
408  CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
409  infot = 2
410  CALL cpbtrf( 'U', -1, 0, a, 1, info )
411  CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
412  infot = 3
413  CALL cpbtrf( 'U', 1, -1, a, 1, info )
414  CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
415  infot = 5
416  CALL cpbtrf( 'U', 2, 1, a, 1, info )
417  CALL chkxer( 'CPBTRF', infot, nout, lerr, ok )
418 *
419 * CPBTF2
420 *
421  srnamt = 'CPBTF2'
422  infot = 1
423  CALL cpbtf2( '/', 0, 0, a, 1, info )
424  CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
425  infot = 2
426  CALL cpbtf2( 'U', -1, 0, a, 1, info )
427  CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
428  infot = 3
429  CALL cpbtf2( 'U', 1, -1, a, 1, info )
430  CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
431  infot = 5
432  CALL cpbtf2( 'U', 2, 1, a, 1, info )
433  CALL chkxer( 'CPBTF2', infot, nout, lerr, ok )
434 *
435 * CPBTRS
436 *
437  srnamt = 'CPBTRS'
438  infot = 1
439  CALL cpbtrs( '/', 0, 0, 0, a, 1, b, 1, info )
440  CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
441  infot = 2
442  CALL cpbtrs( 'U', -1, 0, 0, a, 1, b, 1, info )
443  CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
444  infot = 3
445  CALL cpbtrs( 'U', 1, -1, 0, a, 1, b, 1, info )
446  CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
447  infot = 4
448  CALL cpbtrs( 'U', 0, 0, -1, a, 1, b, 1, info )
449  CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
450  infot = 6
451  CALL cpbtrs( 'U', 2, 1, 1, a, 1, b, 1, info )
452  CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
453  infot = 8
454  CALL cpbtrs( 'U', 2, 0, 1, a, 1, b, 1, info )
455  CALL chkxer( 'CPBTRS', infot, nout, lerr, ok )
456 *
457 * CPBRFS
458 *
459  srnamt = 'CPBRFS'
460  infot = 1
461  CALL cpbrfs( '/', 0, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
462  $ r, info )
463  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
464  infot = 2
465  CALL cpbrfs( 'U', -1, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
466  $ r, info )
467  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
468  infot = 3
469  CALL cpbrfs( 'U', 1, -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
470  $ r, info )
471  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
472  infot = 4
473  CALL cpbrfs( 'U', 0, 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
474  $ r, info )
475  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
476  infot = 6
477  CALL cpbrfs( 'U', 2, 1, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w,
478  $ r, info )
479  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
480  infot = 8
481  CALL cpbrfs( 'U', 2, 1, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w,
482  $ r, info )
483  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
484  infot = 10
485  CALL cpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 1, x, 2, r1, r2, w,
486  $ r, info )
487  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
488  infot = 12
489  CALL cpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 2, x, 1, r1, r2, w,
490  $ r, info )
491  CALL chkxer( 'CPBRFS', infot, nout, lerr, ok )
492 *
493 * CPBCON
494 *
495  srnamt = 'CPBCON'
496  infot = 1
497  CALL cpbcon( '/', 0, 0, a, 1, anrm, rcond, w, r, info )
498  CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
499  infot = 2
500  CALL cpbcon( 'U', -1, 0, a, 1, anrm, rcond, w, r, info )
501  CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
502  infot = 3
503  CALL cpbcon( 'U', 1, -1, a, 1, anrm, rcond, w, r, info )
504  CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
505  infot = 5
506  CALL cpbcon( 'U', 2, 1, a, 1, anrm, rcond, w, r, info )
507  CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
508  infot = 6
509  CALL cpbcon( 'U', 1, 0, a, 1, -anrm, rcond, w, r, info )
510  CALL chkxer( 'CPBCON', infot, nout, lerr, ok )
511 *
512 * CPBEQU
513 *
514  srnamt = 'CPBEQU'
515  infot = 1
516  CALL cpbequ( '/', 0, 0, a, 1, r1, rcond, anrm, info )
517  CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
518  infot = 2
519  CALL cpbequ( 'U', -1, 0, a, 1, r1, rcond, anrm, info )
520  CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
521  infot = 3
522  CALL cpbequ( 'U', 1, -1, a, 1, r1, rcond, anrm, info )
523  CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
524  infot = 5
525  CALL cpbequ( 'U', 2, 1, a, 1, r1, rcond, anrm, info )
526  CALL chkxer( 'CPBEQU', infot, nout, lerr, ok )
527  END IF
528 *
529 * Print a summary line.
530 *
531  CALL alaesm( path, ok, nout )
532 *
533  RETURN
534 *
535 * End of CERRPO
536 *
537  END
subroutine cpptrs(UPLO, N, NRHS, AP, B, LDB, INFO)
CPPTRS
Definition: cpptrs.f:110
subroutine cpotri(UPLO, N, A, LDA, INFO)
CPOTRI
Definition: cpotri.f:97
subroutine cporfs(UPLO, N, NRHS, A, LDA, AF, LDAF, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CPORFS
Definition: cporfs.f:185
subroutine cpbequ(UPLO, N, KD, AB, LDAB, S, SCOND, AMAX, INFO)
CPBEQU
Definition: cpbequ.f:132
subroutine cpbcon(UPLO, N, KD, AB, LDAB, ANORM, RCOND, WORK, RWORK, INFO)
CPBCON
Definition: cpbcon.f:135
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine cpptrf(UPLO, N, AP, INFO)
CPPTRF
Definition: cpptrf.f:121
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:144
subroutine cpocon(UPLO, N, A, LDA, ANORM, RCOND, WORK, RWORK, INFO)
CPOCON
Definition: cpocon.f:123
subroutine cpbrfs(UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CPBRFS
Definition: cpbrfs.f:191
subroutine cppcon(UPLO, N, AP, ANORM, RCOND, WORK, RWORK, INFO)
CPPCON
Definition: cppcon.f:120
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine cpotrs(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
CPOTRS
Definition: cpotrs.f:112
subroutine cpptri(UPLO, N, AP, INFO)
CPPTRI
Definition: cpptri.f:95
subroutine cpoequb(N, A, LDA, S, SCOND, AMAX, INFO)
CPOEQUB
Definition: cpoequb.f:115
subroutine cpoequ(N, A, LDA, S, SCOND, AMAX, INFO)
CPOEQU
Definition: cpoequ.f:115
subroutine cpprfs(UPLO, N, NRHS, AP, AFP, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CPPRFS
Definition: cpprfs.f:173
subroutine cpotrf(UPLO, N, A, LDA, INFO)
CPOTRF
Definition: cpotrf.f:109
subroutine cpotf2(UPLO, N, A, LDA, INFO)
CPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition: cpotf2.f:111
subroutine cpbtrf(UPLO, N, KD, AB, LDAB, INFO)
CPBTRF
Definition: cpbtrf.f:144
subroutine cppequ(UPLO, N, AP, S, SCOND, AMAX, INFO)
CPPEQU
Definition: cppequ.f:119
subroutine cerrpo(PATH, NUNIT)
CERRPO
Definition: cerrpo.f:57
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:395
subroutine cpbtrs(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO)
CPBTRS
Definition: cpbtrs.f:123