LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zerrsyx.f
Go to the documentation of this file.
1 *> \brief \b ZERRSYX
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 *>
27 *> Note that this file is used only when the XBLAS are available,
28 *> otherwise zerrsy.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 complex16_lin
57 *
58 * =====================================================================
59  SUBROUTINE zerrsy( 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  DOUBLE PRECISION anrm, rcond, berr
82 * ..
83 * .. Local Arrays ..
84  INTEGER ip( nmax )
85  DOUBLE PRECISION r( nmax ), r1( nmax ), r2( nmax ),
86  $ s( nmax ), err_bnds_n( nmax, 3 ),
87  $ err_bnds_c( nmax, 3 ), params( 1 )
88  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
89  $ w( 2*nmax ), x( nmax )
90 * ..
91 * .. External Functions ..
92  LOGICAL lsamen
93  EXTERNAL lsamen
94 * ..
95 * .. External Subroutines ..
96  EXTERNAL alaesm, chkxer, zspcon, zsprfs, zsptrf, zsptri,
100  $ zsyrfsx
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 dble, dcmplx
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 ) = dcmplx( 1.d0 / dble( i+j ),
125  $ -1.d0 / dble( i+j ) )
126  af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
127  $ -1.d0 / dble( i+j ) )
128  10 CONTINUE
129  b( j ) = 0.d0
130  r1( j ) = 0.d0
131  r2( j ) = 0.d0
132  w( j ) = 0.d0
133  x( j ) = 0.d0
134  s( j ) = 0.d0
135  ip( j ) = j
136  20 CONTINUE
137  anrm = 1.0d0
138  ok = .true.
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  IF( lsamen( 2, c2, 'SY' ) ) THEN
145 *
146 * ZSYTRF
147 *
148  srnamt = 'ZSYTRF'
149  infot = 1
150  CALL zsytrf( '/', 0, a, 1, ip, w, 1, info )
151  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
152  infot = 2
153  CALL zsytrf( 'U', -1, a, 1, ip, w, 1, info )
154  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
155  infot = 4
156  CALL zsytrf( 'U', 2, a, 1, ip, w, 4, info )
157  CALL chkxer( 'ZSYTRF', infot, nout, lerr, ok )
158 *
159 * ZSYTF2
160 *
161  srnamt = 'ZSYTF2'
162  infot = 1
163  CALL zsytf2( '/', 0, a, 1, ip, info )
164  CALL chkxer( 'ZSYTF2', infot, nout, lerr, ok )
165  infot = 2
166  CALL zsytf2( 'U', -1, a, 1, ip, info )
167  CALL chkxer( 'ZSYTF2', infot, nout, lerr, ok )
168  infot = 4
169  CALL zsytf2( 'U', 2, a, 1, ip, info )
170  CALL chkxer( 'ZSYTF2', infot, nout, lerr, ok )
171 *
172 * ZSYTRI
173 *
174  srnamt = 'ZSYTRI'
175  infot = 1
176  CALL zsytri( '/', 0, a, 1, ip, w, info )
177  CALL chkxer( 'ZSYTRI', infot, nout, lerr, ok )
178  infot = 2
179  CALL zsytri( 'U', -1, a, 1, ip, w, info )
180  CALL chkxer( 'ZSYTRI', infot, nout, lerr, ok )
181  infot = 4
182  CALL zsytri( 'U', 2, a, 1, ip, w, info )
183  CALL chkxer( 'ZSYTRI', infot, nout, lerr, ok )
184 *
185 * ZSYTRI2
186 *
187  srnamt = 'ZSYTRI2'
188  infot = 1
189  CALL zsytri2( '/', 0, a, 1, ip, w, 1, info )
190  CALL chkxer( 'ZSYTRI2', infot, nout, lerr, ok )
191  infot = 2
192  CALL zsytri2( 'U', -1, a, 1, ip, w, 1, info )
193  CALL chkxer( 'ZSYTRI2', infot, nout, lerr, ok )
194  infot = 4
195  CALL zsytri2( 'U', 2, a, 1, ip, w, 1, info )
196  CALL chkxer( 'ZSYTRI2', infot, nout, lerr, ok )
197 *
198 * ZSYTRS
199 *
200  srnamt = 'ZSYTRS'
201  infot = 1
202  CALL zsytrs( '/', 0, 0, a, 1, ip, b, 1, info )
203  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
204  infot = 2
205  CALL zsytrs( 'U', -1, 0, a, 1, ip, b, 1, info )
206  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
207  infot = 3
208  CALL zsytrs( 'U', 0, -1, a, 1, ip, b, 1, info )
209  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
210  infot = 5
211  CALL zsytrs( 'U', 2, 1, a, 1, ip, b, 2, info )
212  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
213  infot = 8
214  CALL zsytrs( 'U', 2, 1, a, 2, ip, b, 1, info )
215  CALL chkxer( 'ZSYTRS', infot, nout, lerr, ok )
216 *
217 * ZSYRFS
218 *
219  srnamt = 'ZSYRFS'
220  infot = 1
221  CALL zsyrfs( '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
222  $ r, info )
223  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
224  infot = 2
225  CALL zsyrfs( 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
226  $ w, r, info )
227  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
228  infot = 3
229  CALL zsyrfs( 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
230  $ w, r, info )
231  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
232  infot = 5
233  CALL zsyrfs( 'U', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
234  $ r, info )
235  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
236  infot = 7
237  CALL zsyrfs( 'U', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
238  $ r, info )
239  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
240  infot = 10
241  CALL zsyrfs( 'U', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
242  $ r, info )
243  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
244  infot = 12
245  CALL zsyrfs( 'U', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
246  $ r, info )
247  CALL chkxer( 'ZSYRFS', infot, nout, lerr, ok )
248 *
249 * ZSYRFSX
250 *
251  n_err_bnds = 3
252  nparams = 0
253  srnamt = 'ZSYRFSX'
254  infot = 1
255  CALL zsyrfsx( '/', eq, 0, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
256  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
257  $ params, w, r, info )
258  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
259  infot = 2
260  CALL zsyrfsx( 'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
261  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
262  $ params, w, r, info )
263  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
264  eq = 'N'
265  infot = 3
266  CALL zsyrfsx( 'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
267  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
268  $ params, w, r, info )
269  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
270  infot = 4
271  CALL zsyrfsx( 'U', eq, 0, -1, a, 1, af, 1, ip, s, b, 1, x, 1,
272  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
273  $ params, w, r, info )
274  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
275  infot = 6
276  CALL zsyrfsx( 'U', eq, 2, 1, a, 1, af, 2, ip, s, b, 2, x, 2,
277  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
278  $ params, w, r, info )
279  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
280  infot = 8
281  CALL zsyrfsx( 'U', eq, 2, 1, a, 2, af, 1, ip, s, b, 2, x, 2,
282  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
283  $ params, w, r, info )
284  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
285  infot = 12
286  CALL zsyrfsx( 'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 1, x, 2,
287  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
288  $ params, w, r, info )
289  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
290  infot = 14
291  CALL zsyrfsx( 'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 2, x, 1,
292  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
293  $ params, w, r, info )
294  CALL chkxer( 'ZSYRFSX', infot, nout, lerr, ok )
295 *
296 * ZSYCON
297 *
298  srnamt = 'ZSYCON'
299  infot = 1
300  CALL zsycon( '/', 0, a, 1, ip, anrm, rcond, w, info )
301  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
302  infot = 2
303  CALL zsycon( 'U', -1, a, 1, ip, anrm, rcond, w, info )
304  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
305  infot = 4
306  CALL zsycon( 'U', 2, a, 1, ip, anrm, rcond, w, info )
307  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
308  infot = 6
309  CALL zsycon( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
310  CALL chkxer( 'ZSYCON', infot, nout, lerr, ok )
311 *
312 * Test error exits of the routines that use factorization
313 * of a symmetric indefinite matrix with "rook"
314 * (bounded Bunch-Kaufman) diagonal pivoting method.
315 *
316  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
317 *
318 * ZSYTRF_ROOK
319 *
320  srnamt = 'ZSYTRF_ROOK'
321  infot = 1
322  CALL zsytrf_rook( '/', 0, a, 1, ip, w, 1, info )
323  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
324  infot = 2
325  CALL zsytrf_rook( 'U', -1, a, 1, ip, w, 1, info )
326  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
327  infot = 4
328  CALL zsytrf_rook( 'U', 2, a, 1, ip, w, 4, info )
329  CALL chkxer( 'ZSYTRF_ROOK', infot, nout, lerr, ok )
330 *
331 * ZSYTF2_ROOK
332 *
333  srnamt = 'ZSYTF2_ROOK'
334  infot = 1
335  CALL zsytf2_rook( '/', 0, a, 1, ip, info )
336  CALL chkxer( 'ZSYTF2_ROOK', infot, nout, lerr, ok )
337  infot = 2
338  CALL zsytf2_rook( 'U', -1, a, 1, ip, info )
339  CALL chkxer( 'ZSYTF2_ROOK', infot, nout, lerr, ok )
340  infot = 4
341  CALL zsytf2_rook( 'U', 2, a, 1, ip, info )
342  CALL chkxer( 'ZSYTF2_ROOK', infot, nout, lerr, ok )
343 *
344 * ZSYTRI_ROOK
345 *
346  srnamt = 'ZSYTRI_ROOK'
347  infot = 1
348  CALL zsytri_rook( '/', 0, a, 1, ip, w, info )
349  CALL chkxer( 'ZSYTRI_ROOK', infot, nout, lerr, ok )
350  infot = 2
351  CALL zsytri_rook( 'U', -1, a, 1, ip, w, info )
352  CALL chkxer( 'ZSYTRI_ROOK', infot, nout, lerr, ok )
353  infot = 4
354  CALL zsytri_rook( 'U', 2, a, 1, ip, w, info )
355  CALL chkxer( 'ZSYTRI_ROOK', infot, nout, lerr, ok )
356 *
357 * ZSYTRS_ROOK
358 *
359  srnamt = 'ZSYTRS_ROOK'
360  infot = 1
361  CALL zsytrs_rook( '/', 0, 0, a, 1, ip, b, 1, info )
362  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
363  infot = 2
364  CALL zsytrs_rook( 'U', -1, 0, a, 1, ip, b, 1, info )
365  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
366  infot = 3
367  CALL zsytrs_rook( 'U', 0, -1, a, 1, ip, b, 1, info )
368  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
369  infot = 5
370  CALL zsytrs_rook( 'U', 2, 1, a, 1, ip, b, 2, info )
371  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
372  infot = 8
373  CALL zsytrs_rook( 'U', 2, 1, a, 2, ip, b, 1, info )
374  CALL chkxer( 'ZSYTRS_ROOK', infot, nout, lerr, ok )
375 *
376 * ZSYCON_ROOK
377 *
378  srnamt = 'ZSYCON_ROOK'
379  infot = 1
380  CALL zsycon_rook( '/', 0, a, 1, ip, anrm, rcond, w, info )
381  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
382  infot = 2
383  CALL zsycon_rook( 'U', -1, a, 1, ip, anrm, rcond, w, info )
384  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
385  infot = 4
386  CALL zsycon_rook( 'U', 2, a, 1, ip, anrm, rcond, w, info )
387  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
388  infot = 6
389  CALL zsycon_rook( 'U', 1, a, 1, ip, -anrm, rcond, w, info )
390  CALL chkxer( 'ZSYCON_ROOK', infot, nout, lerr, ok )
391 *
392 * Test error exits of the routines that use factorization
393 * of a symmetric indefinite packed matrix with patrial
394 * (Bunch-Kaufman) pivoting.
395 *
396  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
397 *
398 * ZSPTRF
399 *
400  srnamt = 'ZSPTRF'
401  infot = 1
402  CALL zsptrf( '/', 0, a, ip, info )
403  CALL chkxer( 'ZSPTRF', infot, nout, lerr, ok )
404  infot = 2
405  CALL zsptrf( 'U', -1, a, ip, info )
406  CALL chkxer( 'ZSPTRF', infot, nout, lerr, ok )
407 *
408 * ZSPTRI
409 *
410  srnamt = 'ZSPTRI'
411  infot = 1
412  CALL zsptri( '/', 0, a, ip, w, info )
413  CALL chkxer( 'ZSPTRI', infot, nout, lerr, ok )
414  infot = 2
415  CALL zsptri( 'U', -1, a, ip, w, info )
416  CALL chkxer( 'ZSPTRI', infot, nout, lerr, ok )
417 *
418 * ZSPTRS
419 *
420  srnamt = 'ZSPTRS'
421  infot = 1
422  CALL zsptrs( '/', 0, 0, a, ip, b, 1, info )
423  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
424  infot = 2
425  CALL zsptrs( 'U', -1, 0, a, ip, b, 1, info )
426  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
427  infot = 3
428  CALL zsptrs( 'U', 0, -1, a, ip, b, 1, info )
429  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
430  infot = 7
431  CALL zsptrs( 'U', 2, 1, a, ip, b, 1, info )
432  CALL chkxer( 'ZSPTRS', infot, nout, lerr, ok )
433 *
434 * ZSPRFS
435 *
436  srnamt = 'ZSPRFS'
437  infot = 1
438  CALL zsprfs( '/', 0, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
439  $ info )
440  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
441  infot = 2
442  CALL zsprfs( 'U', -1, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
443  $ info )
444  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
445  infot = 3
446  CALL zsprfs( 'U', 0, -1, a, af, ip, b, 1, x, 1, r1, r2, w, r,
447  $ info )
448  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
449  infot = 8
450  CALL zsprfs( 'U', 2, 1, a, af, ip, b, 1, x, 2, r1, r2, w, r,
451  $ info )
452  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
453  infot = 10
454  CALL zsprfs( 'U', 2, 1, a, af, ip, b, 2, x, 1, r1, r2, w, r,
455  $ info )
456  CALL chkxer( 'ZSPRFS', infot, nout, lerr, ok )
457 *
458 * ZSPCON
459 *
460  srnamt = 'ZSPCON'
461  infot = 1
462  CALL zspcon( '/', 0, a, ip, anrm, rcond, w, info )
463  CALL chkxer( 'ZSPCON', infot, nout, lerr, ok )
464  infot = 2
465  CALL zspcon( 'U', -1, a, ip, anrm, rcond, w, info )
466  CALL chkxer( 'ZSPCON', infot, nout, lerr, ok )
467  infot = 5
468  CALL zspcon( 'U', 1, a, ip, -anrm, rcond, w, info )
469  CALL chkxer( 'ZSPCON', infot, nout, lerr, ok )
470  END IF
471 *
472 * Print a summary line.
473 *
474  CALL alaesm( path, ok, nout )
475 *
476  RETURN
477 *
478 * End of ZERRSY
479 *
480  END
subroutine zsycon(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
ZSYCON
Definition: zsycon.f:127
subroutine zsptri(UPLO, N, AP, IPIV, WORK, INFO)
ZSPTRI
Definition: zsptri.f:111
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 zsytrf_rook(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRF_ROOK
Definition: zsytrf_rook.f:210
subroutine zsptrf(UPLO, N, AP, IPIV, INFO)
ZSPTRF
Definition: zsptrf.f:160
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
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 zsytri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRI2
Definition: zsytri2.f:129
subroutine zspcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO)
ZSPCON
Definition: zspcon.f:120
subroutine zsytrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRF
Definition: zsytrf.f:184
subroutine zsyrfsx(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)
ZSYRFSX
Definition: zsyrfsx.f:404
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 zsprfs(UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
ZSPRFS
Definition: zsprfs.f:182
subroutine zsptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZSPTRS
Definition: zsptrs.f:117
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