LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zerrgex.f
Go to the documentation of this file.
1 *> \brief \b ZERRGEX
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 ZERRGE( 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 *> ZERRGE tests the error exits for the COMPLEX*16 routines
25 *> for general matrices.
26 *>
27 *> Note that this file is used only when the XBLAS are available,
28 *> otherwise zerrge.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 2011
55 *
56 *> \ingroup complex16_lin
57 *
58 * =====================================================================
59  SUBROUTINE zerrge( PATH, NUNIT )
60 *
61 * -- LAPACK test routine (version 3.4.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 2011
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, ccond, rcond, berr
82 * ..
83 * .. Local Arrays ..
84  INTEGER ip( nmax )
85  DOUBLE PRECISION r( nmax ), r1( nmax ), r2( nmax ), cs( nmax ),
86  $ rs( nmax )
87  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
88  $ w( 2*nmax ), x( nmax ), err_bnds_n( nmax, 3 ),
89  $ err_bnds_c( nmax, 3 ), params
90 * ..
91 * .. External Functions ..
92  LOGICAL lsamen
93  EXTERNAL lsamen
94 * ..
95 * .. External Subroutines ..
96  EXTERNAL alaesm, chkxer, zgbcon, zgbequ, zgbrfs, zgbtf2,
99  $ zgbequb, zgbrfsx
100 * ..
101 * .. Scalars in Common ..
102  LOGICAL lerr, ok
103  CHARACTER*32 srnamt
104  INTEGER infot, nout
105 * ..
106 * .. Common blocks ..
107  common / infoc / infot, nout, ok, lerr
108  common / srnamc / srnamt
109 * ..
110 * .. Intrinsic Functions ..
111  INTRINSIC dble, dcmplx
112 * ..
113 * .. Executable Statements ..
114 *
115  nout = nunit
116  WRITE( nout, fmt = * )
117  c2 = path( 2: 3 )
118 *
119 * Set the variables to innocuous values.
120 *
121  DO 20 j = 1, nmax
122  DO 10 i = 1, nmax
123  a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
124  $ -1.d0 / dble( i+j ) )
125  af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
126  $ -1.d0 / dble( i+j ) )
127  10 continue
128  b( j ) = 0.d0
129  r1( j ) = 0.d0
130  r2( j ) = 0.d0
131  w( j ) = 0.d0
132  x( j ) = 0.d0
133  cs( j ) = 0.d0
134  rs( j ) = 0.d0
135  ip( j ) = j
136  20 continue
137  ok = .true.
138 *
139 * Test error exits of the routines that use the LU decomposition
140 * of a general matrix.
141 *
142  IF( lsamen( 2, c2, 'GE' ) ) THEN
143 *
144 * ZGETRF
145 *
146  srnamt = 'ZGETRF'
147  infot = 1
148  CALL zgetrf( -1, 0, a, 1, ip, info )
149  CALL chkxer( 'ZGETRF', infot, nout, lerr, ok )
150  infot = 2
151  CALL zgetrf( 0, -1, a, 1, ip, info )
152  CALL chkxer( 'ZGETRF', infot, nout, lerr, ok )
153  infot = 4
154  CALL zgetrf( 2, 1, a, 1, ip, info )
155  CALL chkxer( 'ZGETRF', infot, nout, lerr, ok )
156 *
157 * ZGETF2
158 *
159  srnamt = 'ZGETF2'
160  infot = 1
161  CALL zgetf2( -1, 0, a, 1, ip, info )
162  CALL chkxer( 'ZGETF2', infot, nout, lerr, ok )
163  infot = 2
164  CALL zgetf2( 0, -1, a, 1, ip, info )
165  CALL chkxer( 'ZGETF2', infot, nout, lerr, ok )
166  infot = 4
167  CALL zgetf2( 2, 1, a, 1, ip, info )
168  CALL chkxer( 'ZGETF2', infot, nout, lerr, ok )
169 *
170 * ZGETRI
171 *
172  srnamt = 'ZGETRI'
173  infot = 1
174  CALL zgetri( -1, a, 1, ip, w, 1, info )
175  CALL chkxer( 'ZGETRI', infot, nout, lerr, ok )
176  infot = 3
177  CALL zgetri( 2, a, 1, ip, w, 2, info )
178  CALL chkxer( 'ZGETRI', infot, nout, lerr, ok )
179  infot = 6
180  CALL zgetri( 2, a, 2, ip, w, 1, info )
181  CALL chkxer( 'ZGETRI', infot, nout, lerr, ok )
182 *
183 * ZGETRS
184 *
185  srnamt = 'ZGETRS'
186  infot = 1
187  CALL zgetrs( '/', 0, 0, a, 1, ip, b, 1, info )
188  CALL chkxer( 'ZGETRS', infot, nout, lerr, ok )
189  infot = 2
190  CALL zgetrs( 'N', -1, 0, a, 1, ip, b, 1, info )
191  CALL chkxer( 'ZGETRS', infot, nout, lerr, ok )
192  infot = 3
193  CALL zgetrs( 'N', 0, -1, a, 1, ip, b, 1, info )
194  CALL chkxer( 'ZGETRS', infot, nout, lerr, ok )
195  infot = 5
196  CALL zgetrs( 'N', 2, 1, a, 1, ip, b, 2, info )
197  CALL chkxer( 'ZGETRS', infot, nout, lerr, ok )
198  infot = 8
199  CALL zgetrs( 'N', 2, 1, a, 2, ip, b, 1, info )
200  CALL chkxer( 'ZGETRS', infot, nout, lerr, ok )
201 *
202 * ZGERFS
203 *
204  srnamt = 'ZGERFS'
205  infot = 1
206  CALL zgerfs( '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
207  $ r, info )
208  CALL chkxer( 'ZGERFS', infot, nout, lerr, ok )
209  infot = 2
210  CALL zgerfs( 'N', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
211  $ w, r, info )
212  CALL chkxer( 'ZGERFS', infot, nout, lerr, ok )
213  infot = 3
214  CALL zgerfs( 'N', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
215  $ w, r, info )
216  CALL chkxer( 'ZGERFS', infot, nout, lerr, ok )
217  infot = 5
218  CALL zgerfs( 'N', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
219  $ r, info )
220  CALL chkxer( 'ZGERFS', infot, nout, lerr, ok )
221  infot = 7
222  CALL zgerfs( 'N', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
223  $ r, info )
224  CALL chkxer( 'ZGERFS', infot, nout, lerr, ok )
225  infot = 10
226  CALL zgerfs( 'N', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
227  $ r, info )
228  CALL chkxer( 'ZGERFS', infot, nout, lerr, ok )
229  infot = 12
230  CALL zgerfs( 'N', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
231  $ r, info )
232  CALL chkxer( 'ZGERFS', infot, nout, lerr, ok )
233 *
234 * ZGERFSX
235 *
236  n_err_bnds = 3
237  nparams = 0
238  srnamt = 'ZGERFSX'
239  infot = 1
240  CALL zgerfsx( '/', eq, 0, 0, a, 1, af, 1, ip, rs, cs, b, 1, x,
241  $ 1, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
242  $ nparams, params, w, r, info )
243  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
244  infot = 2
245  eq = '/'
246  CALL zgerfsx( 'N', eq, 2, 1, a, 1, af, 2, ip, rs, cs, b, 2, x,
247  $ 2, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
248  $ nparams, params, w, r, info )
249  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
250  infot = 3
251  eq = 'R'
252  CALL zgerfsx( 'N', eq, -1, 0, a, 1, af, 1, ip, rs, cs, b, 1, x,
253  $ 1, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
254  $ nparams, params, w, r, info )
255  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
256  infot = 4
257  CALL zgerfsx( 'N', eq, 0, -1, a, 1, af, 1, ip, rs, cs, b, 1, x,
258  $ 1, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
259  $ nparams, params, w, r, info )
260  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
261  infot = 6
262  CALL zgerfsx( 'N', eq, 2, 1, a, 1, af, 2, ip, rs, cs, b, 2, x,
263  $ 2, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
264  $ nparams, params, w, r, info )
265  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
266  infot = 8
267  CALL zgerfsx( 'N', eq, 2, 1, a, 2, af, 1, ip, rs, cs, b, 2, x,
268  $ 2, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
269  $ nparams, params, w, r, info )
270  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
271  infot = 13
272  eq = 'C'
273  CALL zgerfsx( 'N', eq, 2, 1, a, 2, af, 2, ip, rs, cs, b, 1, x,
274  $ 2, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
275  $ nparams, params, w, r, info )
276  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
277  infot = 15
278  CALL zgerfsx( 'N', eq, 2, 1, a, 2, af, 2, ip, rs, cs, b, 2, x,
279  $ 1, rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c,
280  $ nparams, params, w, r, info )
281  CALL chkxer( 'ZGERFSX', infot, nout, lerr, ok )
282 *
283 * ZGECON
284 *
285  srnamt = 'ZGECON'
286  infot = 1
287  CALL zgecon( '/', 0, a, 1, anrm, rcond, w, r, info )
288  CALL chkxer( 'ZGECON', infot, nout, lerr, ok )
289  infot = 2
290  CALL zgecon( '1', -1, a, 1, anrm, rcond, w, r, info )
291  CALL chkxer( 'ZGECON', infot, nout, lerr, ok )
292  infot = 4
293  CALL zgecon( '1', 2, a, 1, anrm, rcond, w, r, info )
294  CALL chkxer( 'ZGECON', infot, nout, lerr, ok )
295 *
296 * ZGEEQU
297 *
298  srnamt = 'ZGEEQU'
299  infot = 1
300  CALL zgeequ( -1, 0, a, 1, r1, r2, rcond, ccond, anrm, info )
301  CALL chkxer( 'ZGEEQU', infot, nout, lerr, ok )
302  infot = 2
303  CALL zgeequ( 0, -1, a, 1, r1, r2, rcond, ccond, anrm, info )
304  CALL chkxer( 'ZGEEQU', infot, nout, lerr, ok )
305  infot = 4
306  CALL zgeequ( 2, 2, a, 1, r1, r2, rcond, ccond, anrm, info )
307  CALL chkxer( 'ZGEEQU', infot, nout, lerr, ok )
308 *
309 * ZGEEQUB
310 *
311  srnamt = 'ZGEEQUB'
312  infot = 1
313  CALL zgeequb( -1, 0, a, 1, r1, r2, rcond, ccond, anrm, info )
314  CALL chkxer( 'ZGEEQUB', infot, nout, lerr, ok )
315  infot = 2
316  CALL zgeequb( 0, -1, a, 1, r1, r2, rcond, ccond, anrm, info )
317  CALL chkxer( 'ZGEEQUB', infot, nout, lerr, ok )
318  infot = 4
319  CALL zgeequb( 2, 2, a, 1, r1, r2, rcond, ccond, anrm, info )
320  CALL chkxer( 'ZGEEQUB', infot, nout, lerr, ok )
321 *
322 * Test error exits of the routines that use the LU decomposition
323 * of a general band matrix.
324 *
325  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
326 *
327 * ZGBTRF
328 *
329  srnamt = 'ZGBTRF'
330  infot = 1
331  CALL zgbtrf( -1, 0, 0, 0, a, 1, ip, info )
332  CALL chkxer( 'ZGBTRF', infot, nout, lerr, ok )
333  infot = 2
334  CALL zgbtrf( 0, -1, 0, 0, a, 1, ip, info )
335  CALL chkxer( 'ZGBTRF', infot, nout, lerr, ok )
336  infot = 3
337  CALL zgbtrf( 1, 1, -1, 0, a, 1, ip, info )
338  CALL chkxer( 'ZGBTRF', infot, nout, lerr, ok )
339  infot = 4
340  CALL zgbtrf( 1, 1, 0, -1, a, 1, ip, info )
341  CALL chkxer( 'ZGBTRF', infot, nout, lerr, ok )
342  infot = 6
343  CALL zgbtrf( 2, 2, 1, 1, a, 3, ip, info )
344  CALL chkxer( 'ZGBTRF', infot, nout, lerr, ok )
345 *
346 * ZGBTF2
347 *
348  srnamt = 'ZGBTF2'
349  infot = 1
350  CALL zgbtf2( -1, 0, 0, 0, a, 1, ip, info )
351  CALL chkxer( 'ZGBTF2', infot, nout, lerr, ok )
352  infot = 2
353  CALL zgbtf2( 0, -1, 0, 0, a, 1, ip, info )
354  CALL chkxer( 'ZGBTF2', infot, nout, lerr, ok )
355  infot = 3
356  CALL zgbtf2( 1, 1, -1, 0, a, 1, ip, info )
357  CALL chkxer( 'ZGBTF2', infot, nout, lerr, ok )
358  infot = 4
359  CALL zgbtf2( 1, 1, 0, -1, a, 1, ip, info )
360  CALL chkxer( 'ZGBTF2', infot, nout, lerr, ok )
361  infot = 6
362  CALL zgbtf2( 2, 2, 1, 1, a, 3, ip, info )
363  CALL chkxer( 'ZGBTF2', infot, nout, lerr, ok )
364 *
365 * ZGBTRS
366 *
367  srnamt = 'ZGBTRS'
368  infot = 1
369  CALL zgbtrs( '/', 0, 0, 0, 1, a, 1, ip, b, 1, info )
370  CALL chkxer( 'ZGBTRS', infot, nout, lerr, ok )
371  infot = 2
372  CALL zgbtrs( 'N', -1, 0, 0, 1, a, 1, ip, b, 1, info )
373  CALL chkxer( 'ZGBTRS', infot, nout, lerr, ok )
374  infot = 3
375  CALL zgbtrs( 'N', 1, -1, 0, 1, a, 1, ip, b, 1, info )
376  CALL chkxer( 'ZGBTRS', infot, nout, lerr, ok )
377  infot = 4
378  CALL zgbtrs( 'N', 1, 0, -1, 1, a, 1, ip, b, 1, info )
379  CALL chkxer( 'ZGBTRS', infot, nout, lerr, ok )
380  infot = 5
381  CALL zgbtrs( 'N', 1, 0, 0, -1, a, 1, ip, b, 1, info )
382  CALL chkxer( 'ZGBTRS', infot, nout, lerr, ok )
383  infot = 7
384  CALL zgbtrs( 'N', 2, 1, 1, 1, a, 3, ip, b, 2, info )
385  CALL chkxer( 'ZGBTRS', infot, nout, lerr, ok )
386  infot = 10
387  CALL zgbtrs( 'N', 2, 0, 0, 1, a, 1, ip, b, 1, info )
388  CALL chkxer( 'ZGBTRS', infot, nout, lerr, ok )
389 *
390 * ZGBRFS
391 *
392  srnamt = 'ZGBRFS'
393  infot = 1
394  CALL zgbrfs( '/', 0, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
395  $ r2, w, r, info )
396  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
397  infot = 2
398  CALL zgbrfs( 'N', -1, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
399  $ r2, w, r, info )
400  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
401  infot = 3
402  CALL zgbrfs( 'N', 1, -1, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
403  $ r2, w, r, info )
404  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
405  infot = 4
406  CALL zgbrfs( 'N', 1, 0, -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
407  $ r2, w, r, info )
408  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
409  infot = 5
410  CALL zgbrfs( 'N', 1, 0, 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1,
411  $ r2, w, r, info )
412  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
413  infot = 7
414  CALL zgbrfs( 'N', 2, 1, 1, 1, a, 2, af, 4, ip, b, 2, x, 2, r1,
415  $ r2, w, r, info )
416  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
417  infot = 9
418  CALL zgbrfs( 'N', 2, 1, 1, 1, a, 3, af, 3, ip, b, 2, x, 2, r1,
419  $ r2, w, r, info )
420  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
421  infot = 12
422  CALL zgbrfs( 'N', 2, 0, 0, 1, a, 1, af, 1, ip, b, 1, x, 2, r1,
423  $ r2, w, r, info )
424  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
425  infot = 14
426  CALL zgbrfs( 'N', 2, 0, 0, 1, a, 1, af, 1, ip, b, 2, x, 1, r1,
427  $ r2, w, r, info )
428  CALL chkxer( 'ZGBRFS', infot, nout, lerr, ok )
429 *
430 * ZGBRFSX
431 *
432  n_err_bnds = 3
433  nparams = 0
434  srnamt = 'ZGBRFSX'
435  infot = 1
436  CALL zgbrfsx( '/', eq, 0, 0, 0, 0, a, 1, af, 1, ip, rs, cs, b,
437  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
438  $ err_bnds_c, nparams, params, w, r, info )
439  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
440  infot = 2
441  eq = '/'
442  CALL zgbrfsx( 'N', eq, 2, 1, 1, 1, a, 1, af, 2, ip, rs, cs, b,
443  $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
444  $ err_bnds_c, nparams, params, w, r, info )
445  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
446  infot = 3
447  eq = 'R'
448  CALL zgbrfsx( 'N', eq, -1, 1, 1, 0, a, 1, af, 1, ip, rs, cs, b,
449  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
450  $ err_bnds_c, nparams, params, w, r, info )
451  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
452  infot = 4
453  eq = 'R'
454  CALL zgbrfsx( 'N', eq, 2, -1, 1, 1, a, 3, af, 4, ip, rs, cs, b,
455  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
456  $ err_bnds_c, nparams, params, w, r, info )
457  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
458  infot = 5
459  eq = 'R'
460  CALL zgbrfsx( 'N', eq, 2, 1, -1, 1, a, 3, af, 4, ip, rs, cs, b,
461  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
462  $ err_bnds_c, nparams, params, w, r, info )
463  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
464  infot = 6
465  CALL zgbrfsx( 'N', eq, 0, 0, 0, -1, a, 1, af, 1, ip, rs, cs, b,
466  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
467  $ err_bnds_c, nparams, params, w, r, info )
468  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
469  infot = 8
470  CALL zgbrfsx( 'N', eq, 2, 1, 1, 1, a, 1, af, 2, ip, rs, cs, b,
471  $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
472  $ err_bnds_c, nparams, params, w, r, info )
473  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
474  infot = 10
475  CALL zgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 3, ip, rs, cs, b,
476  $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
477  $ err_bnds_c, nparams, params, w, r, info )
478  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
479  infot = 13
480  eq = 'C'
481  CALL zgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 5, ip, rs, cs, b,
482  $ 1, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
483  $ err_bnds_c, nparams, params, w, r, info )
484  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
485  infot = 15
486  CALL zgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 5, ip, rs, cs, b,
487  $ 2, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
488  $ err_bnds_c, nparams, params, w, r, info )
489  CALL chkxer( 'ZGBRFSX', infot, nout, lerr, ok )
490 *
491 * ZGBCON
492 *
493  srnamt = 'ZGBCON'
494  infot = 1
495  CALL zgbcon( '/', 0, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
496  CALL chkxer( 'ZGBCON', infot, nout, lerr, ok )
497  infot = 2
498  CALL zgbcon( '1', -1, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
499  CALL chkxer( 'ZGBCON', infot, nout, lerr, ok )
500  infot = 3
501  CALL zgbcon( '1', 1, -1, 0, a, 1, ip, anrm, rcond, w, r, info )
502  CALL chkxer( 'ZGBCON', infot, nout, lerr, ok )
503  infot = 4
504  CALL zgbcon( '1', 1, 0, -1, a, 1, ip, anrm, rcond, w, r, info )
505  CALL chkxer( 'ZGBCON', infot, nout, lerr, ok )
506  infot = 6
507  CALL zgbcon( '1', 2, 1, 1, a, 3, ip, anrm, rcond, w, r, info )
508  CALL chkxer( 'ZGBCON', infot, nout, lerr, ok )
509 *
510 * ZGBEQU
511 *
512  srnamt = 'ZGBEQU'
513  infot = 1
514  CALL zgbequ( -1, 0, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
515  $ info )
516  CALL chkxer( 'ZGBEQU', infot, nout, lerr, ok )
517  infot = 2
518  CALL zgbequ( 0, -1, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
519  $ info )
520  CALL chkxer( 'ZGBEQU', infot, nout, lerr, ok )
521  infot = 3
522  CALL zgbequ( 1, 1, -1, 0, a, 1, r1, r2, rcond, ccond, anrm,
523  $ info )
524  CALL chkxer( 'ZGBEQU', infot, nout, lerr, ok )
525  infot = 4
526  CALL zgbequ( 1, 1, 0, -1, a, 1, r1, r2, rcond, ccond, anrm,
527  $ info )
528  CALL chkxer( 'ZGBEQU', infot, nout, lerr, ok )
529  infot = 6
530  CALL zgbequ( 2, 2, 1, 1, a, 2, r1, r2, rcond, ccond, anrm,
531  $ info )
532  CALL chkxer( 'ZGBEQU', infot, nout, lerr, ok )
533 *
534 * ZGBEQUB
535 *
536  srnamt = 'ZGBEQUB'
537  infot = 1
538  CALL zgbequb( -1, 0, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
539  $ info )
540  CALL chkxer( 'ZGBEQUB', infot, nout, lerr, ok )
541  infot = 2
542  CALL zgbequb( 0, -1, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
543  $ info )
544  CALL chkxer( 'ZGBEQUB', infot, nout, lerr, ok )
545  infot = 3
546  CALL zgbequb( 1, 1, -1, 0, a, 1, r1, r2, rcond, ccond, anrm,
547  $ info )
548  CALL chkxer( 'ZGBEQUB', infot, nout, lerr, ok )
549  infot = 4
550  CALL zgbequb( 1, 1, 0, -1, a, 1, r1, r2, rcond, ccond, anrm,
551  $ info )
552  CALL chkxer( 'ZGBEQUB', infot, nout, lerr, ok )
553  infot = 6
554  CALL zgbequb( 2, 2, 1, 1, a, 2, r1, r2, rcond, ccond, anrm,
555  $ info )
556  CALL chkxer( 'ZGBEQUB', infot, nout, lerr, ok )
557  END IF
558 *
559 * Print a summary line.
560 *
561  CALL alaesm( path, ok, nout )
562 *
563  return
564 *
565 * End of ZERRGE
566 *
567  END