LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
subroutine zerrvx ( character*3  PATH,
integer  NUNIT 
)

ZERRVX

ZERRVXX

Purpose:
 ZERRVX tests the error exits for the COMPLEX*16 driver routines
 for solving linear systems of equations.
Parameters
[in]PATH
          PATH is CHARACTER*3
          The LAPACK path name for the routines to be tested.
[in]NUNIT
          NUNIT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
December 2016

Definition at line 57 of file zerrvx.f.

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 eq
76  CHARACTER*2 c2
77  INTEGER i, info, j
78  DOUBLE PRECISION rcond
79 * ..
80 * .. Local Arrays ..
81  INTEGER ip( nmax )
82  DOUBLE PRECISION c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
83  $ rf( nmax ), rw( nmax )
84  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
85  $ e( nmax ), w( 2*nmax ), x( nmax )
86 * ..
87 * .. External Functions ..
88  LOGICAL lsamen
89  EXTERNAL lsamen
90 * ..
91 * .. External Subroutines ..
92  EXTERNAL chkxer, zgbsv, zgbsvx, zgesv, zgesvx, zgtsv,
97  $ zsysvx
98 * ..
99 * .. Scalars in Common ..
100  LOGICAL lerr, ok
101  CHARACTER*32 srnamt
102  INTEGER infot, nout
103 * ..
104 * .. Common blocks ..
105  COMMON / infoc / infot, nout, ok, lerr
106  COMMON / srnamc / srnamt
107 * ..
108 * .. Intrinsic Functions ..
109  INTRINSIC dble, dcmplx
110 * ..
111 * .. Executable Statements ..
112 *
113  nout = nunit
114  WRITE( nout, fmt = * )
115  c2 = path( 2: 3 )
116 *
117 * Set the variables to innocuous values.
118 *
119  DO 20 j = 1, nmax
120  DO 10 i = 1, nmax
121  a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
122  $ -1.d0 / dble( i+j ) )
123  af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
124  $ -1.d0 / dble( i+j ) )
125  10 CONTINUE
126  b( j ) = 0.d0
127  e( j ) = 0.d0
128  r1( j ) = 0.d0
129  r2( j ) = 0.d0
130  w( j ) = 0.d0
131  x( j ) = 0.d0
132  c( j ) = 0.d0
133  r( j ) = 0.d0
134  ip( j ) = j
135  20 CONTINUE
136  eq = ' '
137  ok = .true.
138 *
139  IF( lsamen( 2, c2, 'GE' ) ) THEN
140 *
141 * ZGESV
142 *
143  srnamt = 'ZGESV '
144  infot = 1
145  CALL zgesv( -1, 0, a, 1, ip, b, 1, info )
146  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
147  infot = 2
148  CALL zgesv( 0, -1, a, 1, ip, b, 1, info )
149  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
150  infot = 4
151  CALL zgesv( 2, 1, a, 1, ip, b, 2, info )
152  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
153  infot = 7
154  CALL zgesv( 2, 1, a, 2, ip, b, 1, info )
155  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
156 *
157 * ZGESVX
158 *
159  srnamt = 'ZGESVX'
160  infot = 1
161  CALL zgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
162  $ x, 1, rcond, r1, r2, w, rw, info )
163  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
164  infot = 2
165  CALL zgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
166  $ x, 1, rcond, r1, r2, w, rw, info )
167  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
168  infot = 3
169  CALL zgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
170  $ x, 1, rcond, r1, r2, w, rw, info )
171  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
172  infot = 4
173  CALL zgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
174  $ x, 1, rcond, r1, r2, w, rw, info )
175  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
176  infot = 6
177  CALL zgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
178  $ x, 2, rcond, r1, r2, w, rw, info )
179  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
180  infot = 8
181  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
182  $ x, 2, rcond, r1, r2, w, rw, info )
183  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
184  infot = 10
185  eq = '/'
186  CALL zgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
187  $ x, 1, rcond, r1, r2, w, rw, info )
188  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
189  infot = 11
190  eq = 'R'
191  CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
192  $ x, 1, rcond, r1, r2, w, rw, info )
193  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
194  infot = 12
195  eq = 'C'
196  CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
197  $ x, 1, rcond, r1, r2, w, rw, info )
198  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
199  infot = 14
200  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
201  $ x, 2, rcond, r1, r2, w, rw, info )
202  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
203  infot = 16
204  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
205  $ x, 1, rcond, r1, r2, w, rw, info )
206  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
207 *
208  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
209 *
210 * ZGBSV
211 *
212  srnamt = 'ZGBSV '
213  infot = 1
214  CALL zgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
215  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
216  infot = 2
217  CALL zgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
218  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
219  infot = 3
220  CALL zgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
221  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
222  infot = 4
223  CALL zgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
224  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
225  infot = 6
226  CALL zgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
227  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
228  infot = 9
229  CALL zgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
230  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
231 *
232 * ZGBSVX
233 *
234  srnamt = 'ZGBSVX'
235  infot = 1
236  CALL zgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
237  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
238  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
239  infot = 2
240  CALL zgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
241  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
242  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
243  infot = 3
244  CALL zgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
245  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
246  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
247  infot = 4
248  CALL zgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
249  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
250  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
251  infot = 5
252  CALL zgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
253  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
254  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
255  infot = 6
256  CALL zgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
257  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
258  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
259  infot = 8
260  CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
261  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
262  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
263  infot = 10
264  CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
265  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
266  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
267  infot = 12
268  eq = '/'
269  CALL zgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
270  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
271  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
272  infot = 13
273  eq = 'R'
274  CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
275  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
276  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
277  infot = 14
278  eq = 'C'
279  CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
280  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
281  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
282  infot = 16
283  CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
284  $ b, 1, x, 2, rcond, r1, r2, w, rw, info )
285  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
286  infot = 18
287  CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
288  $ b, 2, x, 1, rcond, r1, r2, w, rw, info )
289  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
290 *
291  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
292 *
293 * ZGTSV
294 *
295  srnamt = 'ZGTSV '
296  infot = 1
297  CALL zgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
298  $ info )
299  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
300  infot = 2
301  CALL zgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
302  $ info )
303  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
304  infot = 7
305  CALL zgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
306  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
307 *
308 * ZGTSVX
309 *
310  srnamt = 'ZGTSVX'
311  infot = 1
312  CALL zgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
313  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
314  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
315  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
316  infot = 2
317  CALL zgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
318  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
319  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
320  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
321  infot = 3
322  CALL zgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
323  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
324  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
325  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
326  infot = 4
327  CALL zgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
328  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
329  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
330  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
331  infot = 14
332  CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
333  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
334  $ ip, b, 1, x, 2, rcond, r1, r2, w, rw, info )
335  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
336  infot = 16
337  CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
338  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
339  $ ip, b, 2, x, 1, rcond, r1, r2, w, rw, info )
340  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
341 *
342  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
343 *
344 * ZPOSV
345 *
346  srnamt = 'ZPOSV '
347  infot = 1
348  CALL zposv( '/', 0, 0, a, 1, b, 1, info )
349  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
350  infot = 2
351  CALL zposv( 'U', -1, 0, a, 1, b, 1, info )
352  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
353  infot = 3
354  CALL zposv( 'U', 0, -1, a, 1, b, 1, info )
355  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
356  infot = 5
357  CALL zposv( 'U', 2, 0, a, 1, b, 2, info )
358  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
359  infot = 7
360  CALL zposv( 'U', 2, 0, a, 2, b, 1, info )
361  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
362 *
363 * ZPOSVX
364 *
365  srnamt = 'ZPOSVX'
366  infot = 1
367  CALL zposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
368  $ rcond, r1, r2, w, rw, info )
369  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
370  infot = 2
371  CALL zposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
372  $ rcond, r1, r2, w, rw, info )
373  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
374  infot = 3
375  CALL zposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
376  $ rcond, r1, r2, w, rw, info )
377  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
378  infot = 4
379  CALL zposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
380  $ rcond, r1, r2, w, rw, info )
381  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
382  infot = 6
383  CALL zposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
384  $ rcond, r1, r2, w, rw, info )
385  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
386  infot = 8
387  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
388  $ rcond, r1, r2, w, rw, info )
389  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
390  infot = 9
391  eq = '/'
392  CALL zposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
393  $ rcond, r1, r2, w, rw, info )
394  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
395  infot = 10
396  eq = 'Y'
397  CALL zposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
398  $ rcond, r1, r2, w, rw, info )
399  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
400  infot = 12
401  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
402  $ rcond, r1, r2, w, rw, info )
403  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
404  infot = 14
405  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
406  $ rcond, r1, r2, w, rw, info )
407  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
408 *
409  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
410 *
411 * ZPPSV
412 *
413  srnamt = 'ZPPSV '
414  infot = 1
415  CALL zppsv( '/', 0, 0, a, b, 1, info )
416  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
417  infot = 2
418  CALL zppsv( 'U', -1, 0, a, b, 1, info )
419  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
420  infot = 3
421  CALL zppsv( 'U', 0, -1, a, b, 1, info )
422  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
423  infot = 6
424  CALL zppsv( 'U', 2, 0, a, b, 1, info )
425  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
426 *
427 * ZPPSVX
428 *
429  srnamt = 'ZPPSVX'
430  infot = 1
431  CALL zppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
432  $ r1, r2, w, rw, info )
433  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
434  infot = 2
435  CALL zppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
436  $ r1, r2, w, rw, info )
437  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
438  infot = 3
439  CALL zppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
440  $ r1, r2, w, rw, info )
441  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
442  infot = 4
443  CALL zppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
444  $ r1, r2, w, rw, info )
445  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
446  infot = 7
447  eq = '/'
448  CALL zppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
449  $ r1, r2, w, rw, info )
450  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
451  infot = 8
452  eq = 'Y'
453  CALL zppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
454  $ r1, r2, w, rw, info )
455  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
456  infot = 10
457  CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
458  $ r1, r2, w, rw, info )
459  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
460  infot = 12
461  CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
462  $ r1, r2, w, rw, info )
463  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
464 *
465  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
466 *
467 * ZPBSV
468 *
469  srnamt = 'ZPBSV '
470  infot = 1
471  CALL zpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
472  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
473  infot = 2
474  CALL zpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
475  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
476  infot = 3
477  CALL zpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
478  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
479  infot = 4
480  CALL zpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
481  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
482  infot = 6
483  CALL zpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
484  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
485  infot = 8
486  CALL zpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
487  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
488 *
489 * ZPBSVX
490 *
491  srnamt = 'ZPBSVX'
492  infot = 1
493  CALL zpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
494  $ rcond, r1, r2, w, rw, info )
495  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
496  infot = 2
497  CALL zpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
498  $ rcond, r1, r2, w, rw, info )
499  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
500  infot = 3
501  CALL zpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
502  $ 1, rcond, r1, r2, w, rw, info )
503  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
504  infot = 4
505  CALL zpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
506  $ 1, rcond, r1, r2, w, rw, info )
507  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
508  infot = 5
509  CALL zpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
510  $ 1, rcond, r1, r2, w, rw, info )
511  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
512  infot = 7
513  CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
514  $ rcond, r1, r2, w, rw, info )
515  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
516  infot = 9
517  CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
518  $ rcond, r1, r2, w, rw, info )
519  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
520  infot = 10
521  eq = '/'
522  CALL zpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
523  $ rcond, r1, r2, w, rw, info )
524  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
525  infot = 11
526  eq = 'Y'
527  CALL zpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
528  $ rcond, r1, r2, w, rw, info )
529  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
530  infot = 13
531  CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
532  $ rcond, r1, r2, w, rw, info )
533  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
534  infot = 15
535  CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
536  $ rcond, r1, r2, w, rw, info )
537  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
538 *
539  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
540 *
541 * ZPTSV
542 *
543  srnamt = 'ZPTSV '
544  infot = 1
545  CALL zptsv( -1, 0, r, a( 1, 1 ), b, 1, info )
546  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
547  infot = 2
548  CALL zptsv( 0, -1, r, a( 1, 1 ), b, 1, info )
549  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
550  infot = 6
551  CALL zptsv( 2, 0, r, a( 1, 1 ), b, 1, info )
552  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
553 *
554 * ZPTSVX
555 *
556  srnamt = 'ZPTSVX'
557  infot = 1
558  CALL zptsvx( '/', 0, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
559  $ 1, rcond, r1, r2, w, rw, info )
560  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
561  infot = 2
562  CALL zptsvx( 'N', -1, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
563  $ 1, rcond, r1, r2, w, rw, info )
564  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
565  infot = 3
566  CALL zptsvx( 'N', 0, -1, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
567  $ 1, rcond, r1, r2, w, rw, info )
568  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
569  infot = 9
570  CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
571  $ 2, rcond, r1, r2, w, rw, info )
572  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
573  infot = 11
574  CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 2, x,
575  $ 1, rcond, r1, r2, w, rw, info )
576  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
577 *
578  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
579 *
580 * ZHESV
581 *
582  srnamt = 'ZHESV '
583  infot = 1
584  CALL zhesv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
585  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
586  infot = 2
587  CALL zhesv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
588  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
589  infot = 3
590  CALL zhesv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
591  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
592  infot = 5
593  CALL zhesv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
594  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
595  infot = 8
596  CALL zhesv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
597  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
598  infot = 10
599  CALL zhesv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
600  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
601  infot = 10
602  CALL zhesv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
603  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
604 *
605 * ZHESVX
606 *
607  srnamt = 'ZHESVX'
608  infot = 1
609  CALL zhesvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
610  $ rcond, r1, r2, w, 1, rw, info )
611  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
612  infot = 2
613  CALL zhesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
614  $ rcond, r1, r2, w, 1, rw, info )
615  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
616  infot = 3
617  CALL zhesvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
618  $ rcond, r1, r2, w, 1, rw, info )
619  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
620  infot = 4
621  CALL zhesvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
622  $ rcond, r1, r2, w, 1, rw, info )
623  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
624  infot = 6
625  CALL zhesvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
626  $ rcond, r1, r2, w, 4, rw, info )
627  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
628  infot = 8
629  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
630  $ rcond, r1, r2, w, 4, rw, info )
631  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
632  infot = 11
633  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
634  $ rcond, r1, r2, w, 4, rw, info )
635  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
636  infot = 13
637  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
638  $ rcond, r1, r2, w, 4, rw, info )
639  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
640  infot = 18
641  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
642  $ rcond, r1, r2, w, 3, rw, info )
643  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
644 *
645  ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
646 *
647 * ZHESV_ROOK
648 *
649  srnamt = 'ZHESV_ROOK'
650  infot = 1
651  CALL zhesv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
652  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
653  infot = 2
654  CALL zhesv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
655  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
656  infot = 3
657  CALL zhesv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
658  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
659  infot = 8
660  CALL zhesv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
661  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
662  infot = 10
663  CALL zhesv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
664  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
665  infot = 10
666  CALL zhesv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
667  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
668 *
669  ELSE IF( lsamen( 2, c2, 'HK' ) ) THEN
670 *
671 * ZSYSV_RK
672 *
673 * Test error exits of the driver that uses factorization
674 * of a Hermitian indefinite matrix with rook
675 * (bounded Bunch-Kaufman) pivoting with the new storage
676 * format for factors L ( or U) and D.
677 *
678 * L (or U) is stored in A, diagonal of D is stored on the
679 * diagonal of A, subdiagonal of D is stored in a separate array E.
680 *
681  srnamt = 'ZHESV_RK'
682  infot = 1
683  CALL zhesv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
684  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
685  infot = 2
686  CALL zhesv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
687  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
688  infot = 3
689  CALL zhesv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
690  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
691  infot = 5
692  CALL zhesv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
693  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
694  infot = 9
695  CALL zhesv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
696  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
697  infot = 11
698  CALL zhesv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
699  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
700  infot = 11
701  CALL zhesv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
702  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
703 *
704  ELSE IF( lsamen( 2, c2, 'HA' ) ) THEN
705 *
706 * ZHESV_AA
707 *
708  srnamt = 'ZHESV_AA'
709  infot = 1
710  CALL zhesv_aa( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
711  CALL chkxer( 'ZHESV_AA', infot, nout, lerr, ok )
712  infot = 2
713  CALL zhesv_aa( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
714  CALL chkxer( 'ZHESV_AA', infot, nout, lerr, ok )
715  infot = 3
716  CALL zhesv_aa( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
717  CALL chkxer( 'ZHESV_AA', infot, nout, lerr, ok )
718  infot = 8
719  CALL zhesv_aa( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
720  CALL chkxer( 'ZHESV_AA', infot, nout, lerr, ok )
721 *
722  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
723 *
724 * ZHPSV
725 *
726  srnamt = 'ZHPSV '
727  infot = 1
728  CALL zhpsv( '/', 0, 0, a, ip, b, 1, info )
729  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
730  infot = 2
731  CALL zhpsv( 'U', -1, 0, a, ip, b, 1, info )
732  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
733  infot = 3
734  CALL zhpsv( 'U', 0, -1, a, ip, b, 1, info )
735  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
736  infot = 7
737  CALL zhpsv( 'U', 2, 0, a, ip, b, 1, info )
738  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
739 *
740 * ZHPSVX
741 *
742  srnamt = 'ZHPSVX'
743  infot = 1
744  CALL zhpsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
745  $ r2, w, rw, info )
746  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
747  infot = 2
748  CALL zhpsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
749  $ r2, w, rw, info )
750  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
751  infot = 3
752  CALL zhpsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
753  $ r2, w, rw, info )
754  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
755  infot = 4
756  CALL zhpsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
757  $ r2, w, rw, info )
758  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
759  infot = 9
760  CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
761  $ r2, w, rw, info )
762  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
763  infot = 11
764  CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
765  $ r2, w, rw, info )
766  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
767 *
768  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
769 *
770 * ZSYSV
771 *
772  srnamt = 'ZSYSV '
773  infot = 1
774  CALL zsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
775  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
776  infot = 2
777  CALL zsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
778  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
779  infot = 3
780  CALL zsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
781  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
782  infot = 8
783  CALL zsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
784  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
785  infot = 10
786  CALL zsysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
787  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
788  infot = 10
789  CALL zsysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
790  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
791 *
792 * ZSYSVX
793 *
794  srnamt = 'ZSYSVX'
795  infot = 1
796  CALL zsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
797  $ rcond, r1, r2, w, 1, rw, info )
798  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
799  infot = 2
800  CALL zsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
801  $ rcond, r1, r2, w, 1, rw, info )
802  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
803  infot = 3
804  CALL zsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
805  $ rcond, r1, r2, w, 1, rw, info )
806  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
807  infot = 4
808  CALL zsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
809  $ rcond, r1, r2, w, 1, rw, info )
810  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
811  infot = 6
812  CALL zsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
813  $ rcond, r1, r2, w, 4, rw, info )
814  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
815  infot = 8
816  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
817  $ rcond, r1, r2, w, 4, rw, info )
818  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
819  infot = 11
820  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
821  $ rcond, r1, r2, w, 4, rw, info )
822  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
823  infot = 13
824  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
825  $ rcond, r1, r2, w, 4, rw, info )
826  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
827  infot = 18
828  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
829  $ rcond, r1, r2, w, 3, rw, info )
830  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
831 *
832  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
833 *
834 * ZSYSV_ROOK
835 *
836  srnamt = 'ZSYSV_ROOK'
837  infot = 1
838  CALL zsysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
839  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
840  infot = 2
841  CALL zsysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
842  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
843  infot = 3
844  CALL zsysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
845  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
846  infot = 8
847  CALL zsysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
848  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
849  infot = 10
850  CALL zsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
851  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
852  infot = 10
853  CALL zsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
854 *
855  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
856 *
857 * ZSYSV_RK
858 *
859 * Test error exits of the driver that uses factorization
860 * of a symmetric indefinite matrix with rook
861 * (bounded Bunch-Kaufman) pivoting with the new storage
862 * format for factors L ( or U) and D.
863 *
864 * L (or U) is stored in A, diagonal of D is stored on the
865 * diagonal of A, subdiagonal of D is stored in a separate array E.
866 *
867  srnamt = 'ZSYSV_RK'
868  infot = 1
869  CALL zsysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
870  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
871  infot = 2
872  CALL zsysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
873  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
874  infot = 3
875  CALL zsysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
876  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
877  infot = 5
878  CALL zsysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
879  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
880  infot = 9
881  CALL zsysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
882  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
883  infot = 11
884  CALL zsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
885  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
886  infot = 11
887  CALL zsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
888  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
889 *
890  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
891 *
892 * ZSPSV
893 *
894  srnamt = 'ZSPSV '
895  infot = 1
896  CALL zspsv( '/', 0, 0, a, ip, b, 1, info )
897  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
898  infot = 2
899  CALL zspsv( 'U', -1, 0, a, ip, b, 1, info )
900  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
901  infot = 3
902  CALL zspsv( 'U', 0, -1, a, ip, b, 1, info )
903  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
904  infot = 7
905  CALL zspsv( 'U', 2, 0, a, ip, b, 1, info )
906  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
907 *
908 * ZSPSVX
909 *
910  srnamt = 'ZSPSVX'
911  infot = 1
912  CALL zspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
913  $ r2, w, rw, info )
914  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
915  infot = 2
916  CALL zspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
917  $ r2, w, rw, info )
918  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
919  infot = 3
920  CALL zspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
921  $ r2, w, rw, info )
922  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
923  infot = 4
924  CALL zspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
925  $ r2, w, rw, info )
926  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
927  infot = 9
928  CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
929  $ r2, w, rw, info )
930  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
931  infot = 11
932  CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
933  $ r2, w, rw, info )
934  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
935  END IF
936 *
937 * Print a summary line.
938 *
939  IF( ok ) THEN
940  WRITE( nout, fmt = 9999 )path
941  ELSE
942  WRITE( nout, fmt = 9998 )path
943  END IF
944 *
945  9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
946  9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
947  $ 'exits ***' )
948 *
949  RETURN
950 *
951 * End of ZERRVX
952 *
subroutine zsysv_rk(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysv_rk.f:230
subroutine zsysv_aa(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYSV_AA computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysv_aa.f:164
subroutine zhesv_rk(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV_RK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zhesv_rk.f:230
subroutine zgbsv(N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
ZGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver) ...
Definition: zgbsv.f:164
subroutine zgtsvx(FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZGTSVX computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: zgtsvx.f:296
subroutine zsysv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYSV computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysv.f:173
subroutine zsysvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO)
ZSYSVX computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysvx.f:287
subroutine zhpsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZHPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zhpsv.f:164
subroutine zposv(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
ZPOSV computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: zposv.f:132
subroutine zppsvx(FACT, UPLO, N, NRHS, AP, AFP, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zppsvx.f:313
subroutine zgesv(N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZGESV computes the solution to system of linear equations A * X = B for GE matrices (simple driver) ...
Definition: zgesv.f:124
subroutine zhesvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO)
ZHESVX computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesvx.f:287
subroutine zpbsv(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO)
ZPBSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zpbsv.f:166
subroutine zgbsvx(FACT, TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZGBSVX computes the solution to system of linear equations A * X = B for GB matrices ...
Definition: zgbsvx.f:372
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
subroutine zspsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZSPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zspsv.f:164
subroutine zptsvx(FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPTSVX computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: zptsvx.f:236
subroutine zgesvx(FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZGESVX computes the solution to system of linear equations A * X = B for GE matrices ...
Definition: zgesvx.f:352
subroutine zhpsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZHPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zhpsvx.f:279
subroutine zhesv_aa(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV_AA computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesv_aa.f:166
subroutine zppsv(UPLO, N, NRHS, AP, B, LDB, INFO)
ZPPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zppsv.f:146
subroutine zspsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zspsvx.f:279
subroutine zpbsvx(FACT, UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zpbsvx.f:344
subroutine zhesv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using the ...
Definition: zhesv_rook.f:207
subroutine zposvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPOSVX computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: zposvx.f:308
subroutine zhesv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesv.f:173
subroutine zptsv(N, NRHS, D, E, B, LDB, INFO)
ZPTSV computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: zptsv.f:117
subroutine zsysv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysv_rook.f:206
subroutine zgtsv(N, NRHS, DL, D, DU, B, LDB, INFO)
ZGTSV computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: zgtsv.f:126

Here is the call graph for this function:

Here is the caller graph for this function: