LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zerrpox.f
Go to the documentation of this file.
1 *> \brief \b ZERRPOX
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 ZERRPO( 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 *> ZERRPO tests the error exits for the COMPLEX*16 routines
25 *> for Hermitian positive definite matrices.
26 *>
27 *> Note that this file is used only when the XBLAS are available,
28 *> otherwise zerrpo.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 zerrpo( 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, rcond, berr
82 * ..
83 * .. Local Arrays ..
84  DOUBLE PRECISION s( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
85  $ err_bnds_n( nmax, 3 ), err_bnds_c( nmax, 3 ),
86  $ params( 1 )
87  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
88  $ w( 2*nmax ), x( nmax )
89 * ..
90 * .. External Functions ..
91  LOGICAL lsamen
92  EXTERNAL lsamen
93 * ..
94 * .. External Subroutines ..
95  EXTERNAL alaesm, chkxer, zpbcon, zpbequ, zpbrfs, zpbtf2,
99 * ..
100 * .. Scalars in Common ..
101  LOGICAL lerr, ok
102  CHARACTER*32 srnamt
103  INTEGER infot, nout
104 * ..
105 * .. Common blocks ..
106  common / infoc / infot, nout, ok, lerr
107  common / srnamc / srnamt
108 * ..
109 * .. Intrinsic Functions ..
110  INTRINSIC dble, dcmplx
111 * ..
112 * .. Executable Statements ..
113 *
114  nout = nunit
115  WRITE( nout, fmt = * )
116  c2 = path( 2: 3 )
117 *
118 * Set the variables to innocuous values.
119 *
120  DO 20 j = 1, nmax
121  DO 10 i = 1, nmax
122  a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
123  $ -1.d0 / dble( i+j ) )
124  af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
125  $ -1.d0 / dble( i+j ) )
126  10 continue
127  b( j ) = 0.d0
128  r1( j ) = 0.d0
129  r2( j ) = 0.d0
130  w( j ) = 0.d0
131  x( j ) = 0.d0
132  s( j ) = 0.d0
133  20 continue
134  anrm = 1.d0
135  ok = .true.
136 *
137 * Test error exits of the routines that use the Cholesky
138 * decomposition of a Hermitian positive definite matrix.
139 *
140  IF( lsamen( 2, c2, 'PO' ) ) THEN
141 *
142 * ZPOTRF
143 *
144  srnamt = 'ZPOTRF'
145  infot = 1
146  CALL zpotrf( '/', 0, a, 1, info )
147  CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
148  infot = 2
149  CALL zpotrf( 'U', -1, a, 1, info )
150  CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
151  infot = 4
152  CALL zpotrf( 'U', 2, a, 1, info )
153  CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
154 *
155 * ZPOTF2
156 *
157  srnamt = 'ZPOTF2'
158  infot = 1
159  CALL zpotf2( '/', 0, a, 1, info )
160  CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
161  infot = 2
162  CALL zpotf2( 'U', -1, a, 1, info )
163  CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
164  infot = 4
165  CALL zpotf2( 'U', 2, a, 1, info )
166  CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
167 *
168 * ZPOTRI
169 *
170  srnamt = 'ZPOTRI'
171  infot = 1
172  CALL zpotri( '/', 0, a, 1, info )
173  CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
174  infot = 2
175  CALL zpotri( 'U', -1, a, 1, info )
176  CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
177  infot = 4
178  CALL zpotri( 'U', 2, a, 1, info )
179  CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
180 *
181 * ZPOTRS
182 *
183  srnamt = 'ZPOTRS'
184  infot = 1
185  CALL zpotrs( '/', 0, 0, a, 1, b, 1, info )
186  CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
187  infot = 2
188  CALL zpotrs( 'U', -1, 0, a, 1, b, 1, info )
189  CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
190  infot = 3
191  CALL zpotrs( 'U', 0, -1, a, 1, b, 1, info )
192  CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
193  infot = 5
194  CALL zpotrs( 'U', 2, 1, a, 1, b, 2, info )
195  CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
196  infot = 7
197  CALL zpotrs( 'U', 2, 1, a, 2, b, 1, info )
198  CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
199 *
200 * ZPORFS
201 *
202  srnamt = 'ZPORFS'
203  infot = 1
204  CALL zporfs( '/', 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
205  $ info )
206  CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
207  infot = 2
208  CALL zporfs( 'U', -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
209  $ info )
210  CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
211  infot = 3
212  CALL zporfs( 'U', 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
213  $ info )
214  CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
215  infot = 5
216  CALL zporfs( 'U', 2, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w, r,
217  $ info )
218  CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
219  infot = 7
220  CALL zporfs( 'U', 2, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w, r,
221  $ info )
222  CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
223  infot = 9
224  CALL zporfs( 'U', 2, 1, a, 2, af, 2, b, 1, x, 2, r1, r2, w, r,
225  $ info )
226  CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
227  infot = 11
228  CALL zporfs( 'U', 2, 1, a, 2, af, 2, b, 2, x, 1, r1, r2, w, r,
229  $ info )
230  CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
231 *
232 * ZPORFSX
233 *
234  n_err_bnds = 3
235  nparams = 0
236  srnamt = 'ZPORFSX'
237  infot = 1
238  CALL zporfsx( '/', eq, 0, 0, a, 1, af, 1, s, b, 1, x, 1,
239  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
240  $ params, w, r, info )
241  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
242  infot = 2
243  CALL zporfsx( 'U', eq, -1, 0, a, 1, af, 1, s, b, 1, x, 1,
244  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
245  $ params, w, r, info )
246  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
247  eq = 'N'
248  infot = 3
249  CALL zporfsx( 'U', eq, -1, 0, a, 1, af, 1, s, b, 1, x, 1,
250  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
251  $ params, w, r, info )
252  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
253  infot = 4
254  CALL zporfsx( 'U', eq, 0, -1, a, 1, af, 1, s, b, 1, x, 1,
255  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
256  $ params, w, r, info )
257  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
258  infot = 6
259  CALL zporfsx( 'U', eq, 2, 1, a, 1, af, 2, s, b, 2, x, 2,
260  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
261  $ params, w, r, info )
262  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
263  infot = 8
264  CALL zporfsx( 'U', eq, 2, 1, a, 2, af, 1, s, b, 2, x, 2,
265  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
266  $ params, w, r, info )
267  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
268  infot = 11
269  CALL zporfsx( 'U', eq, 2, 1, a, 2, af, 2, s, b, 1, x, 2,
270  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
271  $ params, w, r, info )
272  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
273  infot = 13
274  CALL zporfsx( 'U', eq, 2, 1, a, 2, af, 2, s, b, 2, x, 1,
275  $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
276  $ params, w, r, info )
277  CALL chkxer( 'ZPORFSX', infot, nout, lerr, ok )
278 *
279 * ZPOCON
280 *
281  srnamt = 'ZPOCON'
282  infot = 1
283  CALL zpocon( '/', 0, a, 1, anrm, rcond, w, r, info )
284  CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
285  infot = 2
286  CALL zpocon( 'U', -1, a, 1, anrm, rcond, w, r, info )
287  CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
288  infot = 4
289  CALL zpocon( 'U', 2, a, 1, anrm, rcond, w, r, info )
290  CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
291  infot = 5
292  CALL zpocon( 'U', 1, a, 1, -anrm, rcond, w, r, info )
293  CALL chkxer( 'ZPOCON', infot, nout, lerr, ok )
294 *
295 * ZPOEQU
296 *
297  srnamt = 'ZPOEQU'
298  infot = 1
299  CALL zpoequ( -1, a, 1, r1, rcond, anrm, info )
300  CALL chkxer( 'ZPOEQU', infot, nout, lerr, ok )
301  infot = 3
302  CALL zpoequ( 2, a, 1, r1, rcond, anrm, info )
303  CALL chkxer( 'ZPOEQU', infot, nout, lerr, ok )
304 *
305 * ZPOEQUB
306 *
307  srnamt = 'ZPOEQUB'
308  infot = 1
309  CALL zpoequb( -1, a, 1, r1, rcond, anrm, info )
310  CALL chkxer( 'ZPOEQUB', infot, nout, lerr, ok )
311  infot = 3
312  CALL zpoequb( 2, a, 1, r1, rcond, anrm, info )
313  CALL chkxer( 'ZPOEQUB', infot, nout, lerr, ok )
314 *
315 * Test error exits of the routines that use the Cholesky
316 * decomposition of a Hermitian positive definite packed matrix.
317 *
318  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
319 *
320 * ZPPTRF
321 *
322  srnamt = 'ZPPTRF'
323  infot = 1
324  CALL zpptrf( '/', 0, a, info )
325  CALL chkxer( 'ZPPTRF', infot, nout, lerr, ok )
326  infot = 2
327  CALL zpptrf( 'U', -1, a, info )
328  CALL chkxer( 'ZPPTRF', infot, nout, lerr, ok )
329 *
330 * ZPPTRI
331 *
332  srnamt = 'ZPPTRI'
333  infot = 1
334  CALL zpptri( '/', 0, a, info )
335  CALL chkxer( 'ZPPTRI', infot, nout, lerr, ok )
336  infot = 2
337  CALL zpptri( 'U', -1, a, info )
338  CALL chkxer( 'ZPPTRI', infot, nout, lerr, ok )
339 *
340 * ZPPTRS
341 *
342  srnamt = 'ZPPTRS'
343  infot = 1
344  CALL zpptrs( '/', 0, 0, a, b, 1, info )
345  CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
346  infot = 2
347  CALL zpptrs( 'U', -1, 0, a, b, 1, info )
348  CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
349  infot = 3
350  CALL zpptrs( 'U', 0, -1, a, b, 1, info )
351  CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
352  infot = 6
353  CALL zpptrs( 'U', 2, 1, a, b, 1, info )
354  CALL chkxer( 'ZPPTRS', infot, nout, lerr, ok )
355 *
356 * ZPPRFS
357 *
358  srnamt = 'ZPPRFS'
359  infot = 1
360  CALL zpprfs( '/', 0, 0, a, af, b, 1, x, 1, r1, r2, w, r, info )
361  CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
362  infot = 2
363  CALL zpprfs( 'U', -1, 0, a, af, b, 1, x, 1, r1, r2, w, r,
364  $ info )
365  CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
366  infot = 3
367  CALL zpprfs( 'U', 0, -1, a, af, b, 1, x, 1, r1, r2, w, r,
368  $ info )
369  CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
370  infot = 7
371  CALL zpprfs( 'U', 2, 1, a, af, b, 1, x, 2, r1, r2, w, r, info )
372  CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
373  infot = 9
374  CALL zpprfs( 'U', 2, 1, a, af, b, 2, x, 1, r1, r2, w, r, info )
375  CALL chkxer( 'ZPPRFS', infot, nout, lerr, ok )
376 *
377 * ZPPCON
378 *
379  srnamt = 'ZPPCON'
380  infot = 1
381  CALL zppcon( '/', 0, a, anrm, rcond, w, r, info )
382  CALL chkxer( 'ZPPCON', infot, nout, lerr, ok )
383  infot = 2
384  CALL zppcon( 'U', -1, a, anrm, rcond, w, r, info )
385  CALL chkxer( 'ZPPCON', infot, nout, lerr, ok )
386  infot = 4
387  CALL zppcon( 'U', 1, a, -anrm, rcond, w, r, info )
388  CALL chkxer( 'ZPPCON', infot, nout, lerr, ok )
389 *
390 * ZPPEQU
391 *
392  srnamt = 'ZPPEQU'
393  infot = 1
394  CALL zppequ( '/', 0, a, r1, rcond, anrm, info )
395  CALL chkxer( 'ZPPEQU', infot, nout, lerr, ok )
396  infot = 2
397  CALL zppequ( 'U', -1, a, r1, rcond, anrm, info )
398  CALL chkxer( 'ZPPEQU', infot, nout, lerr, ok )
399 *
400 * Test error exits of the routines that use the Cholesky
401 * decomposition of a Hermitian positive definite band matrix.
402 *
403  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
404 *
405 * ZPBTRF
406 *
407  srnamt = 'ZPBTRF'
408  infot = 1
409  CALL zpbtrf( '/', 0, 0, a, 1, info )
410  CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
411  infot = 2
412  CALL zpbtrf( 'U', -1, 0, a, 1, info )
413  CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
414  infot = 3
415  CALL zpbtrf( 'U', 1, -1, a, 1, info )
416  CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
417  infot = 5
418  CALL zpbtrf( 'U', 2, 1, a, 1, info )
419  CALL chkxer( 'ZPBTRF', infot, nout, lerr, ok )
420 *
421 * ZPBTF2
422 *
423  srnamt = 'ZPBTF2'
424  infot = 1
425  CALL zpbtf2( '/', 0, 0, a, 1, info )
426  CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
427  infot = 2
428  CALL zpbtf2( 'U', -1, 0, a, 1, info )
429  CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
430  infot = 3
431  CALL zpbtf2( 'U', 1, -1, a, 1, info )
432  CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
433  infot = 5
434  CALL zpbtf2( 'U', 2, 1, a, 1, info )
435  CALL chkxer( 'ZPBTF2', infot, nout, lerr, ok )
436 *
437 * ZPBTRS
438 *
439  srnamt = 'ZPBTRS'
440  infot = 1
441  CALL zpbtrs( '/', 0, 0, 0, a, 1, b, 1, info )
442  CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
443  infot = 2
444  CALL zpbtrs( 'U', -1, 0, 0, a, 1, b, 1, info )
445  CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
446  infot = 3
447  CALL zpbtrs( 'U', 1, -1, 0, a, 1, b, 1, info )
448  CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
449  infot = 4
450  CALL zpbtrs( 'U', 0, 0, -1, a, 1, b, 1, info )
451  CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
452  infot = 6
453  CALL zpbtrs( 'U', 2, 1, 1, a, 1, b, 1, info )
454  CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
455  infot = 8
456  CALL zpbtrs( 'U', 2, 0, 1, a, 1, b, 1, info )
457  CALL chkxer( 'ZPBTRS', infot, nout, lerr, ok )
458 *
459 * ZPBRFS
460 *
461  srnamt = 'ZPBRFS'
462  infot = 1
463  CALL zpbrfs( '/', 0, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
464  $ r, info )
465  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
466  infot = 2
467  CALL zpbrfs( 'U', -1, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
468  $ r, info )
469  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
470  infot = 3
471  CALL zpbrfs( 'U', 1, -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
472  $ r, info )
473  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
474  infot = 4
475  CALL zpbrfs( 'U', 0, 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
476  $ r, info )
477  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
478  infot = 6
479  CALL zpbrfs( 'U', 2, 1, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w,
480  $ r, info )
481  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
482  infot = 8
483  CALL zpbrfs( 'U', 2, 1, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w,
484  $ r, info )
485  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
486  infot = 10
487  CALL zpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 1, x, 2, r1, r2, w,
488  $ r, info )
489  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
490  infot = 12
491  CALL zpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 2, x, 1, r1, r2, w,
492  $ r, info )
493  CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
494 *
495 * ZPBCON
496 *
497  srnamt = 'ZPBCON'
498  infot = 1
499  CALL zpbcon( '/', 0, 0, a, 1, anrm, rcond, w, r, info )
500  CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
501  infot = 2
502  CALL zpbcon( 'U', -1, 0, a, 1, anrm, rcond, w, r, info )
503  CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
504  infot = 3
505  CALL zpbcon( 'U', 1, -1, a, 1, anrm, rcond, w, r, info )
506  CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
507  infot = 5
508  CALL zpbcon( 'U', 2, 1, a, 1, anrm, rcond, w, r, info )
509  CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
510  infot = 6
511  CALL zpbcon( 'U', 1, 0, a, 1, -anrm, rcond, w, r, info )
512  CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
513 *
514 * ZPBEQU
515 *
516  srnamt = 'ZPBEQU'
517  infot = 1
518  CALL zpbequ( '/', 0, 0, a, 1, r1, rcond, anrm, info )
519  CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
520  infot = 2
521  CALL zpbequ( 'U', -1, 0, a, 1, r1, rcond, anrm, info )
522  CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
523  infot = 3
524  CALL zpbequ( 'U', 1, -1, a, 1, r1, rcond, anrm, info )
525  CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
526  infot = 5
527  CALL zpbequ( 'U', 2, 1, a, 1, r1, rcond, anrm, info )
528  CALL chkxer( 'ZPBEQU', infot, nout, lerr, ok )
529  END IF
530 *
531 * Print a summary line.
532 *
533  CALL alaesm( path, ok, nout )
534 *
535  return
536 *
537 * End of ZERRPO
538 *
539  END