LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
cerrhe.f
Go to the documentation of this file.
1 *> \brief \b CERRHE
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 CERRHE( 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 *> CERRHE tests the error exits for the COMPLEX routines
25 *> for Hermitian indefinite matrices.
26 *> \endverbatim
27 *
28 * Arguments:
29 * ==========
30 *
31 *> \param[in] PATH
32 *> \verbatim
33 *> PATH is CHARACTER*3
34 *> The LAPACK path name for the routines to be tested.
35 *> \endverbatim
36 *>
37 *> \param[in] NUNIT
38 *> \verbatim
39 *> NUNIT is INTEGER
40 *> The unit number for output.
41 *> \endverbatim
42 *
43 * Authors:
44 * ========
45 *
46 *> \author Univ. of Tennessee
47 *> \author Univ. of California Berkeley
48 *> \author Univ. of Colorado Denver
49 *> \author NAG Ltd.
50 *
51 *> \date November 2017
52 *
53 *> \ingroup complex_lin
54 *
55 * =====================================================================
56  SUBROUTINE cerrhe( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.8.0) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * November 2017
62 *
63 * .. Scalar Arguments ..
64  CHARACTER*3 PATH
65  INTEGER NUNIT
66 * ..
67 *
68 * =====================================================================
69 *
70 *
71 * .. Parameters ..
72  INTEGER NMAX
73  parameter( nmax = 4 )
74 * ..
75 * .. Local Scalars ..
76  CHARACTER*2 C2
77  INTEGER I, INFO, J
78  REAL ANRM, RCOND
79 * ..
80 * .. Local Arrays ..
81  INTEGER IP( NMAX )
82  REAL R( NMAX ), R1( NMAX ), R2( NMAX )
83  COMPLEX A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
84  $ E( NMAX ), W( 2*NMAX ), X( NMAX )
85 * ..
86 * .. External Functions ..
87  LOGICAL LSAMEN
88  EXTERNAL lsamen
89 * ..
90 * .. External Subroutines ..
98  $ chptri, chptrs
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.e+0
126  e( j ) = 0.e+0
127  r1( j ) = 0.e+0
128  r2( j ) = 0.e+0
129  w( j ) = 0.e+0
130  x( j ) = 0.e+0
131  ip( j ) = j
132  20 CONTINUE
133  anrm = 1.0
134  ok = .true.
135 *
136  IF( lsamen( 2, c2, 'HE' ) ) THEN
137 *
138 * Test error exits of the routines that use factorization
139 * of a Hermitian indefinite matrix with patrial
140 * (Bunch-Kaufman) diagonal pivoting method.
141 *
142 * CHETRF
143 *
144  srnamt = 'CHETRF'
145  infot = 1
146  CALL chetrf( '/', 0, a, 1, ip, w, 1, info )
147  CALL chkxer( 'CHETRF', infot, nout, lerr, ok )
148  infot = 2
149  CALL chetrf( 'U', -1, a, 1, ip, w, 1, info )
150  CALL chkxer( 'CHETRF', infot, nout, lerr, ok )
151  infot = 4
152  CALL chetrf( 'U', 2, a, 1, ip, w, 4, info )
153  CALL chkxer( 'CHETRF', infot, nout, lerr, ok )
154  infot = 7
155  CALL chetrf( 'U', 0, a, 1, ip, w, 0, info )
156  CALL chkxer( 'CHETRF', infot, nout, lerr, ok )
157  infot = 7
158  CALL chetrf( 'U', 0, a, 1, ip, w, -2, info )
159  CALL chkxer( 'CHETRF', infot, nout, lerr, ok )
160 *
161 * CHETF2
162 *
163  srnamt = 'CHETF2'
164  infot = 1
165  CALL chetf2( '/', 0, a, 1, ip, info )
166  CALL chkxer( 'CHETF2', infot, nout, lerr, ok )
167  infot = 2
168  CALL chetf2( 'U', -1, a, 1, ip, info )
169  CALL chkxer( 'CHETF2', infot, nout, lerr, ok )
170  infot = 4
171  CALL chetf2( 'U', 2, a, 1, ip, info )
172  CALL chkxer( 'CHETF2', infot, nout, lerr, ok )
173 *
174 * CHETRI
175 *
176  srnamt = 'CHETRI'
177  infot = 1
178  CALL chetri( '/', 0, a, 1, ip, w, info )
179  CALL chkxer( 'CHETRI', infot, nout, lerr, ok )
180  infot = 2
181  CALL chetri( 'U', -1, a, 1, ip, w, info )
182  CALL chkxer( 'CHETRI', infot, nout, lerr, ok )
183  infot = 4
184  CALL chetri( 'U', 2, a, 1, ip, w, info )
185  CALL chkxer( 'CHETRI', infot, nout, lerr, ok )
186 *
187 * CHETRI2
188 *
189  srnamt = 'CHETRI2'
190  infot = 1
191  CALL chetri2( '/', 0, a, 1, ip, w, 1, info )
192  CALL chkxer( 'CHETRI2', infot, nout, lerr, ok )
193  infot = 2
194  CALL chetri2( 'U', -1, a, 1, ip, w, 1, info )
195  CALL chkxer( 'CHETRI2', infot, nout, lerr, ok )
196  infot = 4
197  CALL chetri2( 'U', 2, a, 1, ip, w, 1, info )
198  CALL chkxer( 'CHETRI2', infot, nout, lerr, ok )
199 *
200 * CHETRI2X
201 *
202  srnamt = 'CHETRI2X'
203  infot = 1
204  CALL chetri2x( '/', 0, a, 1, ip, w, 1, info )
205  CALL chkxer( 'CHETRI2X', infot, nout, lerr, ok )
206  infot = 2
207  CALL chetri2x( 'U', -1, a, 1, ip, w, 1, info )
208  CALL chkxer( 'CHETRI2X', infot, nout, lerr, ok )
209  infot = 4
210  CALL chetri2x( 'U', 2, a, 1, ip, w, 1, info )
211  CALL chkxer( 'CHETRI2X', infot, nout, lerr, ok )
212 *
213 * CHETRS
214 *
215  srnamt = 'CHETRS'
216  infot = 1
217  CALL chetrs( '/', 0, 0, a, 1, ip, b, 1, info )
218  CALL chkxer( 'CHETRS', infot, nout, lerr, ok )
219  infot = 2
220  CALL chetrs( 'U', -1, 0, a, 1, ip, b, 1, info )
221  CALL chkxer( 'CHETRS', infot, nout, lerr, ok )
222  infot = 3
223  CALL chetrs( 'U', 0, -1, a, 1, ip, b, 1, info )
224  CALL chkxer( 'CHETRS', infot, nout, lerr, ok )
225  infot = 5
226  CALL chetrs( 'U', 2, 1, a, 1, ip, b, 2, info )
227  CALL chkxer( 'CHETRS', infot, nout, lerr, ok )
228  infot = 8
229  CALL chetrs( 'U', 2, 1, a, 2, ip, b, 1, info )
230  CALL chkxer( 'CHETRS', infot, nout, lerr, ok )
231 *
232 * CHERFS
233 *
234  srnamt = 'CHERFS'
235  infot = 1
236  CALL cherfs( '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
237  $ r, info )
238  CALL chkxer( 'CHERFS', infot, nout, lerr, ok )
239  infot = 2
240  CALL cherfs( 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
241  $ w, r, info )
242  CALL chkxer( 'CHERFS', infot, nout, lerr, ok )
243  infot = 3
244  CALL cherfs( 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
245  $ w, r, info )
246  CALL chkxer( 'CHERFS', infot, nout, lerr, ok )
247  infot = 5
248  CALL cherfs( 'U', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
249  $ r, info )
250  CALL chkxer( 'CHERFS', infot, nout, lerr, ok )
251  infot = 7
252  CALL cherfs( 'U', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
253  $ r, info )
254  CALL chkxer( 'CHERFS', infot, nout, lerr, ok )
255  infot = 10
256  CALL cherfs( 'U', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
257  $ r, info )
258  CALL chkxer( 'CHERFS', infot, nout, lerr, ok )
259  infot = 12
260  CALL cherfs( 'U', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
261  $ r, info )
262  CALL chkxer( 'CHERFS', infot, nout, lerr, ok )
263 *
264 * CHECON
265 *
266  srnamt = 'CHECON'
267  infot = 1
268  CALL checon( '/', 0, a, 1, ip, anrm, rcond, w, info )
269  CALL chkxer( 'CHECON', infot, nout, lerr, ok )
270  infot = 2
271  CALL checon( 'U', -1, a, 1, ip, anrm, rcond, w, info )
272  CALL chkxer( 'CHECON', infot, nout, lerr, ok )
273  infot = 4
274  CALL checon( 'U', 2, a, 1, ip, anrm, rcond, w, info )
275  CALL chkxer( 'CHECON', infot, nout, lerr, ok )
276  infot = 6
277  CALL checon( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
278  CALL chkxer( 'CHECON', infot, nout, lerr, ok )
279 *
280  ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
281 *
282 * Test error exits of the routines that use factorization
283 * of a Hermitian indefinite matrix with rook
284 * (bounded Bunch-Kaufman) diagonal pivoting method.
285 *
286 * CHETRF_ROOK
287 *
288  srnamt = 'CHETRF_ROOK'
289  infot = 1
290  CALL chetrf_rook( '/', 0, a, 1, ip, w, 1, info )
291  CALL chkxer( 'CHETRF_ROOK', infot, nout, lerr, ok )
292  infot = 2
293  CALL chetrf_rook( 'U', -1, a, 1, ip, w, 1, info )
294  CALL chkxer( 'CHETRF_ROOK', infot, nout, lerr, ok )
295  infot = 4
296  CALL chetrf_rook( 'U', 2, a, 1, ip, w, 4, info )
297  CALL chkxer( 'CHETRF_ROOK', infot, nout, lerr, ok )
298  infot = 7
299  CALL chetrf_rook( 'U', 0, a, 1, ip, w, 0, info )
300  CALL chkxer( 'CHETRF_ROOK', infot, nout, lerr, ok )
301  infot = 7
302  CALL chetrf_rook( 'U', 0, a, 1, ip, w, -2, info )
303  CALL chkxer( 'CHETRF_ROOK', infot, nout, lerr, ok )
304 *
305 * CHETF2_ROOK
306 *
307  srnamt = 'CHETF2_ROOK'
308  infot = 1
309  CALL chetf2_rook( '/', 0, a, 1, ip, info )
310  CALL chkxer( 'CHETF2_ROOK', infot, nout, lerr, ok )
311  infot = 2
312  CALL chetf2_rook( 'U', -1, a, 1, ip, info )
313  CALL chkxer( 'CHETF2_ROOK', infot, nout, lerr, ok )
314  infot = 4
315  CALL chetf2_rook( 'U', 2, a, 1, ip, info )
316  CALL chkxer( 'CHETF2_ROOK', infot, nout, lerr, ok )
317 *
318 * CHETRI_ROOK
319 *
320  srnamt = 'CHETRI_ROOK'
321  infot = 1
322  CALL chetri_rook( '/', 0, a, 1, ip, w, info )
323  CALL chkxer( 'CHETRI_ROOK', infot, nout, lerr, ok )
324  infot = 2
325  CALL chetri_rook( 'U', -1, a, 1, ip, w, info )
326  CALL chkxer( 'CHETRI_ROOK', infot, nout, lerr, ok )
327  infot = 4
328  CALL chetri_rook( 'U', 2, a, 1, ip, w, info )
329  CALL chkxer( 'CHETRI_ROOK', infot, nout, lerr, ok )
330 *
331 * CHETRS_ROOK
332 *
333  srnamt = 'CHETRS_ROOK'
334  infot = 1
335  CALL chetrs_rook( '/', 0, 0, a, 1, ip, b, 1, info )
336  CALL chkxer( 'CHETRS_ROOK', infot, nout, lerr, ok )
337  infot = 2
338  CALL chetrs_rook( 'U', -1, 0, a, 1, ip, b, 1, info )
339  CALL chkxer( 'CHETRS_ROOK', infot, nout, lerr, ok )
340  infot = 3
341  CALL chetrs_rook( 'U', 0, -1, a, 1, ip, b, 1, info )
342  CALL chkxer( 'CHETRS_ROOK', infot, nout, lerr, ok )
343  infot = 5
344  CALL chetrs_rook( 'U', 2, 1, a, 1, ip, b, 2, info )
345  CALL chkxer( 'CHETRS_ROOK', infot, nout, lerr, ok )
346  infot = 8
347  CALL chetrs_rook( 'U', 2, 1, a, 2, ip, b, 1, info )
348  CALL chkxer( 'CHETRS_ROOK', infot, nout, lerr, ok )
349 *
350 * CHECON_ROOK
351 *
352  srnamt = 'CHECON_ROOK'
353  infot = 1
354  CALL checon_rook( '/', 0, a, 1, ip, anrm, rcond, w, info )
355  CALL chkxer( 'CHECON_ROOK', infot, nout, lerr, ok )
356  infot = 2
357  CALL checon_rook( 'U', -1, a, 1, ip, anrm, rcond, w, info )
358  CALL chkxer( 'CHECON_ROOK', infot, nout, lerr, ok )
359  infot = 4
360  CALL checon_rook( 'U', 2, a, 1, ip, anrm, rcond, w, info )
361  CALL chkxer( 'CHECON_ROOK', infot, nout, lerr, ok )
362  infot = 6
363  CALL checon_rook( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
364  CALL chkxer( 'CHECON_ROOK', infot, nout, lerr, ok )
365 *
366  ELSE IF( lsamen( 2, c2, 'HK' ) ) THEN
367 *
368 * Test error exits of the routines that use factorization
369 * of a Hermitian indefinite matrix with rook
370 * (bounded Bunch-Kaufman) pivoting with the new storage
371 * format for factors L ( or U) and D.
372 *
373 * L (or U) is stored in A, diagonal of D is stored on the
374 * diagonal of A, subdiagonal of D is stored in a separate array E.
375 *
376 * CHETRF_RK
377 *
378  srnamt = 'CHETRF_RK'
379  infot = 1
380  CALL chetrf_rk( '/', 0, a, 1, e, ip, w, 1, info )
381  CALL chkxer( 'CHETRF_RK', infot, nout, lerr, ok )
382  infot = 2
383  CALL chetrf_rk( 'U', -1, a, 1, e, ip, w, 1, info )
384  CALL chkxer( 'CHETRF_RK', infot, nout, lerr, ok )
385  infot = 4
386  CALL chetrf_rk( 'U', 2, a, 1, e, ip, w, 4, info )
387  CALL chkxer( 'CHETRF_RK', infot, nout, lerr, ok )
388  infot = 8
389  CALL chetrf_rk( 'U', 0, a, 1, e, ip, w, 0, info )
390  CALL chkxer( 'CHETRF_RK', infot, nout, lerr, ok )
391  infot = 8
392  CALL chetrf_rk( 'U', 0, a, 1, e, ip, w, -2, info )
393  CALL chkxer( 'CHETRF_RK', infot, nout, lerr, ok )
394 *
395 * CHETF2_RK
396 *
397  srnamt = 'CHETF2_RK'
398  infot = 1
399  CALL chetf2_rk( '/', 0, a, 1, e, ip, info )
400  CALL chkxer( 'CHETF2_RK', infot, nout, lerr, ok )
401  infot = 2
402  CALL chetf2_rk( 'U', -1, a, 1, e, ip, info )
403  CALL chkxer( 'CHETF2_RK', infot, nout, lerr, ok )
404  infot = 4
405  CALL chetf2_rk( 'U', 2, a, 1, e, ip, info )
406  CALL chkxer( 'CHETF2_RK', infot, nout, lerr, ok )
407 *
408 * CHETRI_3
409 *
410  srnamt = 'CHETRI_3'
411  infot = 1
412  CALL chetri_3( '/', 0, a, 1, e, ip, w, 1, info )
413  CALL chkxer( 'CHETRI_3', infot, nout, lerr, ok )
414  infot = 2
415  CALL chetri_3( 'U', -1, a, 1, e, ip, w, 1, info )
416  CALL chkxer( 'CHETRI_3', infot, nout, lerr, ok )
417  infot = 4
418  CALL chetri_3( 'U', 2, a, 1, e, ip, w, 1, info )
419  CALL chkxer( 'CHETRI_3', infot, nout, lerr, ok )
420  infot = 8
421  CALL chetri_3( 'U', 0, a, 1, e, ip, w, 0, info )
422  CALL chkxer( 'CHETRI_3', infot, nout, lerr, ok )
423  infot = 8
424  CALL chetri_3( 'U', 0, a, 1, e, ip, w, -2, info )
425  CALL chkxer( 'CHETRI_3', infot, nout, lerr, ok )
426 *
427 * CHETRI_3X
428 *
429  srnamt = 'CHETRI_3X'
430  infot = 1
431  CALL chetri_3x( '/', 0, a, 1, e, ip, w, 1, info )
432  CALL chkxer( 'CHETRI_3X', infot, nout, lerr, ok )
433  infot = 2
434  CALL chetri_3x( 'U', -1, a, 1, e, ip, w, 1, info )
435  CALL chkxer( 'CHETRI_3X', infot, nout, lerr, ok )
436  infot = 4
437  CALL chetri_3x( 'U', 2, a, 1, e, ip, w, 1, info )
438  CALL chkxer( 'CHETRI_3X', infot, nout, lerr, ok )
439 *
440 * CHETRS_3
441 *
442  srnamt = 'CHETRS_3'
443  infot = 1
444  CALL chetrs_3( '/', 0, 0, a, 1, e, ip, b, 1, info )
445  CALL chkxer( 'CHETRS_3', infot, nout, lerr, ok )
446  infot = 2
447  CALL chetrs_3( 'U', -1, 0, a, 1, e, ip, b, 1, info )
448  CALL chkxer( 'CHETRS_3', infot, nout, lerr, ok )
449  infot = 3
450  CALL chetrs_3( 'U', 0, -1, a, 1, e, ip, b, 1, info )
451  CALL chkxer( 'CHETRS_3', infot, nout, lerr, ok )
452  infot = 5
453  CALL chetrs_3( 'U', 2, 1, a, 1, e, ip, b, 2, info )
454  CALL chkxer( 'CHETRS_3', infot, nout, lerr, ok )
455  infot = 9
456  CALL chetrs_3( 'U', 2, 1, a, 2, e, ip, b, 1, info )
457  CALL chkxer( 'CHETRS_3', infot, nout, lerr, ok )
458 *
459 * CHECON_3
460 *
461  srnamt = 'CHECON_3'
462  infot = 1
463  CALL checon_3( '/', 0, a, 1, e, ip, anrm, rcond, w, info )
464  CALL chkxer( 'CHECON_3', infot, nout, lerr, ok )
465  infot = 2
466  CALL checon_3( 'U', -1, a, 1, e, ip, anrm, rcond, w, info )
467  CALL chkxer( 'CHECON_3', infot, nout, lerr, ok )
468  infot = 4
469  CALL checon_3( 'U', 2, a, 1, e, ip, anrm, rcond, w, info )
470  CALL chkxer( 'CHECON_3', infot, nout, lerr, ok )
471  infot = 7
472  CALL checon_3( 'U', 1, a, 1, e, ip, -1.0e0, rcond, w, info)
473  CALL chkxer( 'CHECON_3', infot, nout, lerr, ok )
474 *
475  ELSE IF( lsamen( 2, c2, 'HA' ) ) THEN
476 *
477 * Test error exits of the routines that use factorization
478 * of a Hermitian indefinite matrix with Aasen's algorithm.
479 *
480 * CHETRF_AA
481 *
482  srnamt = 'CHETRF_AA'
483  infot = 1
484  CALL chetrf_aa( '/', 0, a, 1, ip, w, 1, info )
485  CALL chkxer( 'CHETRF_AA', infot, nout, lerr, ok )
486  infot = 2
487  CALL chetrf_aa( 'U', -1, a, 1, ip, w, 1, info )
488  CALL chkxer( 'CHETRF_AA', infot, nout, lerr, ok )
489  infot = 4
490  CALL chetrf_aa( 'U', 2, a, 1, ip, w, 4, info )
491  CALL chkxer( 'CHETRF_AA', infot, nout, lerr, ok )
492  infot = 7
493  CALL chetrf_aa( 'U', 2, a, 2, ip, w, 0, info )
494  CALL chkxer( 'CHETRF_AA', infot, nout, lerr, ok )
495  infot = 7
496  CALL chetrf_aa( 'U', 2, a, 2, ip, w, -2, info )
497  CALL chkxer( 'CHETRF_AA', infot, nout, lerr, ok )
498 *
499 * CHETRS_AA
500 *
501  srnamt = 'CHETRS_AA'
502  infot = 1
503  CALL chetrs_aa( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
504  CALL chkxer( 'CHETRS_AA', infot, nout, lerr, ok )
505  infot = 2
506  CALL chetrs_aa( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
507  CALL chkxer( 'CHETRS_AA', infot, nout, lerr, ok )
508  infot = 3
509  CALL chetrs_aa( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
510  CALL chkxer( 'CHETRS_AA', infot, nout, lerr, ok )
511  infot = 5
512  CALL chetrs_aa( 'U', 2, 1, a, 1, ip, b, 2, w, 1, info )
513  CALL chkxer( 'CHETRS_AA', infot, nout, lerr, ok )
514  infot = 8
515  CALL chetrs_aa( 'U', 2, 1, a, 2, ip, b, 1, w, 1, info )
516  CALL chkxer( 'CHETRS_AA', infot, nout, lerr, ok )
517  infot = 10
518  CALL chetrs_aa( 'U', 2, 1, a, 2, ip, b, 2, w, 0, info )
519  CALL chkxer( 'CHETRS_AA', infot, nout, lerr, ok )
520  infot = 10
521  CALL chetrs_aa( 'U', 2, 1, a, 2, ip, b, 2, w, -2, info )
522  CALL chkxer( 'CHETRS_AA', infot, nout, lerr, ok )
523 *
524  ELSE IF( lsamen( 2, c2, 'H2' ) ) THEN
525 *
526 * Test error exits of the routines that use factorization
527 * of a symmetric indefinite matrix with Aasen's algorithm.
528 *
529 * CHETRF_AA_2STAGE
530 *
531  srnamt = 'CHETRF_AA_2STAGE'
532  infot = 1
533  CALL chetrf_aa_2stage( '/', 0, a, 1, a, 1, ip, ip, w, 1,
534  $ info )
535  CALL chkxer( 'CHETRF_AA_2STAGE', infot, nout, lerr, ok )
536  infot = 2
537  CALL chetrf_aa_2stage( 'U', -1, a, 1, a, 1, ip, ip, w, 1,
538  $ info )
539  CALL chkxer( 'CHETRF_AA_2STAGE', infot, nout, lerr, ok )
540  infot = 4
541  CALL chetrf_aa_2stage( 'U', 2, a, 1, a, 2, ip, ip, w, 1,
542  $ info )
543  CALL chkxer( 'CHETRF_AA_2STAGE', infot, nout, lerr, ok )
544  infot = 6
545  CALL chetrf_aa_2stage( 'U', 2, a, 2, a, 1, ip, ip, w, 1,
546  $ info )
547  CALL chkxer( 'CHETRF_AA_2STAGE', infot, nout, lerr, ok )
548  infot = 10
549  CALL chetrf_aa_2stage( 'U', 2, a, 2, a, 8, ip, ip, w, 0,
550  $ info )
551  CALL chkxer( 'CHETRF_AA_2STAGE', infot, nout, lerr, ok )
552 *
553 * CHETRS_AA_2STAGE
554 *
555  srnamt = 'CHETRS_AA_2STAGE'
556  infot = 1
557  CALL chetrs_aa_2stage( '/', 0, 0, a, 1, a, 1, ip, ip,
558  $ b, 1, info )
559  CALL chkxer( 'CHETRS_AA_2STAGE', infot, nout, lerr, ok )
560  infot = 2
561  CALL chetrs_aa_2stage( 'U', -1, 0, a, 1, a, 1, ip, ip,
562  $ b, 1, info )
563  CALL chkxer( 'CHETRS_AA_2STAGE', infot, nout, lerr, ok )
564  infot = 3
565  CALL chetrs_aa_2stage( 'U', 0, -1, a, 1, a, 1, ip, ip,
566  $ b, 1, info )
567  CALL chkxer( 'CHETRS_AA_2STAGE', infot, nout, lerr, ok )
568  infot = 5
569  CALL chetrs_aa_2stage( 'U', 2, 1, a, 1, a, 1, ip, ip,
570  $ b, 1, info )
571  CALL chkxer( 'CHETRS_AA_2STAGE', infot, nout, lerr, ok )
572  infot = 7
573  CALL chetrs_aa_2stage( 'U', 2, 1, a, 2, a, 1, ip, ip,
574  $ b, 1, info )
575  CALL chkxer( 'CHETRS_AA_2STAGE', infot, nout, lerr, ok )
576  infot = 11
577  CALL chetrs_aa_2stage( 'U', 2, 1, a, 2, a, 8, ip, ip,
578  $ b, 1, info )
579  CALL chkxer( 'CHETRS_AA_STAGE', infot, nout, lerr, ok )
580 *
581 * Test error exits of the routines that use factorization
582 * of a Hermitian indefinite packed matrix with patrial
583 * (Bunch-Kaufman) diagonal pivoting method.
584 *
585  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
586 *
587 * CHPTRF
588 *
589  srnamt = 'CHPTRF'
590  infot = 1
591  CALL chptrf( '/', 0, a, ip, info )
592  CALL chkxer( 'CHPTRF', infot, nout, lerr, ok )
593  infot = 2
594  CALL chptrf( 'U', -1, a, ip, info )
595  CALL chkxer( 'CHPTRF', infot, nout, lerr, ok )
596 *
597 * CHPTRI
598 *
599  srnamt = 'CHPTRI'
600  infot = 1
601  CALL chptri( '/', 0, a, ip, w, info )
602  CALL chkxer( 'CHPTRI', infot, nout, lerr, ok )
603  infot = 2
604  CALL chptri( 'U', -1, a, ip, w, info )
605  CALL chkxer( 'CHPTRI', infot, nout, lerr, ok )
606 *
607 * CHPTRS
608 *
609  srnamt = 'CHPTRS'
610  infot = 1
611  CALL chptrs( '/', 0, 0, a, ip, b, 1, info )
612  CALL chkxer( 'CHPTRS', infot, nout, lerr, ok )
613  infot = 2
614  CALL chptrs( 'U', -1, 0, a, ip, b, 1, info )
615  CALL chkxer( 'CHPTRS', infot, nout, lerr, ok )
616  infot = 3
617  CALL chptrs( 'U', 0, -1, a, ip, b, 1, info )
618  CALL chkxer( 'CHPTRS', infot, nout, lerr, ok )
619  infot = 7
620  CALL chptrs( 'U', 2, 1, a, ip, b, 1, info )
621  CALL chkxer( 'CHPTRS', infot, nout, lerr, ok )
622 *
623 * CHPRFS
624 *
625  srnamt = 'CHPRFS'
626  infot = 1
627  CALL chprfs( '/', 0, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
628  $ info )
629  CALL chkxer( 'CHPRFS', infot, nout, lerr, ok )
630  infot = 2
631  CALL chprfs( 'U', -1, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
632  $ info )
633  CALL chkxer( 'CHPRFS', infot, nout, lerr, ok )
634  infot = 3
635  CALL chprfs( 'U', 0, -1, a, af, ip, b, 1, x, 1, r1, r2, w, r,
636  $ info )
637  CALL chkxer( 'CHPRFS', infot, nout, lerr, ok )
638  infot = 8
639  CALL chprfs( 'U', 2, 1, a, af, ip, b, 1, x, 2, r1, r2, w, r,
640  $ info )
641  CALL chkxer( 'CHPRFS', infot, nout, lerr, ok )
642  infot = 10
643  CALL chprfs( 'U', 2, 1, a, af, ip, b, 2, x, 1, r1, r2, w, r,
644  $ info )
645  CALL chkxer( 'CHPRFS', infot, nout, lerr, ok )
646 *
647 * CHPCON
648 *
649  srnamt = 'CHPCON'
650  infot = 1
651  CALL chpcon( '/', 0, a, ip, anrm, rcond, w, info )
652  CALL chkxer( 'CHPCON', infot, nout, lerr, ok )
653  infot = 2
654  CALL chpcon( 'U', -1, a, ip, anrm, rcond, w, info )
655  CALL chkxer( 'CHPCON', infot, nout, lerr, ok )
656  infot = 5
657  CALL chpcon( 'U', 1, a, ip, -anrm, rcond, w, info )
658  CALL chkxer( 'CHPCON', infot, nout, lerr, ok )
659  END IF
660 *
661 * Print a summary line.
662 *
663  CALL alaesm( path, ok, nout )
664 *
665  RETURN
666 *
667 * End of CERRHE
668 *
669  END
chetf2_rook
subroutine chetf2_rook(UPLO, N, A, LDA, IPIV, INFO)
CHETF2_ROOK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bun...
Definition: chetf2_rook.f:196
chetf2_rk
subroutine chetf2_rk(UPLO, N, A, LDA, E, IPIV, INFO)
CHETF2_RK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bunch...
Definition: chetf2_rk.f:243
alaesm
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
chetrs_3
subroutine chetrs_3(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, INFO)
CHETRS_3
Definition: chetrs_3.f:167
checon
subroutine checon(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
CHECON
Definition: checon.f:127
chetrs_aa_2stage
subroutine chetrs_aa_2stage(UPLO, N, NRHS, A, LDA, TB, LTB, IPIV, IPIV2, B, LDB, INFO)
CHETRS_AA_2STAGE
Definition: chetrs_aa_2stage.f:143
checon_rook
subroutine checon_rook(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
CHECON_ROOK estimates the reciprocal of the condition number fort HE matrices using factorization obt...
Definition: checon_rook.f:141
chptrf
subroutine chptrf(UPLO, N, AP, IPIV, INFO)
CHPTRF
Definition: chptrf.f:161
chetrs_aa
subroutine chetrs_aa(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
CHETRS_AA
Definition: chetrs_aa.f:133
chetrf_rook
subroutine chetrf_rook(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRF_ROOK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bun...
Definition: chetrf_rook.f:214
chetri2x
subroutine chetri2x(UPLO, N, A, LDA, IPIV, WORK, NB, INFO)
CHETRI2X
Definition: chetri2x.f:122
chetrf_rk
subroutine chetrf_rk(UPLO, N, A, LDA, E, IPIV, WORK, LWORK, INFO)
CHETRF_RK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bunch...
Definition: chetrf_rk.f:261
chptri
subroutine chptri(UPLO, N, AP, IPIV, WORK, INFO)
CHPTRI
Definition: chptri.f:111
chetrf
subroutine chetrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRF
Definition: chetrf.f:179
checon_3
subroutine checon_3(UPLO, N, A, LDA, E, IPIV, ANORM, RCOND, WORK, INFO)
CHECON_3
Definition: checon_3.f:168
chkxer
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
chetrs_rook
subroutine chetrs_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CHETRS_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using fac...
Definition: chetrs_rook.f:138
chetri_3
subroutine chetri_3(UPLO, N, A, LDA, E, IPIV, WORK, LWORK, INFO)
CHETRI_3
Definition: chetri_3.f:172
chetrf_aa_2stage
subroutine chetrf_aa_2stage(UPLO, N, A, LDA, TB, LTB, IPIV, IPIV2, WORK, LWORK, INFO)
CHETRF_AA_2STAGE
Definition: chetrf_aa_2stage.f:162
cerrhe
subroutine cerrhe(PATH, NUNIT)
CERRHE
Definition: cerrhe.f:57
chetri2
subroutine chetri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRI2
Definition: chetri2.f:129
chetrs
subroutine chetrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CHETRS
Definition: chetrs.f:122
chprfs
subroutine chprfs(UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CHPRFS
Definition: chprfs.f:182
cherfs
subroutine cherfs(UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CHERFS
Definition: cherfs.f:194
chetrf_aa
subroutine chetrf_aa(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRF_AA
Definition: chetrf_aa.f:134
chetri_3x
subroutine chetri_3x(UPLO, N, A, LDA, E, IPIV, WORK, NB, INFO)
CHETRI_3X
Definition: chetri_3x.f:161
chpcon
subroutine chpcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO)
CHPCON
Definition: chpcon.f:120
chetri
subroutine chetri(UPLO, N, A, LDA, IPIV, WORK, INFO)
CHETRI
Definition: chetri.f:116
chetri_rook
subroutine chetri_rook(UPLO, N, A, LDA, IPIV, WORK, INFO)
CHETRI_ROOK computes the inverse of HE matrix using the factorization obtained with the bounded Bunch...
Definition: chetri_rook.f:130
chptrs
subroutine chptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
CHPTRS
Definition: chptrs.f:117
csycon_3
subroutine csycon_3(UPLO, N, A, LDA, E, IPIV, ANORM, RCOND, WORK, INFO)
CSYCON_3
Definition: csycon_3.f:168
chetf2
subroutine chetf2(UPLO, N, A, LDA, IPIV, INFO)
CHETF2 computes the factorization of a complex Hermitian matrix, using the diagonal pivoting method (...
Definition: chetf2.f:188