LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zerrvx.f
Go to the documentation of this file.
1*> \brief \b ZERRVX
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 ZERRVX( 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*> ZERRVX tests the error exits for the COMPLEX*16 driver routines
25*> for solving linear systems of equations.
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*> \ingroup complex16_lin
52*
53* =====================================================================
54 SUBROUTINE zerrvx( PATH, NUNIT )
55*
56* -- LAPACK test routine --
57* -- LAPACK is a software package provided by Univ. of Tennessee, --
58* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
59*
60* .. Scalar Arguments ..
61 CHARACTER*3 PATH
62 INTEGER NUNIT
63* ..
64*
65* =====================================================================
66*
67* .. Parameters ..
68 INTEGER NMAX
69 parameter( nmax = 4 )
70* ..
71* .. Local Scalars ..
72 CHARACTER EQ
73 CHARACTER*2 C2
74 INTEGER I, INFO, J
75 DOUBLE PRECISION RCOND
76* ..
77* .. Local Arrays ..
78 INTEGER IP( NMAX )
79 DOUBLE PRECISION C( NMAX ), R( NMAX ), R1( NMAX ), R2( NMAX ),
80 $ RF( NMAX ), RW( NMAX )
81 COMPLEX*16 A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
82 $ E( NMAX ), W( 2*NMAX ), X( NMAX )
83* ..
84* .. External Functions ..
85 LOGICAL LSAMEN
86 EXTERNAL lsamen
87* ..
88* .. External Subroutines ..
89 EXTERNAL chkxer, zgbsv, zgbsvx, zgesv, zgesvx, zgtsv,
95* ..
96* .. Scalars in Common ..
97 LOGICAL LERR, OK
98 CHARACTER*32 SRNAMT
99 INTEGER INFOT, NOUT
100* ..
101* .. Common blocks ..
102 COMMON / infoc / infot, nout, ok, lerr
103 COMMON / srnamc / srnamt
104* ..
105* .. Intrinsic Functions ..
106 INTRINSIC dble, dcmplx
107* ..
108* .. Executable Statements ..
109*
110 nout = nunit
111 WRITE( nout, fmt = * )
112 c2 = path( 2: 3 )
113*
114* Set the variables to innocuous values.
115*
116 DO 20 j = 1, nmax
117 DO 10 i = 1, nmax
118 a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
119 $ -1.d0 / dble( i+j ) )
120 af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
121 $ -1.d0 / dble( i+j ) )
122 10 CONTINUE
123 b( j ) = 0.d0
124 e( j ) = 0.d0
125 r1( j ) = 0.d0
126 r2( j ) = 0.d0
127 w( j ) = 0.d0
128 x( j ) = 0.d0
129 c( j ) = 0.d0
130 r( j ) = 0.d0
131 ip( j ) = j
132 20 CONTINUE
133 eq = ' '
134 ok = .true.
135*
136 IF( lsamen( 2, c2, 'GE' ) ) THEN
137*
138* ZGESV
139*
140 srnamt = 'ZGESV '
141 infot = 1
142 CALL zgesv( -1, 0, a, 1, ip, b, 1, info )
143 CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
144 infot = 2
145 CALL zgesv( 0, -1, a, 1, ip, b, 1, info )
146 CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
147 infot = 4
148 CALL zgesv( 2, 1, a, 1, ip, b, 2, info )
149 CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
150 infot = 7
151 CALL zgesv( 2, 1, a, 2, ip, b, 1, info )
152 CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
153*
154* ZGESVX
155*
156 srnamt = 'ZGESVX'
157 infot = 1
158 CALL zgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
159 $ x, 1, rcond, r1, r2, w, rw, info )
160 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
161 infot = 2
162 CALL zgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
163 $ x, 1, rcond, r1, r2, w, rw, info )
164 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
165 infot = 3
166 CALL zgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
167 $ x, 1, rcond, r1, r2, w, rw, info )
168 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
169 infot = 4
170 CALL zgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
171 $ x, 1, rcond, r1, r2, w, rw, info )
172 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
173 infot = 6
174 CALL zgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
175 $ x, 2, rcond, r1, r2, w, rw, info )
176 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
177 infot = 8
178 CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
179 $ x, 2, rcond, r1, r2, w, rw, info )
180 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
181 infot = 10
182 eq = '/'
183 CALL zgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
184 $ x, 1, rcond, r1, r2, w, rw, info )
185 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
186 infot = 11
187 eq = 'R'
188 CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
189 $ x, 1, rcond, r1, r2, w, rw, info )
190 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
191 infot = 12
192 eq = 'C'
193 CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
194 $ x, 1, rcond, r1, r2, w, rw, info )
195 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
196 infot = 14
197 CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
198 $ x, 2, rcond, r1, r2, w, rw, info )
199 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
200 infot = 16
201 CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
202 $ x, 1, rcond, r1, r2, w, rw, info )
203 CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
204*
205 ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
206*
207* ZGBSV
208*
209 srnamt = 'ZGBSV '
210 infot = 1
211 CALL zgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
212 CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
213 infot = 2
214 CALL zgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
215 CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
216 infot = 3
217 CALL zgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
218 CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
219 infot = 4
220 CALL zgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
221 CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
222 infot = 6
223 CALL zgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
224 CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
225 infot = 9
226 CALL zgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
227 CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
228*
229* ZGBSVX
230*
231 srnamt = 'ZGBSVX'
232 infot = 1
233 CALL zgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
234 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
235 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
236 infot = 2
237 CALL zgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
238 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
239 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
240 infot = 3
241 CALL zgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
242 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
243 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
244 infot = 4
245 CALL zgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
246 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
247 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
248 infot = 5
249 CALL zgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
250 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
251 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
252 infot = 6
253 CALL zgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
254 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
255 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
256 infot = 8
257 CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
258 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
259 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
260 infot = 10
261 CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
262 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
263 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
264 infot = 12
265 eq = '/'
266 CALL zgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
267 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
268 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
269 infot = 13
270 eq = 'R'
271 CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
272 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
273 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
274 infot = 14
275 eq = 'C'
276 CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
277 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
278 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
279 infot = 16
280 CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
281 $ b, 1, x, 2, rcond, r1, r2, w, rw, info )
282 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
283 infot = 18
284 CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
285 $ b, 2, x, 1, rcond, r1, r2, w, rw, info )
286 CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
287*
288 ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
289*
290* ZGTSV
291*
292 srnamt = 'ZGTSV '
293 infot = 1
294 CALL zgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
295 $ info )
296 CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
297 infot = 2
298 CALL zgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
299 $ info )
300 CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
301 infot = 7
302 CALL zgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
303 CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
304*
305* ZGTSVX
306*
307 srnamt = 'ZGTSVX'
308 infot = 1
309 CALL zgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
310 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
311 $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
312 CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
313 infot = 2
314 CALL zgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
315 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
316 $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
317 CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
318 infot = 3
319 CALL zgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
320 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
321 $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
322 CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
323 infot = 4
324 CALL zgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
325 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
326 $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
327 CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
328 infot = 14
329 CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
330 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
331 $ ip, b, 1, x, 2, rcond, r1, r2, w, rw, info )
332 CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
333 infot = 16
334 CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
335 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
336 $ ip, b, 2, x, 1, rcond, r1, r2, w, rw, info )
337 CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
338*
339 ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
340*
341* ZPOSV
342*
343 srnamt = 'ZPOSV '
344 infot = 1
345 CALL zposv( '/', 0, 0, a, 1, b, 1, info )
346 CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
347 infot = 2
348 CALL zposv( 'U', -1, 0, a, 1, b, 1, info )
349 CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
350 infot = 3
351 CALL zposv( 'U', 0, -1, a, 1, b, 1, info )
352 CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
353 infot = 5
354 CALL zposv( 'U', 2, 0, a, 1, b, 2, info )
355 CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
356 infot = 7
357 CALL zposv( 'U', 2, 0, a, 2, b, 1, info )
358 CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
359*
360* ZPOSVX
361*
362 srnamt = 'ZPOSVX'
363 infot = 1
364 CALL zposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
365 $ rcond, r1, r2, w, rw, info )
366 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
367 infot = 2
368 CALL zposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
369 $ rcond, r1, r2, w, rw, info )
370 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
371 infot = 3
372 CALL zposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
373 $ rcond, r1, r2, w, rw, info )
374 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
375 infot = 4
376 CALL zposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
377 $ rcond, r1, r2, w, rw, info )
378 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
379 infot = 6
380 CALL zposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
381 $ rcond, r1, r2, w, rw, info )
382 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
383 infot = 8
384 CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
385 $ rcond, r1, r2, w, rw, info )
386 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
387 infot = 9
388 eq = '/'
389 CALL zposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
390 $ rcond, r1, r2, w, rw, info )
391 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
392 infot = 10
393 eq = 'Y'
394 CALL zposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
395 $ rcond, r1, r2, w, rw, info )
396 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
397 infot = 12
398 CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
399 $ rcond, r1, r2, w, rw, info )
400 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
401 infot = 14
402 CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
403 $ rcond, r1, r2, w, rw, info )
404 CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
405*
406 ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
407*
408* ZPPSV
409*
410 srnamt = 'ZPPSV '
411 infot = 1
412 CALL zppsv( '/', 0, 0, a, b, 1, info )
413 CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
414 infot = 2
415 CALL zppsv( 'U', -1, 0, a, b, 1, info )
416 CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
417 infot = 3
418 CALL zppsv( 'U', 0, -1, a, b, 1, info )
419 CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
420 infot = 6
421 CALL zppsv( 'U', 2, 0, a, b, 1, info )
422 CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
423*
424* ZPPSVX
425*
426 srnamt = 'ZPPSVX'
427 infot = 1
428 CALL zppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
429 $ r1, r2, w, rw, info )
430 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
431 infot = 2
432 CALL zppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
433 $ r1, r2, w, rw, info )
434 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
435 infot = 3
436 CALL zppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
437 $ r1, r2, w, rw, info )
438 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
439 infot = 4
440 CALL zppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
441 $ r1, r2, w, rw, info )
442 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
443 infot = 7
444 eq = '/'
445 CALL zppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
446 $ r1, r2, w, rw, info )
447 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
448 infot = 8
449 eq = 'Y'
450 CALL zppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
451 $ r1, r2, w, rw, info )
452 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
453 infot = 10
454 CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
455 $ r1, r2, w, rw, info )
456 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
457 infot = 12
458 CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
459 $ r1, r2, w, rw, info )
460 CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
461*
462 ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
463*
464* ZPBSV
465*
466 srnamt = 'ZPBSV '
467 infot = 1
468 CALL zpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
469 CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
470 infot = 2
471 CALL zpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
472 CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
473 infot = 3
474 CALL zpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
475 CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
476 infot = 4
477 CALL zpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
478 CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
479 infot = 6
480 CALL zpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
481 CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
482 infot = 8
483 CALL zpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
484 CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
485*
486* ZPBSVX
487*
488 srnamt = 'ZPBSVX'
489 infot = 1
490 CALL zpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
491 $ rcond, r1, r2, w, rw, info )
492 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
493 infot = 2
494 CALL zpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
495 $ rcond, r1, r2, w, rw, info )
496 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
497 infot = 3
498 CALL zpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
499 $ 1, rcond, r1, r2, w, rw, info )
500 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
501 infot = 4
502 CALL zpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
503 $ 1, rcond, r1, r2, w, rw, info )
504 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
505 infot = 5
506 CALL zpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
507 $ 1, rcond, r1, r2, w, rw, info )
508 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
509 infot = 7
510 CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
511 $ rcond, r1, r2, w, rw, info )
512 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
513 infot = 9
514 CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
515 $ rcond, r1, r2, w, rw, info )
516 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
517 infot = 10
518 eq = '/'
519 CALL zpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
520 $ rcond, r1, r2, w, rw, info )
521 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
522 infot = 11
523 eq = 'Y'
524 CALL zpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
525 $ rcond, r1, r2, w, rw, info )
526 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
527 infot = 13
528 CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
529 $ rcond, r1, r2, w, rw, info )
530 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
531 infot = 15
532 CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
533 $ rcond, r1, r2, w, rw, info )
534 CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
535*
536 ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
537*
538* ZPTSV
539*
540 srnamt = 'ZPTSV '
541 infot = 1
542 CALL zptsv( -1, 0, r, a( 1, 1 ), b, 1, info )
543 CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
544 infot = 2
545 CALL zptsv( 0, -1, r, a( 1, 1 ), b, 1, info )
546 CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
547 infot = 6
548 CALL zptsv( 2, 0, r, a( 1, 1 ), b, 1, info )
549 CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
550*
551* ZPTSVX
552*
553 srnamt = 'ZPTSVX'
554 infot = 1
555 CALL zptsvx( '/', 0, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
556 $ 1, rcond, r1, r2, w, rw, info )
557 CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
558 infot = 2
559 CALL zptsvx( 'N', -1, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
560 $ 1, rcond, r1, r2, w, rw, info )
561 CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
562 infot = 3
563 CALL zptsvx( 'N', 0, -1, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
564 $ 1, rcond, r1, r2, w, rw, info )
565 CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
566 infot = 9
567 CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
568 $ 2, rcond, r1, r2, w, rw, info )
569 CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
570 infot = 11
571 CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 2, x,
572 $ 1, rcond, r1, r2, w, rw, info )
573 CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
574*
575 ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
576*
577* ZHESV
578*
579 srnamt = 'ZHESV '
580 infot = 1
581 CALL zhesv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
582 CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
583 infot = 2
584 CALL zhesv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
585 CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
586 infot = 3
587 CALL zhesv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
588 CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
589 infot = 5
590 CALL zhesv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
591 CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
592 infot = 8
593 CALL zhesv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
594 CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
595 infot = 10
596 CALL zhesv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
597 CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
598 infot = 10
599 CALL zhesv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
600 CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
601*
602* ZHESVX
603*
604 srnamt = 'ZHESVX'
605 infot = 1
606 CALL zhesvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
607 $ rcond, r1, r2, w, 1, rw, info )
608 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
609 infot = 2
610 CALL zhesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
611 $ rcond, r1, r2, w, 1, rw, info )
612 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
613 infot = 3
614 CALL zhesvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
615 $ rcond, r1, r2, w, 1, rw, info )
616 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
617 infot = 4
618 CALL zhesvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
619 $ rcond, r1, r2, w, 1, rw, info )
620 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
621 infot = 6
622 CALL zhesvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
623 $ rcond, r1, r2, w, 4, rw, info )
624 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
625 infot = 8
626 CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
627 $ rcond, r1, r2, w, 4, rw, info )
628 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
629 infot = 11
630 CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
631 $ rcond, r1, r2, w, 4, rw, info )
632 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
633 infot = 13
634 CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
635 $ rcond, r1, r2, w, 4, rw, info )
636 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
637 infot = 18
638 CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
639 $ rcond, r1, r2, w, 3, rw, info )
640 CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
641*
642 ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
643*
644* ZHESV_ROOK
645*
646 srnamt = 'ZHESV_ROOK'
647 infot = 1
648 CALL zhesv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
649 CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
650 infot = 2
651 CALL zhesv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
652 CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
653 infot = 3
654 CALL zhesv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
655 CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
656 infot = 5
657 CALL zhesv_rook( 'U', 2, 0, a, 1, ip, b, 2, 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_AASEN
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 = 5
719 CALL zhesv_aa( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
720 CALL chkxer( 'ZHESV_AA', infot, nout, lerr, ok )
721 infot = 8
722 CALL zhesv_aa( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
723 CALL chkxer( 'ZHESV_AA', infot, nout, lerr, ok )
724 infot = 10
725 CALL zhesv_aa( 'U', 3, 1, a, 3, ip, b, 3, w, 6, info )
726 CALL chkxer( 'ZHESV_AA', infot, nout, lerr, ok )
727*
728 ELSE IF( lsamen( 2, c2, 'H2' ) ) THEN
729*
730* ZHESV_AASEN_2STAGE
731*
732 srnamt = 'ZHESV_AA_2STAGE'
733 infot = 1
734 CALL zhesv_aa_2stage( '/', 0, 0, a, 1, a, 1, ip, ip, b, 1,
735 $ w, 1, info )
736 CALL chkxer( 'ZHESV_AA_2STAGE', infot, nout, lerr, ok )
737 infot = 2
738 CALL zhesv_aa_2stage( 'U', -1, 0, a, 1, a, 1, ip, ip, b, 1,
739 $ w, 1, info )
740 CALL chkxer( 'ZHESV_AA_2STAGE', infot, nout, lerr, ok )
741 infot = 3
742 CALL zhesv_aa_2stage( 'U', 0, -1, a, 1, a, 1, ip, ip, b, 1,
743 $ w, 1, info )
744 CALL chkxer( 'ZHESV_AA_2STAGE', infot, nout, lerr, ok )
745 infot = 5
746 CALL zhesv_aa_2stage( 'U', 2, 1, a, 1, a, 1, ip, ip, b, 1,
747 $ w, 1, info )
748 CALL chkxer( 'ZHESV_AA_2STAGE', infot, nout, lerr, ok )
749 infot = 7
750 CALL zhesv_aa_2stage( 'U', 2, 1, a, 2, a, 1, ip, ip, b, 2,
751 $ w, 1, info )
752 CALL chkxer( 'ZHESV_AA_2STAGE', infot, nout, lerr, ok )
753 infot = 11
754 CALL zhesv_aa_2stage( 'U', 2, 1, a, 2, a, 8, ip, ip, b, 1,
755 $ w, 1, info )
756 CALL chkxer( 'ZHESV_AA_2STAGE', infot, nout, lerr, ok )
757 infot = 13
758 CALL zhesv_aa_2stage( 'U', 2, 1, a, 2, a, 8, ip, ip, b, 2,
759 $ w, 1, info )
760 CALL chkxer( 'ZHESV_AA_2STAGE', infot, nout, lerr, ok )
761*
762 ELSE IF( lsamen( 2, c2, 'SA' ) ) THEN
763*
764* ZSYSV_AASEN
765*
766 srnamt = 'ZSYSV_AA'
767 infot = 1
768 CALL zsysv_aa( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
769 CALL chkxer( 'ZSYSV_AA', infot, nout, lerr, ok )
770 infot = 2
771 CALL zsysv_aa( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
772 CALL chkxer( 'ZSYSV_AA', infot, nout, lerr, ok )
773 infot = 3
774 CALL zsysv_aa( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
775 CALL chkxer( 'ZSYSV_AA', infot, nout, lerr, ok )
776 infot = 5
777 CALL zsysv_aa( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
778 CALL chkxer( 'ZSYSV_AA', infot, nout, lerr, ok )
779 infot = 8
780 CALL zsysv_aa( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
781 CALL chkxer( 'ZSYSV_AA', infot, nout, lerr, ok )
782 infot = 10
783 CALL zsysv_aa( 'U', 3, 1, a, 3, ip, b, 3, w, 6, info )
784 CALL chkxer( 'ZSYSV_AA', infot, nout, lerr, ok )
785*
786 ELSE IF( lsamen( 2, c2, 'S2' ) ) THEN
787*
788* ZSYSV_AASEN_2STAGE
789*
790 srnamt = 'ZSYSV_AA_2STAGE'
791 infot = 1
792 CALL zsysv_aa_2stage( '/', 0, 0, a, 1, a, 1, ip, ip, b, 1,
793 $ w, 1, info )
794 CALL chkxer( 'ZSYSV_AA_2STAGE', infot, nout, lerr, ok )
795 infot = 2
796 CALL zsysv_aa_2stage( 'U', -1, 0, a, 1, a, 1, ip, ip, b, 1,
797 $ w, 1, info )
798 CALL chkxer( 'ZSYSV_AA_2STAGE', infot, nout, lerr, ok )
799 infot = 3
800 CALL zsysv_aa_2stage( 'U', 0, -1, a, 1, a, 1, ip, ip, b, 1,
801 $ w, 1, info )
802 CALL chkxer( 'ZSYSV_AA_2STAGE', infot, nout, lerr, ok )
803 infot = 5
804 CALL zsysv_aa_2stage( 'U', 2, 1, a, 1, a, 1, ip, ip, b, 1,
805 $ w, 1, info )
806 CALL chkxer( 'ZSYSV_AA_2STAGE', infot, nout, lerr, ok )
807 infot = 7
808 CALL zsysv_aa_2stage( 'U', 2, 1, a, 2, a, 1, ip, ip, b, 2,
809 $ w, 1, info )
810 CALL chkxer( 'ZSYSV_AA_2STAGE', infot, nout, lerr, ok )
811 infot = 11
812 CALL zsysv_aa_2stage( 'U', 2, 1, a, 2, a, 8, ip, ip, b, 1,
813 $ w, 1, info )
814 CALL chkxer( 'ZSYSV_AA_2STAGE', infot, nout, lerr, ok )
815 infot = 13
816 CALL zsysv_aa_2stage( 'U', 2, 1, a, 2, a, 8, ip, ip, b, 2,
817 $ w, 1, info )
818 CALL chkxer( 'ZSYSV_AA_2STAGE', infot, nout, lerr, ok )
819*
820 ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
821*
822* ZHPSV
823*
824 srnamt = 'ZHPSV '
825 infot = 1
826 CALL zhpsv( '/', 0, 0, a, ip, b, 1, info )
827 CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
828 infot = 2
829 CALL zhpsv( 'U', -1, 0, a, ip, b, 1, info )
830 CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
831 infot = 3
832 CALL zhpsv( 'U', 0, -1, a, ip, b, 1, info )
833 CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
834 infot = 7
835 CALL zhpsv( 'U', 2, 0, a, ip, b, 1, info )
836 CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
837*
838* ZHPSVX
839*
840 srnamt = 'ZHPSVX'
841 infot = 1
842 CALL zhpsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
843 $ r2, w, rw, info )
844 CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
845 infot = 2
846 CALL zhpsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
847 $ r2, w, rw, info )
848 CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
849 infot = 3
850 CALL zhpsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
851 $ r2, w, rw, info )
852 CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
853 infot = 4
854 CALL zhpsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
855 $ r2, w, rw, info )
856 CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
857 infot = 9
858 CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
859 $ r2, w, rw, info )
860 CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
861 infot = 11
862 CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
863 $ r2, w, rw, info )
864 CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
865*
866 ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
867*
868* ZSYSV
869*
870 srnamt = 'ZSYSV '
871 infot = 1
872 CALL zsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
873 CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
874 infot = 2
875 CALL zsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
876 CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
877 infot = 3
878 CALL zsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
879 CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
880 infot = 5
881 CALL zsysv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
882 CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
883 infot = 8
884 CALL zsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
885 CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
886 infot = 10
887 CALL zsysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
888 CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
889 infot = 10
890 CALL zsysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
891 CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
892*
893* ZSYSVX
894*
895 srnamt = 'ZSYSVX'
896 infot = 1
897 CALL zsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
898 $ rcond, r1, r2, w, 1, rw, info )
899 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
900 infot = 2
901 CALL zsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
902 $ rcond, r1, r2, w, 1, rw, info )
903 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
904 infot = 3
905 CALL zsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
906 $ rcond, r1, r2, w, 1, rw, info )
907 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
908 infot = 4
909 CALL zsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
910 $ rcond, r1, r2, w, 1, rw, info )
911 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
912 infot = 6
913 CALL zsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
914 $ rcond, r1, r2, w, 4, rw, info )
915 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
916 infot = 8
917 CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
918 $ rcond, r1, r2, w, 4, rw, info )
919 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
920 infot = 11
921 CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
922 $ rcond, r1, r2, w, 4, rw, info )
923 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
924 infot = 13
925 CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
926 $ rcond, r1, r2, w, 4, rw, info )
927 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
928 infot = 18
929 CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
930 $ rcond, r1, r2, w, 3, rw, info )
931 CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
932*
933 ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
934*
935* ZSYSV_ROOK
936*
937 srnamt = 'ZSYSV_ROOK'
938 infot = 1
939 CALL zsysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
940 CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
941 infot = 2
942 CALL zsysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
943 CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
944 infot = 3
945 CALL zsysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
946 CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
947 infot = 5
948 CALL zsysv_rook( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
949 CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
950 infot = 8
951 CALL zsysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
952 CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
953 infot = 10
954 CALL zsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
955 CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
956 infot = 10
957 CALL zsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
958*
959 ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
960*
961* ZSYSV_RK
962*
963* Test error exits of the driver that uses factorization
964* of a symmetric indefinite matrix with rook
965* (bounded Bunch-Kaufman) pivoting with the new storage
966* format for factors L ( or U) and D.
967*
968* L (or U) is stored in A, diagonal of D is stored on the
969* diagonal of A, subdiagonal of D is stored in a separate array E.
970*
971 srnamt = 'ZSYSV_RK'
972 infot = 1
973 CALL zsysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
974 CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
975 infot = 2
976 CALL zsysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
977 CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
978 infot = 3
979 CALL zsysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
980 CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
981 infot = 5
982 CALL zsysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
983 CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
984 infot = 9
985 CALL zsysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
986 CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
987 infot = 11
988 CALL zsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
989 CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
990 infot = 11
991 CALL zsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
992 CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
993*
994 ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
995*
996* ZSPSV
997*
998 srnamt = 'ZSPSV '
999 infot = 1
1000 CALL zspsv( '/', 0, 0, a, ip, b, 1, info )
1001 CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1002 infot = 2
1003 CALL zspsv( 'U', -1, 0, a, ip, b, 1, info )
1004 CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1005 infot = 3
1006 CALL zspsv( 'U', 0, -1, a, ip, b, 1, info )
1007 CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1008 infot = 7
1009 CALL zspsv( 'U', 2, 0, a, ip, b, 1, info )
1010 CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1011*
1012* ZSPSVX
1013*
1014 srnamt = 'ZSPSVX'
1015 infot = 1
1016 CALL zspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1017 $ r2, w, rw, info )
1018 CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1019 infot = 2
1020 CALL zspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1021 $ r2, w, rw, info )
1022 CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1023 infot = 3
1024 CALL zspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1025 $ r2, w, rw, info )
1026 CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1027 infot = 4
1028 CALL zspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1029 $ r2, w, rw, info )
1030 CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1031 infot = 9
1032 CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1033 $ r2, w, rw, info )
1034 CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1035 infot = 11
1036 CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1037 $ r2, w, rw, info )
1038 CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1039 END IF
1040*
1041* Print a summary line.
1042*
1043 IF( ok ) THEN
1044 WRITE( nout, fmt = 9999 )path
1045 ELSE
1046 WRITE( nout, fmt = 9998 )path
1047 END IF
1048*
1049 9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
1050 9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
1051 $ 'exits ***' )
1052*
1053 RETURN
1054*
1055* End of ZERRVX
1056*
1057 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
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:162
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:370
subroutine zgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
Download ZGESV + dependencies <a href="http://www.netlib.org/cgi-bin/netlibfiles....
Definition zgesv.f:124
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:350
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:124
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:294
subroutine zhesv_aa_2stage(uplo, n, nrhs, a, lda, tb, ltb, ipiv, ipiv2, b, ldb, work, lwork, info)
ZHESV_AA_2STAGE computes the solution to system of linear equations A * X = B for HE matrices
subroutine zsysv_aa_2stage(uplo, n, nrhs, a, lda, tb, ltb, ipiv, ipiv2, b, ldb, work, lwork, info)
ZSYSV_AA_2STAGE computes the solution to system of linear equations A * X = B for SY matrices
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:162
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:162
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:228
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:228
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:205
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:204
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:171
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:171
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:285
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:285
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:162
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:162
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:277
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:277
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:164
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:342
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:130
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:306
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:144
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:311
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:115
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:234
subroutine zerrvx(path, nunit)
ZERRVX
Definition zerrvx.f:55