LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cerrgex.f
Go to the documentation of this file.
1 *> \brief \b CERRGEX
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 CERRGE( 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 *> CERRGE tests the error exits for the COMPLEX routines
25 *> for general matrices.
26 *>
27 *> Note that this file is used only when the XBLAS are available,
28 *> otherwise cerrge.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 complex_lin
57 *
58 * =====================================================================
59  SUBROUTINE cerrge( 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  REAL anrm, ccond, rcond, berr
82 * ..
83 * .. Local Arrays ..
84  INTEGER ip( nmax )
85  REAL r( nmax ), r1( nmax ), r2( nmax ), cs( nmax ),
86  $ rs( nmax )
87  COMPLEX 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( 1 )
90 * ..
91 * .. External Functions ..
92  LOGICAL lsamen
93  EXTERNAL lsamen
94 * ..
95 * .. External Subroutines ..
96  EXTERNAL alaesm, cgbcon, cgbequ, cgbrfs, cgbtf2, cgbtrf,
99  $ cgbequb, cgbrfsx
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 cmplx, real
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 ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
124  af( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
125  10 CONTINUE
126  b( j ) = 0.
127  r1( j ) = 0.
128  r2( j ) = 0.
129  w( j ) = 0.
130  x( j ) = 0.
131  cs( j ) = 0.
132  rs( j ) = 0.
133  ip( j ) = j
134  20 CONTINUE
135  ok = .true.
136 *
137 * Test error exits of the routines that use the LU decomposition
138 * of a general matrix.
139 *
140  IF( lsamen( 2, c2, 'GE' ) ) THEN
141 *
142 * CGETRF
143 *
144  srnamt = 'CGETRF'
145  infot = 1
146  CALL cgetrf( -1, 0, a, 1, ip, info )
147  CALL chkxer( 'CGETRF', infot, nout, lerr, ok )
148  infot = 2
149  CALL cgetrf( 0, -1, a, 1, ip, info )
150  CALL chkxer( 'CGETRF', infot, nout, lerr, ok )
151  infot = 4
152  CALL cgetrf( 2, 1, a, 1, ip, info )
153  CALL chkxer( 'CGETRF', infot, nout, lerr, ok )
154 *
155 * CGETF2
156 *
157  srnamt = 'CGETF2'
158  infot = 1
159  CALL cgetf2( -1, 0, a, 1, ip, info )
160  CALL chkxer( 'CGETF2', infot, nout, lerr, ok )
161  infot = 2
162  CALL cgetf2( 0, -1, a, 1, ip, info )
163  CALL chkxer( 'CGETF2', infot, nout, lerr, ok )
164  infot = 4
165  CALL cgetf2( 2, 1, a, 1, ip, info )
166  CALL chkxer( 'CGETF2', infot, nout, lerr, ok )
167 *
168 * CGETRI
169 *
170  srnamt = 'CGETRI'
171  infot = 1
172  CALL cgetri( -1, a, 1, ip, w, 1, info )
173  CALL chkxer( 'CGETRI', infot, nout, lerr, ok )
174  infot = 3
175  CALL cgetri( 2, a, 1, ip, w, 2, info )
176  CALL chkxer( 'CGETRI', infot, nout, lerr, ok )
177  infot = 6
178  CALL cgetri( 2, a, 2, ip, w, 1, info )
179  CALL chkxer( 'CGETRI', infot, nout, lerr, ok )
180 *
181 * CGETRS
182 *
183  srnamt = 'CGETRS'
184  infot = 1
185  CALL cgetrs( '/', 0, 0, a, 1, ip, b, 1, info )
186  CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
187  infot = 2
188  CALL cgetrs( 'N', -1, 0, a, 1, ip, b, 1, info )
189  CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
190  infot = 3
191  CALL cgetrs( 'N', 0, -1, a, 1, ip, b, 1, info )
192  CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
193  infot = 5
194  CALL cgetrs( 'N', 2, 1, a, 1, ip, b, 2, info )
195  CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
196  infot = 8
197  CALL cgetrs( 'N', 2, 1, a, 2, ip, b, 1, info )
198  CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
199 *
200 * CGERFS
201 *
202  srnamt = 'CGERFS'
203  infot = 1
204  CALL cgerfs( '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
205  $ r, info )
206  CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
207  infot = 2
208  CALL cgerfs( 'N', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
209  $ w, r, info )
210  CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
211  infot = 3
212  CALL cgerfs( 'N', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
213  $ w, r, info )
214  CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
215  infot = 5
216  CALL cgerfs( 'N', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
217  $ r, info )
218  CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
219  infot = 7
220  CALL cgerfs( 'N', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
221  $ r, info )
222  CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
223  infot = 10
224  CALL cgerfs( 'N', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
225  $ r, info )
226  CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
227  infot = 12
228  CALL cgerfs( 'N', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
229  $ r, info )
230  CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
231 *
232 * CGERFSX
233 *
234  n_err_bnds = 3
235  nparams = 0
236  srnamt = 'CGERFSX'
237  infot = 1
238  CALL cgerfsx( '/', eq, 0, 0, a, 1, af, 1, ip, rs, cs, b, 1, x,
239  $ 1, rcond, berr, n_err_bnds, err_bnds_n,
240  $ err_bnds_c, nparams, params, w, r, info )
241  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
242  infot = 2
243  eq = '/'
244  CALL cgerfsx( 'N', eq, 2, 1, a, 1, af, 2, ip, rs, cs, b, 2, x,
245  $ 2, rcond, berr, n_err_bnds, err_bnds_n,
246  $ err_bnds_c, nparams, params, w, r, info )
247  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
248  infot = 3
249  eq = 'R'
250  CALL cgerfsx( 'N', eq, -1, 0, a, 1, af, 1, ip, rs, cs, b, 1, x,
251  $ 1, rcond, berr, n_err_bnds, err_bnds_n,
252  $ err_bnds_c, nparams, params, w, r, info )
253  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
254  infot = 4
255  CALL cgerfsx( 'N', eq, 0, -1, a, 1, af, 1, ip, rs, cs, b, 1, x,
256  $ 1, rcond, berr, n_err_bnds, err_bnds_n,
257  $ err_bnds_c, nparams, params, w, r, info )
258  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
259  infot = 6
260  CALL cgerfsx( 'N', eq, 2, 1, a, 1, af, 2, ip, rs, cs, b, 2, x,
261  $ 2, rcond, berr, n_err_bnds, err_bnds_n,
262  $ err_bnds_c, nparams, params, w, r, info )
263  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
264  infot = 8
265  CALL cgerfsx( 'N', eq, 2, 1, a, 2, af, 1, ip, rs, cs, b, 2, x,
266  $ 2, rcond, berr, n_err_bnds, err_bnds_n,
267  $ err_bnds_c, nparams, params, w, r, info )
268  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
269  infot = 13
270  eq = 'C'
271  CALL cgerfsx( 'N', eq, 2, 1, a, 2, af, 2, ip, rs, cs, b, 1, x,
272  $ 2, rcond, berr, n_err_bnds, err_bnds_n,
273  $ err_bnds_c, nparams, params, w, r, info )
274  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
275  infot = 15
276  CALL cgerfsx( 'N', eq, 2, 1, a, 2, af, 2, ip, rs, cs, b, 2, x,
277  $ 1, rcond, berr, n_err_bnds, err_bnds_n,
278  $ err_bnds_c, nparams, params, w, r, info )
279  CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
280 *
281 * CGECON
282 *
283  srnamt = 'CGECON'
284  infot = 1
285  CALL cgecon( '/', 0, a, 1, anrm, rcond, w, r, info )
286  CALL chkxer( 'CGECON', infot, nout, lerr, ok )
287  infot = 2
288  CALL cgecon( '1', -1, a, 1, anrm, rcond, w, r, info )
289  CALL chkxer( 'CGECON', infot, nout, lerr, ok )
290  infot = 4
291  CALL cgecon( '1', 2, a, 1, anrm, rcond, w, r, info )
292  CALL chkxer( 'CGECON', infot, nout, lerr, ok )
293 *
294 * CGEEQU
295 *
296  srnamt = 'CGEEQU'
297  infot = 1
298  CALL cgeequ( -1, 0, a, 1, r1, r2, rcond, ccond, anrm, info )
299  CALL chkxer( 'CGEEQU', infot, nout, lerr, ok )
300  infot = 2
301  CALL cgeequ( 0, -1, a, 1, r1, r2, rcond, ccond, anrm, info )
302  CALL chkxer( 'CGEEQU', infot, nout, lerr, ok )
303  infot = 4
304  CALL cgeequ( 2, 2, a, 1, r1, r2, rcond, ccond, anrm, info )
305  CALL chkxer( 'CGEEQU', infot, nout, lerr, ok )
306 *
307 * CGEEQUB
308 *
309  srnamt = 'CGEEQUB'
310  infot = 1
311  CALL cgeequb( -1, 0, a, 1, r1, r2, rcond, ccond, anrm, info )
312  CALL chkxer( 'CGEEQUB', infot, nout, lerr, ok )
313  infot = 2
314  CALL cgeequb( 0, -1, a, 1, r1, r2, rcond, ccond, anrm, info )
315  CALL chkxer( 'CGEEQUB', infot, nout, lerr, ok )
316  infot = 4
317  CALL cgeequb( 2, 2, a, 1, r1, r2, rcond, ccond, anrm, info )
318  CALL chkxer( 'CGEEQUB', infot, nout, lerr, ok )
319 *
320 * Test error exits of the routines that use the LU decomposition
321 * of a general band matrix.
322 *
323  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
324 *
325 * CGBTRF
326 *
327  srnamt = 'CGBTRF'
328  infot = 1
329  CALL cgbtrf( -1, 0, 0, 0, a, 1, ip, info )
330  CALL chkxer( 'CGBTRF', infot, nout, lerr, ok )
331  infot = 2
332  CALL cgbtrf( 0, -1, 0, 0, a, 1, ip, info )
333  CALL chkxer( 'CGBTRF', infot, nout, lerr, ok )
334  infot = 3
335  CALL cgbtrf( 1, 1, -1, 0, a, 1, ip, info )
336  CALL chkxer( 'CGBTRF', infot, nout, lerr, ok )
337  infot = 4
338  CALL cgbtrf( 1, 1, 0, -1, a, 1, ip, info )
339  CALL chkxer( 'CGBTRF', infot, nout, lerr, ok )
340  infot = 6
341  CALL cgbtrf( 2, 2, 1, 1, a, 3, ip, info )
342  CALL chkxer( 'CGBTRF', infot, nout, lerr, ok )
343 *
344 * CGBTF2
345 *
346  srnamt = 'CGBTF2'
347  infot = 1
348  CALL cgbtf2( -1, 0, 0, 0, a, 1, ip, info )
349  CALL chkxer( 'CGBTF2', infot, nout, lerr, ok )
350  infot = 2
351  CALL cgbtf2( 0, -1, 0, 0, a, 1, ip, info )
352  CALL chkxer( 'CGBTF2', infot, nout, lerr, ok )
353  infot = 3
354  CALL cgbtf2( 1, 1, -1, 0, a, 1, ip, info )
355  CALL chkxer( 'CGBTF2', infot, nout, lerr, ok )
356  infot = 4
357  CALL cgbtf2( 1, 1, 0, -1, a, 1, ip, info )
358  CALL chkxer( 'CGBTF2', infot, nout, lerr, ok )
359  infot = 6
360  CALL cgbtf2( 2, 2, 1, 1, a, 3, ip, info )
361  CALL chkxer( 'CGBTF2', infot, nout, lerr, ok )
362 *
363 * CGBTRS
364 *
365  srnamt = 'CGBTRS'
366  infot = 1
367  CALL cgbtrs( '/', 0, 0, 0, 1, a, 1, ip, b, 1, info )
368  CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
369  infot = 2
370  CALL cgbtrs( 'N', -1, 0, 0, 1, a, 1, ip, b, 1, info )
371  CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
372  infot = 3
373  CALL cgbtrs( 'N', 1, -1, 0, 1, a, 1, ip, b, 1, info )
374  CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
375  infot = 4
376  CALL cgbtrs( 'N', 1, 0, -1, 1, a, 1, ip, b, 1, info )
377  CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
378  infot = 5
379  CALL cgbtrs( 'N', 1, 0, 0, -1, a, 1, ip, b, 1, info )
380  CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
381  infot = 7
382  CALL cgbtrs( 'N', 2, 1, 1, 1, a, 3, ip, b, 2, info )
383  CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
384  infot = 10
385  CALL cgbtrs( 'N', 2, 0, 0, 1, a, 1, ip, b, 1, info )
386  CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
387 *
388 * CGBRFS
389 *
390  srnamt = 'CGBRFS'
391  infot = 1
392  CALL cgbrfs( '/', 0, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
393  $ r2, w, r, info )
394  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
395  infot = 2
396  CALL cgbrfs( 'N', -1, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
397  $ r2, w, r, info )
398  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
399  infot = 3
400  CALL cgbrfs( 'N', 1, -1, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
401  $ r2, w, r, info )
402  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
403  infot = 4
404  CALL cgbrfs( 'N', 1, 0, -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
405  $ r2, w, r, info )
406  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
407  infot = 5
408  CALL cgbrfs( 'N', 1, 0, 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1,
409  $ r2, w, r, info )
410  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
411  infot = 7
412  CALL cgbrfs( 'N', 2, 1, 1, 1, a, 2, af, 4, ip, b, 2, x, 2, r1,
413  $ r2, w, r, info )
414  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
415  infot = 9
416  CALL cgbrfs( 'N', 2, 1, 1, 1, a, 3, af, 3, ip, b, 2, x, 2, r1,
417  $ r2, w, r, info )
418  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
419  infot = 12
420  CALL cgbrfs( 'N', 2, 0, 0, 1, a, 1, af, 1, ip, b, 1, x, 2, r1,
421  $ r2, w, r, info )
422  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
423  infot = 14
424  CALL cgbrfs( 'N', 2, 0, 0, 1, a, 1, af, 1, ip, b, 2, x, 1, r1,
425  $ r2, w, r, info )
426  CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
427 *
428 * CGBRFSX
429 *
430  n_err_bnds = 3
431  nparams = 0
432  srnamt = 'CGBRFSX'
433  infot = 1
434  CALL cgbrfsx( '/', eq, 0, 0, 0, 0, a, 1, af, 1, ip, rs, cs, b,
435  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
436  $ err_bnds_c, nparams, params, w, r, info )
437  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
438  infot = 2
439  eq = '/'
440  CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 1, af, 2, ip, rs, cs, b,
441  $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
442  $ err_bnds_c, nparams, params, w, r, info )
443  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
444  infot = 3
445  eq = 'R'
446  CALL cgbrfsx( 'N', eq, -1, 1, 1, 0, a, 1, af, 1, ip, rs, cs, b,
447  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
448  $ err_bnds_c, nparams, params, w, r, info )
449  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
450  infot = 4
451  eq = 'R'
452  CALL cgbrfsx( 'N', eq, 2, -1, 1, 1, a, 3, af, 4, ip, rs, cs, b,
453  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
454  $ err_bnds_c, nparams, params, w, r, info )
455  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
456  infot = 5
457  eq = 'R'
458  CALL cgbrfsx( 'N', eq, 2, 1, -1, 1, a, 3, af, 4, ip, rs, cs, b,
459  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
460  $ err_bnds_c, nparams, params, w, r, info )
461  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
462  infot = 6
463  CALL cgbrfsx( 'N', eq, 0, 0, 0, -1, a, 1, af, 1, ip, rs, cs, b,
464  $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
465  $ err_bnds_c, nparams, params, w, r, info )
466  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
467  infot = 8
468  CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 1, af, 2, ip, rs, cs, b,
469  $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
470  $ err_bnds_c, nparams, params, w, r, info )
471  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
472  infot = 10
473  CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 3, ip, rs, cs, b,
474  $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
475  $ err_bnds_c, nparams, params, w, r, info )
476  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
477  infot = 13
478  eq = 'C'
479  CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 5, ip, rs, cs, b,
480  $ 1, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
481  $ err_bnds_c, nparams, params, w, r, info )
482  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
483  infot = 15
484  CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 5, ip, rs, cs, b,
485  $ 2, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
486  $ err_bnds_c, nparams, params, w, r, info )
487  CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
488 *
489 * CGBCON
490 *
491  srnamt = 'CGBCON'
492  infot = 1
493  CALL cgbcon( '/', 0, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
494  CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
495  infot = 2
496  CALL cgbcon( '1', -1, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
497  CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
498  infot = 3
499  CALL cgbcon( '1', 1, -1, 0, a, 1, ip, anrm, rcond, w, r, info )
500  CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
501  infot = 4
502  CALL cgbcon( '1', 1, 0, -1, a, 1, ip, anrm, rcond, w, r, info )
503  CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
504  infot = 6
505  CALL cgbcon( '1', 2, 1, 1, a, 3, ip, anrm, rcond, w, r, info )
506  CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
507 *
508 * CGBEQU
509 *
510  srnamt = 'CGBEQU'
511  infot = 1
512  CALL cgbequ( -1, 0, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
513  $ info )
514  CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
515  infot = 2
516  CALL cgbequ( 0, -1, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
517  $ info )
518  CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
519  infot = 3
520  CALL cgbequ( 1, 1, -1, 0, a, 1, r1, r2, rcond, ccond, anrm,
521  $ info )
522  CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
523  infot = 4
524  CALL cgbequ( 1, 1, 0, -1, a, 1, r1, r2, rcond, ccond, anrm,
525  $ info )
526  CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
527  infot = 6
528  CALL cgbequ( 2, 2, 1, 1, a, 2, r1, r2, rcond, ccond, anrm,
529  $ info )
530  CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
531 *
532 * CGBEQUB
533 *
534  srnamt = 'CGBEQUB'
535  infot = 1
536  CALL cgbequb( -1, 0, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
537  $ info )
538  CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
539  infot = 2
540  CALL cgbequb( 0, -1, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
541  $ info )
542  CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
543  infot = 3
544  CALL cgbequb( 1, 1, -1, 0, a, 1, r1, r2, rcond, ccond, anrm,
545  $ info )
546  CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
547  infot = 4
548  CALL cgbequb( 1, 1, 0, -1, a, 1, r1, r2, rcond, ccond, anrm,
549  $ info )
550  CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
551  infot = 6
552  CALL cgbequb( 2, 2, 1, 1, a, 2, r1, r2, rcond, ccond, anrm,
553  $ info )
554  CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
555  END IF
556 *
557 * Print a summary line.
558 *
559  CALL alaesm( path, ok, nout )
560 *
561  RETURN
562 *
563 * End of CERRGE
564 *
565  END
subroutine cgbtrf(M, N, KL, KU, AB, LDAB, IPIV, INFO)
CGBTRF
Definition: cgbtrf.f:146
subroutine cgetri(N, A, LDA, IPIV, WORK, LWORK, INFO)
CGETRI
Definition: cgetri.f:116
subroutine cgerfs(TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CGERFS
Definition: cgerfs.f:188
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
subroutine cgerfsx(TRANS, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV, R, C, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
CGERFSX
Definition: cgerfsx.f:416
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine cgetrs(TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CGETRS
Definition: cgetrs.f:123
subroutine cgbequb(M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND, AMAX, INFO)
CGBEQUB
Definition: cgbequb.f:163
subroutine cgbrfsx(TRANS, EQUED, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, R, C, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
CGBRFSX
Definition: cgbrfsx.f:442
subroutine cgeequb(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)
CGEEQUB
Definition: cgeequb.f:149
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine cgeequ(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)
CGEEQU
Definition: cgeequ.f:142
subroutine cgbcon(NORM, N, KL, KU, AB, LDAB, IPIV, ANORM, RCOND, WORK, RWORK, INFO)
CGBCON
Definition: cgbcon.f:149
subroutine cgetrf(M, N, A, LDA, IPIV, INFO)
CGETRF
Definition: cgetrf.f:110
subroutine cgbequ(M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND, AMAX, INFO)
CGBEQU
Definition: cgbequ.f:156
subroutine cgetf2(M, N, A, LDA, IPIV, INFO)
CGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row inter...
Definition: cgetf2.f:110
subroutine cgbrfs(TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CGBRFS
Definition: cgbrfs.f:208
subroutine cgecon(NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK, INFO)
CGECON
Definition: cgecon.f:126
subroutine cerrge(PATH, NUNIT)
CERRGE
Definition: cerrge.f:57
subroutine cgbtf2(M, N, KL, KU, AB, LDAB, IPIV, INFO)
CGBTF2 computes the LU factorization of a general band matrix using the unblocked version of the algo...
Definition: cgbtf2.f:147
subroutine cgbtrs(TRANS, N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
CGBTRS
Definition: cgbtrs.f:140