LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
zerrsy.f
Go to the documentation of this file.
1 *> \brief \b ZERRSY
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 ZERRSY( 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 *> ZERRSY tests the error exits for the COMPLEX*16 routines
25 *> for symmetric 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 December 2016
52 *
53 *> \ingroup complex16_lin
54 *
55 * =====================================================================
56  SUBROUTINE zerrsy( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.7.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 * December 2016
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*2 C2
76  INTEGER I, INFO, J
77  DOUBLE PRECISION ANRM, RCOND
78 * ..
79 * .. Local Arrays ..
80  INTEGER IP( nmax )
81  DOUBLE PRECISION R( nmax ), R1( nmax ), R2( nmax )
82  COMPLEX*16 A( nmax, nmax ), AF( nmax, nmax ), B( nmax ),
83  $ e( nmax ), w( 2*nmax ), x( nmax )
84 * ..
85 * .. External Functions ..
86  LOGICAL LSAMEN
87  EXTERNAL lsamen
88 * ..
89 * .. External Subroutines ..
90  EXTERNAL alaesm, chkxer, zspcon, zsprfs, zsptrf, zsptri,
94  $ zsytri_3x, zsytri_rook, zsytri2, zsytri2z,
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  e( j ) = 0.d0
126  r1( j ) = 0.d0
127  r2( j ) = 0.d0
128  w( j ) = 0.d0
129  x( j ) = 0.d0
130  ip( j ) = j
131  20 CONTINUE
132  anrm = 1.0d0
133  ok = .true.
134 *
135  IF( lsamen( 2, c2, 'SY' ) ) THEN
136 *
137 * Test error exits of the routines that use factorization
138 * of a symmetric indefinite matrix with patrial
139 * (Bunch-Kaufman) diagonal pivoting method.
140 *
141 * ZSYTRF
142 *
143  srnamt = 'ZSYTRF'
144  infot = 1
145  CALL zsytrf( '/', 0, a, 1, ip, w, 1, info )
146  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
147  infot = 2
148  CALL zsytrf( 'U', -1, a, 1, ip, w, 1, info )
149  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
150  infot = 4
151  CALL zsytrf( 'U', 2, a, 1, ip, w, 4, info )
152  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
153  infot = 7
154  CALL zsytrf( 'U', 0, a, 1, ip, w, 0, info )
155  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
156  infot = 7
157  CALL zsytrf( 'U', 0, a, 1, ip, w, -2, info )
158  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
159 *
160 * ZSYTF2
161 *
162  srnamt = 'ZSYTF2'
163  infot = 1
164  CALL zsytf2( '/', 0, a, 1, ip, info )
165  CALL chkxer( 'ZSYTF2', infot, nout, lerr, ok )
166  infot = 2
167  CALL zsytf2( 'U', -1, a, 1, ip, info )
168  CALL chkxer( 'ZSYTF2', infot, nout, lerr, ok )
169  infot = 4
170  CALL zsytf2( 'U', 2, a, 1, ip, info )
171  CALL chkxer( 'ZSYTF2', infot, nout, lerr, ok )
172 *
173 * ZSYTRI
174 *
175  srnamt = 'ZSYTRI'
176  infot = 1
177  CALL zsytri( '/', 0, a, 1, ip, w, info )
178  CALL chkxer( 'ZSYTRI', infot, nout, lerr, ok )
179  infot = 2
180  CALL zsytri( 'U', -1, a, 1, ip, w, info )
181  CALL chkxer( 'ZSYTRI', infot, nout, lerr, ok )
182  infot = 4
183  CALL zsytri( 'U', 2, a, 1, ip, w, info )
184  CALL chkxer( 'ZSYTRI', infot, nout, lerr, ok )
185 *
186 * ZSYTRI2
187 *
188  srnamt = 'ZSYTRI2'
189  infot = 1
190  CALL zsytri2( '/', 0, a, 1, ip, w, 1, info )
191  CALL chkxer( 'ZSYTRI2', infot, nout, lerr, ok )
192  infot = 2
193  CALL zsytri2( 'U', -1, a, 1, ip, w, 1, info )
194  CALL chkxer( 'ZSYTRI2', infot, nout, lerr, ok )
195  infot = 4
196  CALL zsytri2( 'U', 2, a, 1, ip, w, 1, info )
197  CALL chkxer( 'ZSYTRI2', infot, nout, lerr, ok )
198 *
199 * ZSYTRI2X
200 *
201  srnamt = 'ZSYTRI2X'
202  infot = 1
203  CALL zsytri2x( '/', 0, a, 1, ip, w, 1, info )
204  CALL chkxer( 'ZSYTRI2X', infot, nout, lerr, ok )
205  infot = 2
206  CALL zsytri2x( 'U', -1, a, 1, ip, w, 1, info )
207  CALL chkxer( 'ZSYTRI2X', infot, nout, lerr, ok )
208  infot = 4
209  CALL zsytri2x( 'U', 2, a, 1, ip, w, 1, info )
210  CALL chkxer( 'ZSYTRI2X', infot, nout, lerr, ok )
211 *
212 * ZSYTRS
213 *
214  srnamt = 'ZSYTRS'
215  infot = 1
216  CALL zsytrs( '/', 0, 0, a, 1, ip, b, 1, info )
217  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
218  infot = 2
219  CALL zsytrs( 'U', -1, 0, a, 1, ip, b, 1, info )
220  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
221  infot = 3
222  CALL zsytrs( 'U', 0, -1, a, 1, ip, b, 1, info )
223  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
224  infot = 5
225  CALL zsytrs( 'U', 2, 1, a, 1, ip, b, 2, info )
226  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
227  infot = 8
228  CALL zsytrs( 'U', 2, 1, a, 2, ip, b, 1, info )
229  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
230 *
231 * ZSYRFS
232 *
233  srnamt = 'ZSYRFS'
234  infot = 1
235  CALL zsyrfs( '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
236  $ r, info )
237  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
238  infot = 2
239  CALL zsyrfs( 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
240  $ w, r, info )
241  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
242  infot = 3
243  CALL zsyrfs( 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
244  $ w, r, info )
245  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
246  infot = 5
247  CALL zsyrfs( 'U', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
248  $ r, info )
249  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
250  infot = 7
251  CALL zsyrfs( 'U', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
252  $ r, info )
253  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
254  infot = 10
255  CALL zsyrfs( 'U', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
256  $ r, info )
257  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
258  infot = 12
259  CALL zsyrfs( 'U', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
260  $ r, info )
261  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
262 *
263 * ZSYCON
264 *
265  srnamt = 'ZSYCON'
266  infot = 1
267  CALL zsycon( '/', 0, a, 1, ip, anrm, rcond, w, info )
268  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
269  infot = 2
270  CALL zsycon( 'U', -1, a, 1, ip, anrm, rcond, w, info )
271  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
272  infot = 4
273  CALL zsycon( 'U', 2, a, 1, ip, anrm, rcond, w, info )
274  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
275  infot = 6
276  CALL zsycon( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
277  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
278 *
279  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
280 *
281 * Test error exits of the routines that use factorization
282 * of a symmetric indefinite matrix with rook
283 * (bounded Bunch-Kaufman) diagonal pivoting method.
284 *
285 * ZSYTRF_ROOK
286 *
287  srnamt = 'ZSYTRF_ROOK'
288  infot = 1
289  CALL zsytrf_rook( '/', 0, a, 1, ip, w, 1, info )
290  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
291  infot = 2
292  CALL zsytrf_rook( 'U', -1, a, 1, ip, w, 1, info )
293  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
294  infot = 4
295  CALL zsytrf_rook( 'U', 2, a, 1, ip, w, 4, info )
296  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
297  infot = 7
298  CALL zsytrf_rook( 'U', 0, a, 1, ip, w, 0, info )
299  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
300  infot = 7
301  CALL zsytrf_rook( 'U', 0, a, 1, ip, w, -2, info )
302  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
303 *
304 * ZSYTF2_ROOK
305 *
306  srnamt = 'ZSYTF2_ROOK'
307  infot = 1
308  CALL zsytf2_rook( '/', 0, a, 1, ip, info )
309  CALL chkxer( 'ZSYTF2_ROOK', infot, nout, lerr, ok )
310  infot = 2
311  CALL zsytf2_rook( 'U', -1, a, 1, ip, info )
312  CALL chkxer( 'ZSYTF2_ROOK', infot, nout, lerr, ok )
313  infot = 4
314  CALL zsytf2_rook( 'U', 2, a, 1, ip, info )
315  CALL chkxer( 'ZSYTF2_ROOK', infot, nout, lerr, ok )
316 *
317 * ZSYTRI_ROOK
318 *
319  srnamt = 'ZSYTRI_ROOK'
320  infot = 1
321  CALL zsytri_rook( '/', 0, a, 1, ip, w, info )
322  CALL chkxer( 'ZSYTRI_ROOK', infot, nout, lerr, ok )
323  infot = 2
324  CALL zsytri_rook( 'U', -1, a, 1, ip, w, info )
325  CALL chkxer( 'ZSYTRI_ROOK', infot, nout, lerr, ok )
326  infot = 4
327  CALL zsytri_rook( 'U', 2, a, 1, ip, w, info )
328  CALL chkxer( 'ZSYTRI_ROOK', infot, nout, lerr, ok )
329 *
330 * ZSYTRS_ROOK
331 *
332  srnamt = 'ZSYTRS_ROOK'
333  infot = 1
334  CALL zsytrs_rook( '/', 0, 0, a, 1, ip, b, 1, info )
335  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
336  infot = 2
337  CALL zsytrs_rook( 'U', -1, 0, a, 1, ip, b, 1, info )
338  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
339  infot = 3
340  CALL zsytrs_rook( 'U', 0, -1, a, 1, ip, b, 1, info )
341  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
342  infot = 5
343  CALL zsytrs_rook( 'U', 2, 1, a, 1, ip, b, 2, info )
344  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
345  infot = 8
346  CALL zsytrs_rook( 'U', 2, 1, a, 2, ip, b, 1, info )
347  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
348 *
349 * ZSYCON_ROOK
350 *
351  srnamt = 'ZSYCON_ROOK'
352  infot = 1
353  CALL zsycon_rook( '/', 0, a, 1, ip, anrm, rcond, w, info )
354  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
355  infot = 2
356  CALL zsycon_rook( 'U', -1, a, 1, ip, anrm, rcond, w, info )
357  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
358  infot = 4
359  CALL zsycon_rook( 'U', 2, a, 1, ip, anrm, rcond, w, info )
360  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
361  infot = 6
362  CALL zsycon_rook( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
363  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
364 *
365  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
366 *
367 * Test error exits of the routines that use factorization
368 * of a symmetric indefinite matrix with rook
369 * (bounded Bunch-Kaufman) pivoting with the new storage
370 * format for factors L ( or U) and D.
371 *
372 * L (or U) is stored in A, diagonal of D is stored on the
373 * diagonal of A, subdiagonal of D is stored in a separate array E.
374 *
375 * ZSYTRF_RK
376 *
377  srnamt = 'ZSYTRF_RK'
378  infot = 1
379  CALL zsytrf_rk( '/', 0, a, 1, e, ip, w, 1, info )
380  CALL chkxer( 'ZSYTRF_RK', infot, nout, lerr, ok )
381  infot = 2
382  CALL zsytrf_rk( 'U', -1, a, 1, e, ip, w, 1, info )
383  CALL chkxer( 'ZSYTRF_RK', infot, nout, lerr, ok )
384  infot = 4
385  CALL zsytrf_rk( 'U', 2, a, 1, e, ip, w, 4, info )
386  CALL chkxer( 'ZSYTRF_RK', infot, nout, lerr, ok )
387  infot = 8
388  CALL zsytrf_rk( 'U', 0, a, 1, e, ip, w, 0, info )
389  CALL chkxer( 'ZSYTRF_RK', infot, nout, lerr, ok )
390  infot = 8
391  CALL zsytrf_rk( 'U', 0, a, 1, e, ip, w, -2, info )
392  CALL chkxer( 'ZSYTRF_RK', infot, nout, lerr, ok )
393 *
394 * ZSYTF2_RK
395 *
396  srnamt = 'ZSYTF2_RK'
397  infot = 1
398  CALL zsytf2_rk( '/', 0, a, 1, e, ip, info )
399  CALL chkxer( 'ZSYTF2_RK', infot, nout, lerr, ok )
400  infot = 2
401  CALL zsytf2_rk( 'U', -1, a, 1, e, ip, info )
402  CALL chkxer( 'ZSYTF2_RK', infot, nout, lerr, ok )
403  infot = 4
404  CALL zsytf2_rk( 'U', 2, a, 1, e, ip, info )
405  CALL chkxer( 'ZSYTF2_RK', infot, nout, lerr, ok )
406 *
407 * ZSYTRI_3
408 *
409  srnamt = 'ZSYTRI_3'
410  infot = 1
411  CALL zsytri_3( '/', 0, a, 1, e, ip, w, 1, info )
412  CALL chkxer( 'ZSYTRI_3', infot, nout, lerr, ok )
413  infot = 2
414  CALL zsytri_3( 'U', -1, a, 1, e, ip, w, 1, info )
415  CALL chkxer( 'ZSYTRI_3', infot, nout, lerr, ok )
416  infot = 4
417  CALL zsytri_3( 'U', 2, a, 1, e, ip, w, 1, info )
418  CALL chkxer( 'ZSYTRI_3', infot, nout, lerr, ok )
419  infot = 8
420  CALL zsytri_3( 'U', 0, a, 1, e, ip, w, 0, info )
421  CALL chkxer( 'ZSYTRI_3', infot, nout, lerr, ok )
422  infot = 8
423  CALL zsytri_3( 'U', 0, a, 1, e, ip, w, -2, info )
424  CALL chkxer( 'ZSYTRI_3', infot, nout, lerr, ok )
425 *
426 * ZSYTRI_3X
427 *
428  srnamt = 'ZSYTRI_3X'
429  infot = 1
430  CALL zsytri_3x( '/', 0, a, 1, e, ip, w, 1, info )
431  CALL chkxer( 'ZSYTRI_3X', infot, nout, lerr, ok )
432  infot = 2
433  CALL zsytri_3x( 'U', -1, a, 1, e, ip, w, 1, info )
434  CALL chkxer( 'ZSYTRI_3X', infot, nout, lerr, ok )
435  infot = 4
436  CALL zsytri_3x( 'U', 2, a, 1, e, ip, w, 1, info )
437  CALL chkxer( 'ZSYTRI_3X', infot, nout, lerr, ok )
438 *
439 * ZSYTRS_3
440 *
441  srnamt = 'ZSYTRS_3'
442  infot = 1
443  CALL zsytrs_3( '/', 0, 0, a, 1, e, ip, b, 1, info )
444  CALL chkxer( 'ZSYTRS_3', infot, nout, lerr, ok )
445  infot = 2
446  CALL zsytrs_3( 'U', -1, 0, a, 1, e, ip, b, 1, info )
447  CALL chkxer( 'ZSYTRS_3', infot, nout, lerr, ok )
448  infot = 3
449  CALL zsytrs_3( 'U', 0, -1, a, 1, e, ip, b, 1, info )
450  CALL chkxer( 'ZSYTRS_3', infot, nout, lerr, ok )
451  infot = 5
452  CALL zsytrs_3( 'U', 2, 1, a, 1, e, ip, b, 2, info )
453  CALL chkxer( 'ZSYTRS_3', infot, nout, lerr, ok )
454  infot = 9
455  CALL zsytrs_3( 'U', 2, 1, a, 2, e, ip, b, 1, info )
456  CALL chkxer( 'ZSYTRS_3', infot, nout, lerr, ok )
457 *
458 * ZSYCON_3
459 *
460  srnamt = 'ZSYCON_3'
461  infot = 1
462  CALL zsycon_3( '/', 0, a, 1, e, ip, anrm, rcond, w, info )
463  CALL chkxer( 'ZSYCON_3', infot, nout, lerr, ok )
464  infot = 2
465  CALL zsycon_3( 'U', -1, a, 1, e, ip, anrm, rcond, w, info )
466  CALL chkxer( 'ZSYCON_3', infot, nout, lerr, ok )
467  infot = 4
468  CALL zsycon_3( 'U', 2, a, 1, e, ip, anrm, rcond, w, info )
469  CALL chkxer( 'ZSYCON_3', infot, nout, lerr, ok )
470  infot = 7
471  CALL zsycon_3( 'U', 1, a, 1, e, ip, -1.0d0, rcond, w, info)
472  CALL chkxer( 'ZSYCON_3', infot, nout, lerr, ok )
473 *
474  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
475 *
476 * Test error exits of the routines that use factorization
477 * of a symmetric indefinite packed matrix with patrial
478 * (Bunch-Kaufman) pivoting.
479 *
480 * ZSPTRF
481 *
482  srnamt = 'ZSPTRF'
483  infot = 1
484  CALL zsptrf( '/', 0, a, ip, info )
485  CALL chkxer( 'ZSPTRF', infot, nout, lerr, ok )
486  infot = 2
487  CALL zsptrf( 'U', -1, a, ip, info )
488  CALL chkxer( 'ZSPTRF', infot, nout, lerr, ok )
489 *
490 * ZSPTRI
491 *
492  srnamt = 'ZSPTRI'
493  infot = 1
494  CALL zsptri( '/', 0, a, ip, w, info )
495  CALL chkxer( 'ZSPTRI', infot, nout, lerr, ok )
496  infot = 2
497  CALL zsptri( 'U', -1, a, ip, w, info )
498  CALL chkxer( 'ZSPTRI', infot, nout, lerr, ok )
499 *
500 * ZSPTRS
501 *
502  srnamt = 'ZSPTRS'
503  infot = 1
504  CALL zsptrs( '/', 0, 0, a, ip, b, 1, info )
505  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
506  infot = 2
507  CALL zsptrs( 'U', -1, 0, a, ip, b, 1, info )
508  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
509  infot = 3
510  CALL zsptrs( 'U', 0, -1, a, ip, b, 1, info )
511  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
512  infot = 7
513  CALL zsptrs( 'U', 2, 1, a, ip, b, 1, info )
514  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
515 *
516 * ZSPRFS
517 *
518  srnamt = 'ZSPRFS'
519  infot = 1
520  CALL zsprfs( '/', 0, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
521  $ info )
522  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
523  infot = 2
524  CALL zsprfs( 'U', -1, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
525  $ info )
526  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
527  infot = 3
528  CALL zsprfs( 'U', 0, -1, a, af, ip, b, 1, x, 1, r1, r2, w, r,
529  $ info )
530  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
531  infot = 8
532  CALL zsprfs( 'U', 2, 1, a, af, ip, b, 1, x, 2, r1, r2, w, r,
533  $ info )
534  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
535  infot = 10
536  CALL zsprfs( 'U', 2, 1, a, af, ip, b, 2, x, 1, r1, r2, w, r,
537  $ info )
538  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
539 *
540 * ZSPCON
541 *
542  srnamt = 'ZSPCON'
543  infot = 1
544  CALL zspcon( '/', 0, a, ip, anrm, rcond, w, info )
545  CALL chkxer( 'ZSPCON', infot, nout, lerr, ok )
546  infot = 2
547  CALL zspcon( 'U', -1, a, ip, anrm, rcond, w, info )
548  CALL chkxer( 'ZSPCON', infot, nout, lerr, ok )
549  infot = 5
550  CALL zspcon( 'U', 1, a, ip, -anrm, rcond, w, info )
551  CALL chkxer( 'ZSPCON', infot, nout, lerr, ok )
552 *
553  ELSE IF( lsamen( 2, c2, 'SA' ) ) THEN
554 *
555 * Test error exits of the routines that use factorization
556 * of a symmetric indefinite matrix with Aasen's algorithm.
557 *
558 * ZSYTRF_AA
559 *
560  srnamt = 'ZSYTRF_AA'
561  infot = 1
562  CALL zsytrf_aa( '/', 0, a, 1, ip, w, 1, info )
563  CALL chkxer( 'ZSYTRF_AA', infot, nout, lerr, ok )
564  infot = 2
565  CALL zsytrf_aa( 'U', -1, a, 1, ip, w, 1, info )
566  CALL chkxer( 'ZSYTRF_AA', infot, nout, lerr, ok )
567  infot = 4
568  CALL zsytrf_aa( 'U', 2, a, 1, ip, w, 4, info )
569  CALL chkxer( 'ZSYTRF_AA', infot, nout, lerr, ok )
570  infot = 7
571  CALL zsytrf_aa( 'U', 0, a, 1, ip, w, 0, info )
572  CALL chkxer( 'ZSYTRF_AA', infot, nout, lerr, ok )
573  infot = 7
574  CALL zsytrf_aa( 'U', 0, a, 1, ip, w, -2, info )
575  CALL chkxer( 'ZSYTRF_AA', infot, nout, lerr, ok )
576 *
577 * ZSYTRS_AA
578 *
579  srnamt = 'ZSYTRS_AA'
580  infot = 1
581  CALL zsytrs_aa( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
582  CALL chkxer( 'ZSYTRS_AA', infot, nout, lerr, ok )
583  infot = 2
584  CALL zsytrs_aa( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
585  CALL chkxer( 'ZSYTRS_AA', infot, nout, lerr, ok )
586  infot = 3
587  CALL zsytrs_aa( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
588  CALL chkxer( 'ZSYTRS_AA', infot, nout, lerr, ok )
589  infot = 5
590  CALL zsytrs_aa( 'U', 2, 1, a, 1, ip, b, 2, w, 1, info )
591  CALL chkxer( 'ZSYTRS_AA', infot, nout, lerr, ok )
592  infot = 8
593  CALL zsytrs_aa( 'U', 2, 1, a, 2, ip, b, 1, w, 1, info )
594  CALL chkxer( 'ZSYTRS_AA', infot, nout, lerr, ok )
595 *
596  END IF
597 *
598 * Print a summary line.
599 *
600  CALL alaesm( path, ok, nout )
601 *
602  RETURN
603 *
604 * End of ZERRSY
605 *
606  END
subroutine zsycon(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
ZSYCON
Definition: zsycon.f:127
subroutine zsptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZSPTRS
Definition: zsptrs.f:117
subroutine zerrsy(PATH, NUNIT)
ZERRSY
Definition: zerrsy.f:57
subroutine zsytri_rook(UPLO, N, A, LDA, IPIV, WORK, INFO)
ZSYTRI_ROOK
Definition: zsytri_rook.f:131
subroutine zsytri(UPLO, N, A, LDA, IPIV, WORK, INFO)
ZSYTRI
Definition: zsytri.f:116
subroutine zsptrf(UPLO, N, AP, IPIV, INFO)
ZSPTRF
Definition: zsptrf.f:160
subroutine zsytri_3x(UPLO, N, A, LDA, E, IPIV, WORK, NB, INFO)
ZSYTRI_3X
Definition: zsytri_3x.f:161
subroutine zsytrf_rook(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRF_ROOK
Definition: zsytrf_rook.f:210
subroutine zsytri_3(UPLO, N, A, LDA, E, IPIV, WORK, LWORK, INFO)
ZSYTRI_3
Definition: zsytri_3.f:172
subroutine zsytrf_aa(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRF_AA
Definition: zsytrf_aa.f:138
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine zsytf2_rook(UPLO, N, A, LDA, IPIV, INFO)
ZSYTF2_ROOK computes the factorization of a complex symmetric indefinite matrix using the bounded Bun...
Definition: zsytf2_rook.f:196
subroutine zspcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO)
ZSPCON
Definition: zspcon.f:120
subroutine zsytri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRI2
Definition: zsytri2.f:129
subroutine zsytrs_3(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, INFO)
ZSYTRS_3
Definition: zsytrs_3.f:167
subroutine zsytri2x(UPLO, N, A, LDA, IPIV, WORK, NB, INFO)
ZSYTRI2X
Definition: zsytri2x.f:122
subroutine zsytrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRF
Definition: zsytrf.f:184
subroutine zsptri(UPLO, N, AP, IPIV, WORK, INFO)
ZSPTRI
Definition: zsptri.f:111
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine zsycon_rook(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
ZSYCON_ROOK
Definition: zsycon_rook.f:141
subroutine zsytrf_rk(UPLO, N, A, LDA, E, IPIV, WORK, LWORK, INFO)
ZSYTRF_RK computes the factorization of a complex symmetric indefinite matrix using the bounded Bunch...
Definition: zsytrf_rk.f:261
subroutine zsytf2_rk(UPLO, N, A, LDA, E, IPIV, INFO)
ZSYTF2_RK computes the factorization of a complex symmetric indefinite matrix using the bounded Bunch...
Definition: zsytf2_rk.f:243
subroutine zsytrs_aa(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYTRS_AA
Definition: zsytrs_aa.f:131
subroutine zsycon_3(UPLO, N, A, LDA, E, IPIV, ANORM, RCOND, WORK, INFO)
ZSYCON_3
Definition: zsycon_3.f:173
subroutine zsytrs_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZSYTRS_ROOK
Definition: zsytrs_rook.f:138
subroutine zsyrfs(UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
ZSYRFS
Definition: zsyrfs.f:194
subroutine zsytf2(UPLO, N, A, LDA, IPIV, INFO)
ZSYTF2 computes the factorization of a real symmetric indefinite matrix, using the diagonal pivoting ...
Definition: zsytf2.f:193
subroutine zsytrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZSYTRS
Definition: zsytrs.f:122
subroutine zsprfs(UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
ZSPRFS
Definition: zsprfs.f:182