LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
cerrsyx.f
Go to the documentation of this file.
1 *> \brief \b CERRSYX
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 CERRSY( 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 *> CERRSY tests the error exits for the COMPLEX routines
25 *> for symmetric indefinite matrices.
26 *>
27 *> Note that this file is used only when the XBLAS are available,
28 *> otherwise cerrsy.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 December 2016
55 *
56 *> \ingroup complex_lin
57 *
58 * =====================================================================
59  SUBROUTINE cerrsy( PATH, NUNIT )
60 *
61 * -- LAPACK test routine (version 3.7.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 * December 2016
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  INTEGER ip( nmax )
85  REAL r( nmax ), r1( nmax ), r2( nmax ),
86  $ s( nmax ), err_bnds_n( nmax, 3 ),
87  $ err_bnds_c( nmax, 3 ), params( 1 )
88  COMPLEX a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
89  $ e( nmax), w( 2*nmax ), x( nmax )
90 * ..
91 * .. External Functions ..
92  LOGICAL lsamen
93  EXTERNAL lsamen
94 * ..
95 * .. External Subroutines ..
96  EXTERNAL alaesm, chkxer, cspcon, csprfs, csptrf, csptri,
100  $ csytrs_rook
101 * ..
102 * .. Scalars in Common ..
103  LOGICAL lerr, ok
104  CHARACTER*32 srnamt
105  INTEGER infot, nout
106 * ..
107 * .. Common blocks ..
108  COMMON / infoc / infot, nout, ok, lerr
109  COMMON / srnamc / srnamt
110 * ..
111 * .. Intrinsic Functions ..
112  INTRINSIC cmplx, real
113 * ..
114 * .. Executable Statements ..
115 *
116  nout = nunit
117  WRITE( nout, fmt = * )
118  c2 = path( 2: 3 )
119 *
120 * Set the variables to innocuous values.
121 *
122  DO 20 j = 1, nmax
123  DO 10 i = 1, nmax
124  a( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
125  af( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
126  10 CONTINUE
127  b( j ) = 0.e0
128  e( j ) = 0.e0
129  r1( j ) = 0.e0
130  r2( j ) = 0.e0
131  w( j ) = 0.e0
132  x( j ) = 0.e0
133  ip( j ) = j
134  20 CONTINUE
135  anrm = 1.0
136  ok = .true.
137 
138  IF( lsamen( 2, c2, 'SY' ) ) THEN
139 *
140 * Test error exits of the routines that use factorization
141 * of a symmetric indefinite matrix with patrial
142 * (Bunch-Kaufman) diagonal pivoting method.
143 *
144 * CSYTRF
145 *
146  srnamt = 'CSYTRF'
147  infot = 1
148  CALL csytrf( '/', 0, a, 1, ip, w, 1, info )
149  CALL chkxer( 'CSYTRF', infot, nout, lerr, ok )
150  infot = 2
151  CALL csytrf( 'U', -1, a, 1, ip, w, 1, info )
152  CALL chkxer( 'CSYTRF', infot, nout, lerr, ok )
153  infot = 4
154  CALL csytrf( 'U', 2, a, 1, ip, w, 4, info )
155  CALL chkxer( 'CSYTRF', infot, nout, lerr, ok )
156  infot = 7
157  CALL csytrf( 'U', 0, a, 1, ip, w, 0, info )
158  CALL chkxer( 'CSYTRF', infot, nout, lerr, ok )
159  infot = 7
160  CALL csytrf( 'U', 0, a, 1, ip, w, -2, info )
161  CALL chkxer( 'CSYTRF', infot, nout, lerr, ok )
162 *
163 * CSYTF2
164 *
165  srnamt = 'CSYTF2'
166  infot = 1
167  CALL csytf2( '/', 0, a, 1, ip, info )
168  CALL chkxer( 'CSYTF2', infot, nout, lerr, ok )
169  infot = 2
170  CALL csytf2( 'U', -1, a, 1, ip, info )
171  CALL chkxer( 'CSYTF2', infot, nout, lerr, ok )
172  infot = 4
173  CALL csytf2( 'U', 2, a, 1, ip, info )
174  CALL chkxer( 'CSYTF2', infot, nout, lerr, ok )
175 *
176 * CSYTRI
177 *
178  srnamt = 'CSYTRI'
179  infot = 1
180  CALL csytri( '/', 0, a, 1, ip, w, info )
181  CALL chkxer( 'CSYTRI', infot, nout, lerr, ok )
182  infot = 2
183  CALL csytri( 'U', -1, a, 1, ip, w, info )
184  CALL chkxer( 'CSYTRI', infot, nout, lerr, ok )
185  infot = 4
186  CALL csytri( 'U', 2, a, 1, ip, w, info )
187  CALL chkxer( 'CSYTRI', infot, nout, lerr, ok )
188 *
189 * CSYTRI2
190 *
191  srnamt = 'CSYTRI2'
192  infot = 1
193  CALL csytri2( '/', 0, a, 1, ip, w, 1, info )
194  CALL chkxer( 'CSYTRI2', infot, nout, lerr, ok )
195  infot = 2
196  CALL csytri2( 'U', -1, a, 1, ip, w, 1, info )
197  CALL chkxer( 'CSYTRI2', infot, nout, lerr, ok )
198  infot = 4
199  CALL csytri2( 'U', 2, a, 1, ip, w, 1, info )
200  CALL chkxer( 'CSYTRI2', infot, nout, lerr, ok )
201 *
202 * CSYTRI2X
203 *
204  srnamt = 'CSYTRI2X'
205  infot = 1
206  CALL csytri2x( '/', 0, a, 1, ip, w, 1, info )
207  CALL chkxer( 'CSYTRI2X', infot, nout, lerr, ok )
208  infot = 2
209  CALL csytri2x( 'U', -1, a, 1, ip, w, 1, info )
210  CALL chkxer( 'CSYTRI2X', infot, nout, lerr, ok )
211  infot = 4
212  CALL csytri2x( 'U', 2, a, 1, ip, w, 1, info )
213  CALL chkxer( 'CSYTRI2X', infot, nout, lerr, ok )
214 *
215 * CSYTRS
216 *
217  srnamt = 'CSYTRS'
218  infot = 1
219  CALL csytrs( '/', 0, 0, a, 1, ip, b, 1, info )
220  CALL chkxer( 'CSYTRS', infot, nout, lerr, ok )
221  infot = 2
222  CALL csytrs( 'U', -1, 0, a, 1, ip, b, 1, info )
223  CALL chkxer( 'CSYTRS', infot, nout, lerr, ok )
224  infot = 3
225  CALL csytrs( 'U', 0, -1, a, 1, ip, b, 1, info )
226  CALL chkxer( 'CSYTRS', infot, nout, lerr, ok )
227  infot = 5
228  CALL csytrs( 'U', 2, 1, a, 1, ip, b, 2, info )
229  CALL chkxer( 'CSYTRS', infot, nout, lerr, ok )
230  infot = 8
231  CALL csytrs( 'U', 2, 1, a, 2, ip, b, 1, info )
232  CALL chkxer( 'CSYTRS', infot, nout, lerr, ok )
233 *
234 * CSYRFS
235 *
236  srnamt = 'CSYRFS'
237  infot = 1
238  CALL csyrfs( '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
239  $ r, info )
240  CALL chkxer( 'CSYRFS', infot, nout, lerr, ok )
241  infot = 2
242  CALL csyrfs( 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
243  $ w, r, info )
244  CALL chkxer( 'CSYRFS', infot, nout, lerr, ok )
245  infot = 3
246  CALL csyrfs( 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
247  $ w, r, info )
248  CALL chkxer( 'CSYRFS', infot, nout, lerr, ok )
249  infot = 5
250  CALL csyrfs( 'U', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
251  $ r, info )
252  CALL chkxer( 'CSYRFS', infot, nout, lerr, ok )
253  infot = 7
254  CALL csyrfs( 'U', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
255  $ r, info )
256  CALL chkxer( 'CSYRFS', infot, nout, lerr, ok )
257  infot = 10
258  CALL csyrfs( 'U', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
259  $ r, info )
260  CALL chkxer( 'CSYRFS', infot, nout, lerr, ok )
261  infot = 12
262  CALL csyrfs( 'U', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
263  $ r, info )
264  CALL chkxer( 'CSYRFS', infot, nout, lerr, ok )
265 *
266 * CSYRFSX
267 *
268  n_err_bnds = 3
269  nparams = 0
270  srnamt = 'CSYRFSX'
271  infot = 1
272  CALL csyrfsx( '/', eq, 0, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
273  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
274  $ params, w, r, info )
275  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
276  infot = 2
277  CALL csyrfsx( 'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
278  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
279  $ params, w, r, info )
280  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
281  eq = 'N'
282  infot = 3
283  CALL csyrfsx( 'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
284  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
285  $ params, w, r, info )
286  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
287  infot = 4
288  CALL csyrfsx( 'U', eq, 0, -1, a, 1, af, 1, ip, s, b, 1, x, 1,
289  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
290  $ params, w, r, info )
291  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
292  infot = 6
293  CALL csyrfsx( 'U', eq, 2, 1, a, 1, af, 2, ip, s, b, 2, x, 2,
294  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
295  $ params, w, r, info )
296  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
297  infot = 8
298  CALL csyrfsx( 'U', eq, 2, 1, a, 2, af, 1, ip, s, b, 2, x, 2,
299  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
300  $ params, w, r, info )
301  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
302  infot = 12
303  CALL csyrfsx( 'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 1, x, 2,
304  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
305  $ params, w, r, info )
306  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
307  infot = 14
308  CALL csyrfsx( 'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 2, x, 1,
309  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
310  $ params, w, r, info )
311  CALL chkxer( 'CSYRFSX', infot, nout, lerr, ok )
312 *
313 * CSYCON
314 *
315  srnamt = 'CSYCON'
316  infot = 1
317  CALL csycon( '/', 0, a, 1, ip, anrm, rcond, w, info )
318  CALL chkxer( 'CSYCON', infot, nout, lerr, ok )
319  infot = 2
320  CALL csycon( 'U', -1, a, 1, ip, anrm, rcond, w, info )
321  CALL chkxer( 'CSYCON', infot, nout, lerr, ok )
322  infot = 4
323  CALL csycon( 'U', 2, a, 1, ip, anrm, rcond, w, info )
324  CALL chkxer( 'CSYCON', infot, nout, lerr, ok )
325  infot = 6
326  CALL csycon( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
327  CALL chkxer( 'CSYCON', infot, nout, lerr, ok )
328 *
329  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
330 *
331 * Test error exits of the routines that use factorization
332 * of a symmetric indefinite matrix with rook
333 * (bounded Bunch-Kaufman) diagonal pivoting method.
334 *
335 * CSYTRF_ROOK
336 *
337  srnamt = 'CSYTRF_ROOK'
338  infot = 1
339  CALL csytrf_rook( '/', 0, a, 1, ip, w, 1, info )
340  CALL chkxer( 'CSYTRF_ROOK', infot, nout, lerr, ok )
341  infot = 2
342  CALL csytrf_rook( 'U', -1, a, 1, ip, w, 1, info )
343  CALL chkxer( 'CSYTRF_ROOK', infot, nout, lerr, ok )
344  infot = 4
345  CALL csytrf_rook( 'U', 2, a, 1, ip, w, 4, info )
346  CALL chkxer( 'CSYTRF_ROOK', infot, nout, lerr, ok )
347  infot = 7
348  CALL csytrf_rook( 'U', 0, a, 1, ip, w, 0, info )
349  CALL chkxer( 'CSYTRF_ROOK', infot, nout, lerr, ok )
350  infot = 7
351  CALL csytrf_rook( 'U', 0, a, 1, ip, w, -2, info )
352  CALL chkxer( 'CSYTRF_ROOK', infot, nout, lerr, ok )
353 *
354 * CSYTF2_ROOK
355 *
356  srnamt = 'CSYTF2_ROOK'
357  infot = 1
358  CALL csytf2_rook( '/', 0, a, 1, ip, info )
359  CALL chkxer( 'CSYTF2_ROOK', infot, nout, lerr, ok )
360  infot = 2
361  CALL csytf2_rook( 'U', -1, a, 1, ip, info )
362  CALL chkxer( 'CSYTF2_ROOK', infot, nout, lerr, ok )
363  infot = 4
364  CALL csytf2_rook( 'U', 2, a, 1, ip, info )
365  CALL chkxer( 'CSYTF2_ROOK', infot, nout, lerr, ok )
366 *
367 * CSYTRI_ROOK
368 *
369  srnamt = 'CSYTRI_ROOK'
370  infot = 1
371  CALL csytri_rook( '/', 0, a, 1, ip, w, info )
372  CALL chkxer( 'CSYTRI_ROOK', infot, nout, lerr, ok )
373  infot = 2
374  CALL csytri_rook( 'U', -1, a, 1, ip, w, info )
375  CALL chkxer( 'CSYTRI_ROOK', infot, nout, lerr, ok )
376  infot = 4
377  CALL csytri_rook( 'U', 2, a, 1, ip, w, info )
378  CALL chkxer( 'CSYTRI_ROOK', infot, nout, lerr, ok )
379 *
380 * CSYTRS_ROOK
381 *
382  srnamt = 'CSYTRS_ROOK'
383  infot = 1
384  CALL csytrs_rook( '/', 0, 0, a, 1, ip, b, 1, info )
385  CALL chkxer( 'CSYTRS_ROOK', infot, nout, lerr, ok )
386  infot = 2
387  CALL csytrs_rook( 'U', -1, 0, a, 1, ip, b, 1, info )
388  CALL chkxer( 'CSYTRS_ROOK', infot, nout, lerr, ok )
389  infot = 3
390  CALL csytrs_rook( 'U', 0, -1, a, 1, ip, b, 1, info )
391  CALL chkxer( 'CSYTRS_ROOK', infot, nout, lerr, ok )
392  infot = 5
393  CALL csytrs_rook( 'U', 2, 1, a, 1, ip, b, 2, info )
394  CALL chkxer( 'CSYTRS_ROOK', infot, nout, lerr, ok )
395  infot = 8
396  CALL csytrs_rook( 'U', 2, 1, a, 2, ip, b, 1, info )
397  CALL chkxer( 'CSYTRS_ROOK', infot, nout, lerr, ok )
398 *
399 * CSYCON_ROOK
400 *
401  srnamt = 'CSYCON_ROOK'
402  infot = 1
403  CALL csycon_rook( '/', 0, a, 1, ip, anrm, rcond, w, info )
404  CALL chkxer( 'CSYCON_ROOK', infot, nout, lerr, ok )
405  infot = 2
406  CALL csycon_rook( 'U', -1, a, 1, ip, anrm, rcond, w, info )
407  CALL chkxer( 'CSYCON_ROOK', infot, nout, lerr, ok )
408  infot = 4
409  CALL csycon_rook( 'U', 2, a, 1, ip, anrm, rcond, w, info )
410  CALL chkxer( 'CSYCON_ROOK', infot, nout, lerr, ok )
411  infot = 6
412  CALL csycon_rook( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
413  CALL chkxer( 'CSYCON_ROOK', infot, nout, lerr, ok )
414 *
415  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
416 *
417 * Test error exits of the routines that use factorization
418 * of a symmetric indefinite matrix with rook
419 * (bounded Bunch-Kaufman) pivoting with the new storage
420 * format for factors L ( or U) and D.
421 *
422 * L (or U) is stored in A, diagonal of D is stored on the
423 * diagonal of A, subdiagonal of D is stored in a separate array E.
424 *
425 * CSYTRF_RK
426 *
427  srnamt = 'CSYTRF_RK'
428  infot = 1
429  CALL csytrf_rk( '/', 0, a, 1, e, ip, w, 1, info )
430  CALL chkxer( 'CSYTRF_RK', infot, nout, lerr, ok )
431  infot = 2
432  CALL csytrf_rk( 'U', -1, a, 1, e, ip, w, 1, info )
433  CALL chkxer( 'CSYTRF_RK', infot, nout, lerr, ok )
434  infot = 4
435  CALL csytrf_rk( 'U', 2, a, 1, e, ip, w, 4, info )
436  CALL chkxer( 'CSYTRF_RK', infot, nout, lerr, ok )
437  infot = 8
438  CALL csytrf_rk( 'U', 0, a, 1, e, ip, w, 0, info )
439  CALL chkxer( 'CSYTRF_RK', infot, nout, lerr, ok )
440  infot = 8
441  CALL csytrf_rk( 'U', 0, a, 1, e, ip, w, -2, info )
442  CALL chkxer( 'CSYTRF_RK', infot, nout, lerr, ok )
443 *
444 * CSYTF2_RK
445 *
446  srnamt = 'CSYTF2_RK'
447  infot = 1
448  CALL csytf2_rk( '/', 0, a, 1, e, ip, info )
449  CALL chkxer( 'CSYTF2_RK', infot, nout, lerr, ok )
450  infot = 2
451  CALL csytf2_rk( 'U', -1, a, 1, e, ip, info )
452  CALL chkxer( 'CSYTF2_RK', infot, nout, lerr, ok )
453  infot = 4
454  CALL csytf2_rk( 'U', 2, a, 1, e, ip, info )
455  CALL chkxer( 'CSYTF2_RK', infot, nout, lerr, ok )
456 *
457 * CSYTRI_3
458 *
459  srnamt = 'CSYTRI_3'
460  infot = 1
461  CALL csytri_3( '/', 0, a, 1, e, ip, w, 1, info )
462  CALL chkxer( 'CSYTRI_3', infot, nout, lerr, ok )
463  infot = 2
464  CALL csytri_3( 'U', -1, a, 1, e, ip, w, 1, info )
465  CALL chkxer( 'CSYTRI_3', infot, nout, lerr, ok )
466  infot = 4
467  CALL csytri_3( 'U', 2, a, 1, e, ip, w, 1, info )
468  CALL chkxer( 'CSYTRI_3', infot, nout, lerr, ok )
469  infot = 8
470  CALL csytri_3( 'U', 0, a, 1, e, ip, w, 0, info )
471  CALL chkxer( 'CSYTRI_3', infot, nout, lerr, ok )
472  infot = 8
473  CALL csytri_3( 'U', 0, a, 1, e, ip, w, -2, info )
474  CALL chkxer( 'CSYTRI_3', infot, nout, lerr, ok )
475 *
476 * CSYTRI_3X
477 *
478  srnamt = 'CSYTRI_3X'
479  infot = 1
480  CALL csytri_3x( '/', 0, a, 1, e, ip, w, 1, info )
481  CALL chkxer( 'CSYTRI_3X', infot, nout, lerr, ok )
482  infot = 2
483  CALL csytri_3x( 'U', -1, a, 1, e, ip, w, 1, info )
484  CALL chkxer( 'CSYTRI_3X', infot, nout, lerr, ok )
485  infot = 4
486  CALL csytri_3x( 'U', 2, a, 1, e, ip, w, 1, info )
487  CALL chkxer( 'CSYTRI_3X', infot, nout, lerr, ok )
488 *
489 * CSYTRS_3
490 *
491  srnamt = 'CSYTRS_3'
492  infot = 1
493  CALL csytrs_3( '/', 0, 0, a, 1, e, ip, b, 1, info )
494  CALL chkxer( 'CSYTRS_3', infot, nout, lerr, ok )
495  infot = 2
496  CALL csytrs_3( 'U', -1, 0, a, 1, e, ip, b, 1, info )
497  CALL chkxer( 'CSYTRS_3', infot, nout, lerr, ok )
498  infot = 3
499  CALL csytrs_3( 'U', 0, -1, a, 1, e, ip, b, 1, info )
500  CALL chkxer( 'CSYTRS_3', infot, nout, lerr, ok )
501  infot = 5
502  CALL csytrs_3( 'U', 2, 1, a, 1, e, ip, b, 2, info )
503  CALL chkxer( 'CSYTRS_3', infot, nout, lerr, ok )
504  infot = 9
505  CALL csytrs_3( 'U', 2, 1, a, 2, e, ip, b, 1, info )
506  CALL chkxer( 'CSYTRS_3', infot, nout, lerr, ok )
507 *
508 * CSYCON_3
509 *
510  srnamt = 'CSYCON_3'
511  infot = 1
512  CALL csycon_3( '/', 0, a, 1, e, ip, anrm, rcond, w, info )
513  CALL chkxer( 'CSYCON_3', infot, nout, lerr, ok )
514  infot = 2
515  CALL csycon_3( 'U', -1, a, 1, e, ip, anrm, rcond, w, info )
516  CALL chkxer( 'CSYCON_3', infot, nout, lerr, ok )
517  infot = 4
518  CALL csycon_3( 'U', 2, a, 1, e, ip, anrm, rcond, w, info )
519  CALL chkxer( 'CSYCON_3', infot, nout, lerr, ok )
520  infot = 7
521  CALL csycon_3( 'U', 1, a, 1, e, ip, -1.0e0, rcond, w, info)
522  CALL chkxer( 'CSYCON_3', infot, nout, lerr, ok )
523 *
524  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
525 *
526 * Test error exits of the routines that use factorization
527 * of a symmetric indefinite packed matrix with patrial
528 * (Bunch-Kaufman) diagonal pivoting method.
529 *
530 * CSPTRF
531 *
532  srnamt = 'CSPTRF'
533  infot = 1
534  CALL csptrf( '/', 0, a, ip, info )
535  CALL chkxer( 'CSPTRF', infot, nout, lerr, ok )
536  infot = 2
537  CALL csptrf( 'U', -1, a, ip, info )
538  CALL chkxer( 'CSPTRF', infot, nout, lerr, ok )
539 *
540 * CSPTRI
541 *
542  srnamt = 'CSPTRI'
543  infot = 1
544  CALL csptri( '/', 0, a, ip, w, info )
545  CALL chkxer( 'CSPTRI', infot, nout, lerr, ok )
546  infot = 2
547  CALL csptri( 'U', -1, a, ip, w, info )
548  CALL chkxer( 'CSPTRI', infot, nout, lerr, ok )
549 *
550 * CSPTRS
551 *
552  srnamt = 'CSPTRS'
553  infot = 1
554  CALL csptrs( '/', 0, 0, a, ip, b, 1, info )
555  CALL chkxer( 'CSPTRS', infot, nout, lerr, ok )
556  infot = 2
557  CALL csptrs( 'U', -1, 0, a, ip, b, 1, info )
558  CALL chkxer( 'CSPTRS', infot, nout, lerr, ok )
559  infot = 3
560  CALL csptrs( 'U', 0, -1, a, ip, b, 1, info )
561  CALL chkxer( 'CSPTRS', infot, nout, lerr, ok )
562  infot = 7
563  CALL csptrs( 'U', 2, 1, a, ip, b, 1, info )
564  CALL chkxer( 'CSPTRS', infot, nout, lerr, ok )
565 *
566 * CSPRFS
567 *
568  srnamt = 'CSPRFS'
569  infot = 1
570  CALL csprfs( '/', 0, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
571  $ info )
572  CALL chkxer( 'CSPRFS', infot, nout, lerr, ok )
573  infot = 2
574  CALL csprfs( 'U', -1, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
575  $ info )
576  CALL chkxer( 'CSPRFS', infot, nout, lerr, ok )
577  infot = 3
578  CALL csprfs( 'U', 0, -1, a, af, ip, b, 1, x, 1, r1, r2, w, r,
579  $ info )
580  CALL chkxer( 'CSPRFS', infot, nout, lerr, ok )
581  infot = 8
582  CALL csprfs( 'U', 2, 1, a, af, ip, b, 1, x, 2, r1, r2, w, r,
583  $ info )
584  CALL chkxer( 'CSPRFS', infot, nout, lerr, ok )
585  infot = 10
586  CALL csprfs( 'U', 2, 1, a, af, ip, b, 2, x, 1, r1, r2, w, r,
587  $ info )
588  CALL chkxer( 'CSPRFS', infot, nout, lerr, ok )
589 *
590 * CSPCON
591 *
592  srnamt = 'CSPCON'
593  infot = 1
594  CALL cspcon( '/', 0, a, ip, anrm, rcond, w, info )
595  CALL chkxer( 'CSPCON', infot, nout, lerr, ok )
596  infot = 2
597  CALL cspcon( 'U', -1, a, ip, anrm, rcond, w, info )
598  CALL chkxer( 'CSPCON', infot, nout, lerr, ok )
599  infot = 5
600  CALL cspcon( 'U', 1, a, ip, -anrm, rcond, w, info )
601  CALL chkxer( 'CSPCON', infot, nout, lerr, ok )
602  END IF
603 *
604 * Print a summary line.
605 *
606  CALL alaesm( path, ok, nout )
607 *
608  RETURN
609 *
610 * End of CERRSY
611 *
612  END
subroutine csytri_rook(UPLO, N, A, LDA, IPIV, WORK, INFO)
CSYTRI_ROOK
Definition: csytri_rook.f:131
subroutine csytri2x(UPLO, N, A, LDA, IPIV, WORK, NB, INFO)
CSYTRI2X
Definition: csytri2x.f:122
subroutine csyrfs(UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CSYRFS
Definition: csyrfs.f:194
subroutine csptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
CSPTRS
Definition: csptrs.f:117
subroutine cerrsy(PATH, NUNIT)
CERRSY
Definition: cerrsy.f:57
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine csycon_3(UPLO, N, A, LDA, E, IPIV, ANORM, RCOND, WORK, INFO)
CSYCON_3
Definition: csycon_3.f:173
subroutine csptri(UPLO, N, AP, IPIV, WORK, INFO)
CSPTRI
Definition: csptri.f:111
subroutine csytrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CSYTRS
Definition: csytrs.f:122
subroutine csytrf_rk(UPLO, N, A, LDA, E, IPIV, WORK, LWORK, INFO)
CSYTRF_RK computes the factorization of a complex symmetric indefinite matrix using the bounded Bunch...
Definition: csytrf_rk.f:261
subroutine csytri_3x(UPLO, N, A, LDA, E, IPIV, WORK, NB, INFO)
CSYTRI_3X
Definition: csytri_3x.f:161
subroutine csptrf(UPLO, N, AP, IPIV, INFO)
CSPTRF
Definition: csptrf.f:160
subroutine csytri(UPLO, N, A, LDA, IPIV, WORK, INFO)
CSYTRI
Definition: csytri.f:116
subroutine cspcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO)
CSPCON
Definition: cspcon.f:120
subroutine csyrfsx(UPLO, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV, S, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
CSYRFSX
Definition: csyrfsx.f:404
subroutine csprfs(UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CSPRFS
Definition: csprfs.f:182
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine csytrs_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CSYTRS_ROOK
Definition: csytrs_rook.f:138
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
subroutine csytf2_rk(UPLO, N, A, LDA, E, IPIV, INFO)
CSYTF2_RK computes the factorization of a complex symmetric indefinite matrix using the bounded Bunch...
Definition: csytf2_rk.f:243
subroutine csytrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CSYTRF
Definition: csytrf.f:184
subroutine csytrf_rook(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CSYTRF_ROOK
Definition: csytrf_rook.f:210
subroutine csycon(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
CSYCON
Definition: csycon.f:127
subroutine csytrs_3(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, INFO)
CSYTRS_3
Definition: csytrs_3.f:167
subroutine csytri_3(UPLO, N, A, LDA, E, IPIV, WORK, LWORK, INFO)
CSYTRI_3
Definition: csytri_3.f:172
subroutine csycon_rook(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
CSYCON_ROOK
Definition: csycon_rook.f:141
subroutine csytf2_rook(UPLO, N, A, LDA, IPIV, INFO)
CSYTF2_ROOK computes the factorization of a complex symmetric indefinite matrix using the bounded Bun...
Definition: csytf2_rook.f:196
subroutine csytf2(UPLO, N, A, LDA, IPIV, INFO)
CSYTF2 computes the factorization of a real symmetric indefinite matrix, using the diagonal pivoting ...
Definition: csytf2.f:193
subroutine csytri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CSYTRI2
Definition: csytri2.f:129