LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cerred ( character*3  PATH,
integer  NUNIT 
)

CERRED

Purpose:
 CERRED tests the error exits for the eigenvalue driver routines for
 REAL matrices:

 PATH  driver   description
 ----  ------   -----------
 CEV   CGEEV    find eigenvalues/eigenvectors for nonsymmetric A
 CES   CGEES    find eigenvalues/Schur form for nonsymmetric A
 CVX   CGEEVX   CGEEV + balancing and condition estimation
 CSX   CGEESX   CGEES + balancing and condition estimation
 CBD   CGESVD   compute SVD of an M-by-N matrix A
       CGESDD   compute SVD of an M-by-N matrix A(by divide and
                conquer)
       CGEJSV   compute SVD of an M-by-N matrix A where M >= N
       CGESVDX  compute SVD of an M-by-N matrix A(by bisection
                and inverse iteration)
Parameters
[in]PATH
          PATH is CHARACTER*3
          The LAPACK path name for the routines to be tested.
[in]NUNIT
          NUNIT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
June 2016

Definition at line 70 of file cerred.f.

70 *
71 * -- LAPACK test routine (version 3.6.1) --
72 * -- LAPACK is a software package provided by Univ. of Tennessee, --
73 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
74 * June 2016
75 *
76 * .. Scalar Arguments ..
77  CHARACTER*3 path
78  INTEGER nunit
79 * ..
80 *
81 * =====================================================================
82 *
83 * .. Parameters ..
84  INTEGER nmax, lw
85  parameter ( nmax = 4, lw = 5*nmax )
86  REAL one, zero
87  parameter ( one = 1.0e0, zero = 0.0e0 )
88 * ..
89 * .. Local Scalars ..
90  CHARACTER*2 c2
91  INTEGER i, ihi, ilo, info, j, ns, nt, sdim
92  REAL abnrm
93 * ..
94 * .. Local Arrays ..
95  LOGICAL b( nmax )
96  INTEGER iw( 4*nmax )
97  REAL r1( nmax ), r2( nmax ), rw( lw ), s( nmax )
98  COMPLEX a( nmax, nmax ), u( nmax, nmax ),
99  $ vl( nmax, nmax ), vr( nmax, nmax ),
100  $ vt( nmax, nmax ), w( 10*nmax ), x( nmax )
101 * ..
102 * .. External Subroutines ..
103  EXTERNAL chkxer, cgees, cgeesx, cgeev, cgeevx, cgejsv,
104  $ cgesdd, cgesvd
105 * ..
106 * .. External Functions ..
107  LOGICAL lsamen, cslect
108  EXTERNAL lsamen, cslect
109 * ..
110 * .. Intrinsic Functions ..
111  INTRINSIC len_trim
112 * ..
113 * .. Arrays in Common ..
114  LOGICAL selval( 20 )
115  REAL selwi( 20 ), selwr( 20 )
116 * ..
117 * .. Scalars in Common ..
118  LOGICAL lerr, ok
119  CHARACTER*32 srnamt
120  INTEGER infot, nout, seldim, selopt
121 * ..
122 * .. Common blocks ..
123  COMMON / infoc / infot, nout, ok, lerr
124  COMMON / srnamc / srnamt
125  COMMON / sslct / selopt, seldim, selval, selwr, selwi
126 * ..
127 * .. Executable Statements ..
128 *
129  nout = nunit
130  WRITE( nout, fmt = * )
131  c2 = path( 2: 3 )
132 *
133 * Initialize A
134 *
135  DO 20 j = 1, nmax
136  DO 10 i = 1, nmax
137  a( i, j ) = zero
138  10 CONTINUE
139  20 CONTINUE
140  DO 30 i = 1, nmax
141  a( i, i ) = one
142  30 CONTINUE
143  ok = .true.
144  nt = 0
145 *
146  IF( lsamen( 2, c2, 'EV' ) ) THEN
147 *
148 * Test CGEEV
149 *
150  srnamt = 'CGEEV '
151  infot = 1
152  CALL cgeev( 'X', 'N', 0, a, 1, x, vl, 1, vr, 1, w, 1, rw,
153  $ info )
154  CALL chkxer( 'CGEEV ', infot, nout, lerr, ok )
155  infot = 2
156  CALL cgeev( 'N', 'X', 0, a, 1, x, vl, 1, vr, 1, w, 1, rw,
157  $ info )
158  CALL chkxer( 'CGEEV ', infot, nout, lerr, ok )
159  infot = 3
160  CALL cgeev( 'N', 'N', -1, a, 1, x, vl, 1, vr, 1, w, 1, rw,
161  $ info )
162  CALL chkxer( 'CGEEV ', infot, nout, lerr, ok )
163  infot = 5
164  CALL cgeev( 'N', 'N', 2, a, 1, x, vl, 1, vr, 1, w, 4, rw,
165  $ info )
166  CALL chkxer( 'CGEEV ', infot, nout, lerr, ok )
167  infot = 8
168  CALL cgeev( 'V', 'N', 2, a, 2, x, vl, 1, vr, 1, w, 4, rw,
169  $ info )
170  CALL chkxer( 'CGEEV ', infot, nout, lerr, ok )
171  infot = 10
172  CALL cgeev( 'N', 'V', 2, a, 2, x, vl, 1, vr, 1, w, 4, rw,
173  $ info )
174  CALL chkxer( 'CGEEV ', infot, nout, lerr, ok )
175  infot = 12
176  CALL cgeev( 'V', 'V', 1, a, 1, x, vl, 1, vr, 1, w, 1, rw,
177  $ info )
178  CALL chkxer( 'CGEEV ', infot, nout, lerr, ok )
179  nt = nt + 7
180 *
181  ELSE IF( lsamen( 2, c2, 'ES' ) ) THEN
182 *
183 * Test CGEES
184 *
185  srnamt = 'CGEES '
186  infot = 1
187  CALL cgees( 'X', 'N', cslect, 0, a, 1, sdim, x, vl, 1, w, 1,
188  $ rw, b, info )
189  CALL chkxer( 'CGEES ', infot, nout, lerr, ok )
190  infot = 2
191  CALL cgees( 'N', 'X', cslect, 0, a, 1, sdim, x, vl, 1, w, 1,
192  $ rw, b, info )
193  CALL chkxer( 'CGEES ', infot, nout, lerr, ok )
194  infot = 4
195  CALL cgees( 'N', 'S', cslect, -1, a, 1, sdim, x, vl, 1, w, 1,
196  $ rw, b, info )
197  CALL chkxer( 'CGEES ', infot, nout, lerr, ok )
198  infot = 6
199  CALL cgees( 'N', 'S', cslect, 2, a, 1, sdim, x, vl, 1, w, 4,
200  $ rw, b, info )
201  CALL chkxer( 'CGEES ', infot, nout, lerr, ok )
202  infot = 10
203  CALL cgees( 'V', 'S', cslect, 2, a, 2, sdim, x, vl, 1, w, 4,
204  $ rw, b, info )
205  CALL chkxer( 'CGEES ', infot, nout, lerr, ok )
206  infot = 12
207  CALL cgees( 'N', 'S', cslect, 1, a, 1, sdim, x, vl, 1, w, 1,
208  $ rw, b, info )
209  CALL chkxer( 'CGEES ', infot, nout, lerr, ok )
210  nt = nt + 6
211 *
212  ELSE IF( lsamen( 2, c2, 'VX' ) ) THEN
213 *
214 * Test CGEEVX
215 *
216  srnamt = 'CGEEVX'
217  infot = 1
218  CALL cgeevx( 'X', 'N', 'N', 'N', 0, a, 1, x, vl, 1, vr, 1, ilo,
219  $ ihi, s, abnrm, r1, r2, w, 1, rw, info )
220  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
221  infot = 2
222  CALL cgeevx( 'N', 'X', 'N', 'N', 0, a, 1, x, vl, 1, vr, 1, ilo,
223  $ ihi, s, abnrm, r1, r2, w, 1, rw, info )
224  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
225  infot = 3
226  CALL cgeevx( 'N', 'N', 'X', 'N', 0, a, 1, x, vl, 1, vr, 1, ilo,
227  $ ihi, s, abnrm, r1, r2, w, 1, rw, info )
228  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
229  infot = 4
230  CALL cgeevx( 'N', 'N', 'N', 'X', 0, a, 1, x, vl, 1, vr, 1, ilo,
231  $ ihi, s, abnrm, r1, r2, w, 1, rw, info )
232  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
233  infot = 5
234  CALL cgeevx( 'N', 'N', 'N', 'N', -1, a, 1, x, vl, 1, vr, 1,
235  $ ilo, ihi, s, abnrm, r1, r2, w, 1, rw, info )
236  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
237  infot = 7
238  CALL cgeevx( 'N', 'N', 'N', 'N', 2, a, 1, x, vl, 1, vr, 1, ilo,
239  $ ihi, s, abnrm, r1, r2, w, 4, rw, info )
240  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
241  infot = 10
242  CALL cgeevx( 'N', 'V', 'N', 'N', 2, a, 2, x, vl, 1, vr, 1, ilo,
243  $ ihi, s, abnrm, r1, r2, w, 4, rw, info )
244  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
245  infot = 12
246  CALL cgeevx( 'N', 'N', 'V', 'N', 2, a, 2, x, vl, 1, vr, 1, ilo,
247  $ ihi, s, abnrm, r1, r2, w, 4, rw, info )
248  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
249  infot = 20
250  CALL cgeevx( 'N', 'N', 'N', 'N', 1, a, 1, x, vl, 1, vr, 1, ilo,
251  $ ihi, s, abnrm, r1, r2, w, 1, rw, info )
252  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
253  infot = 20
254  CALL cgeevx( 'N', 'N', 'V', 'V', 1, a, 1, x, vl, 1, vr, 1, ilo,
255  $ ihi, s, abnrm, r1, r2, w, 2, rw, info )
256  CALL chkxer( 'CGEEVX', infot, nout, lerr, ok )
257  nt = nt + 10
258 *
259  ELSE IF( lsamen( 2, c2, 'SX' ) ) THEN
260 *
261 * Test CGEESX
262 *
263  srnamt = 'CGEESX'
264  infot = 1
265  CALL cgeesx( 'X', 'N', cslect, 'N', 0, a, 1, sdim, x, vl, 1,
266  $ r1( 1 ), r2( 1 ), w, 1, rw, b, info )
267  CALL chkxer( 'CGEESX', infot, nout, lerr, ok )
268  infot = 2
269  CALL cgeesx( 'N', 'X', cslect, 'N', 0, a, 1, sdim, x, vl, 1,
270  $ r1( 1 ), r2( 1 ), w, 1, rw, b, info )
271  CALL chkxer( 'CGEESX', infot, nout, lerr, ok )
272  infot = 4
273  CALL cgeesx( 'N', 'N', cslect, 'X', 0, a, 1, sdim, x, vl, 1,
274  $ r1( 1 ), r2( 1 ), w, 1, rw, b, info )
275  CALL chkxer( 'CGEESX', infot, nout, lerr, ok )
276  infot = 5
277  CALL cgeesx( 'N', 'N', cslect, 'N', -1, a, 1, sdim, x, vl, 1,
278  $ r1( 1 ), r2( 1 ), w, 1, rw, b, info )
279  CALL chkxer( 'CGEESX', infot, nout, lerr, ok )
280  infot = 7
281  CALL cgeesx( 'N', 'N', cslect, 'N', 2, a, 1, sdim, x, vl, 1,
282  $ r1( 1 ), r2( 1 ), w, 4, rw, b, info )
283  CALL chkxer( 'CGEESX', infot, nout, lerr, ok )
284  infot = 11
285  CALL cgeesx( 'V', 'N', cslect, 'N', 2, a, 2, sdim, x, vl, 1,
286  $ r1( 1 ), r2( 1 ), w, 4, rw, b, info )
287  CALL chkxer( 'CGEESX', infot, nout, lerr, ok )
288  infot = 15
289  CALL cgeesx( 'N', 'N', cslect, 'N', 1, a, 1, sdim, x, vl, 1,
290  $ r1( 1 ), r2( 1 ), w, 1, rw, b, info )
291  CALL chkxer( 'CGEESX', infot, nout, lerr, ok )
292  nt = nt + 7
293 *
294  ELSE IF( lsamen( 2, c2, 'BD' ) ) THEN
295 *
296 * Test CGESVD
297 *
298  srnamt = 'CGESVD'
299  infot = 1
300  CALL cgesvd( 'X', 'N', 0, 0, a, 1, s, u, 1, vt, 1, w, 1, rw,
301  $ info )
302  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
303  infot = 2
304  CALL cgesvd( 'N', 'X', 0, 0, a, 1, s, u, 1, vt, 1, w, 1, rw,
305  $ info )
306  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
307  infot = 2
308  CALL cgesvd( 'O', 'O', 0, 0, a, 1, s, u, 1, vt, 1, w, 1, rw,
309  $ info )
310  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
311  infot = 3
312  CALL cgesvd( 'N', 'N', -1, 0, a, 1, s, u, 1, vt, 1, w, 1, rw,
313  $ info )
314  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
315  infot = 4
316  CALL cgesvd( 'N', 'N', 0, -1, a, 1, s, u, 1, vt, 1, w, 1, rw,
317  $ info )
318  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
319  infot = 6
320  CALL cgesvd( 'N', 'N', 2, 1, a, 1, s, u, 1, vt, 1, w, 5, rw,
321  $ info )
322  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
323  infot = 9
324  CALL cgesvd( 'A', 'N', 2, 1, a, 2, s, u, 1, vt, 1, w, 5, rw,
325  $ info )
326  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
327  infot = 11
328  CALL cgesvd( 'N', 'A', 1, 2, a, 1, s, u, 1, vt, 1, w, 5, rw,
329  $ info )
330  CALL chkxer( 'CGESVD', infot, nout, lerr, ok )
331  nt = nt + 8
332  IF( ok ) THEN
333  WRITE( nout, fmt = 9999 )srnamt( 1:len_trim( srnamt ) ),
334  $ nt
335  ELSE
336  WRITE( nout, fmt = 9998 )
337  END IF
338 *
339 * Test CGESDD
340 *
341  srnamt = 'CGESDD'
342  infot = 1
343  CALL cgesdd( 'X', 0, 0, a, 1, s, u, 1, vt, 1, w, 1, rw, iw,
344  $ info )
345  CALL chkxer( 'CGESDD', infot, nout, lerr, ok )
346  infot = 2
347  CALL cgesdd( 'N', -1, 0, a, 1, s, u, 1, vt, 1, w, 1, rw, iw,
348  $ info )
349  CALL chkxer( 'CGESDD', infot, nout, lerr, ok )
350  infot = 3
351  CALL cgesdd( 'N', 0, -1, a, 1, s, u, 1, vt, 1, w, 1, rw, iw,
352  $ info )
353  CALL chkxer( 'CGESDD', infot, nout, lerr, ok )
354  infot = 5
355  CALL cgesdd( 'N', 2, 1, a, 1, s, u, 1, vt, 1, w, 5, rw, iw,
356  $ info )
357  CALL chkxer( 'CGESDD', infot, nout, lerr, ok )
358  infot = 8
359  CALL cgesdd( 'A', 2, 1, a, 2, s, u, 1, vt, 1, w, 5, rw, iw,
360  $ info )
361  CALL chkxer( 'CGESDD', infot, nout, lerr, ok )
362  infot = 10
363  CALL cgesdd( 'A', 1, 2, a, 1, s, u, 1, vt, 1, w, 5, rw, iw,
364  $ info )
365  CALL chkxer( 'CGESDD', infot, nout, lerr, ok )
366  nt = nt - 2
367  IF( ok ) THEN
368  WRITE( nout, fmt = 9999 )srnamt( 1:len_trim( srnamt ) ),
369  $ nt
370  ELSE
371  WRITE( nout, fmt = 9998 )
372  END IF
373 *
374 * Test CGEJSV
375 *
376  srnamt = 'CGEJSV'
377  infot = 1
378  CALL cgejsv( 'X', 'U', 'V', 'R', 'N', 'N',
379  $ 0, 0, a, 1, s, u, 1, vt, 1,
380  $ w, 1, rw, 1, iw, info)
381  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
382  infot = 2
383  CALL cgejsv( 'G', 'X', 'V', 'R', 'N', 'N',
384  $ 0, 0, a, 1, s, u, 1, vt, 1,
385  $ w, 1, rw, 1, iw, info)
386  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
387  infot = 3
388  CALL cgejsv( 'G', 'U', 'X', 'R', 'N', 'N',
389  $ 0, 0, a, 1, s, u, 1, vt, 1,
390  $ w, 1, rw, 1, iw, info)
391  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
392  infot = 4
393  CALL cgejsv( 'G', 'U', 'V', 'X', 'N', 'N',
394  $ 0, 0, a, 1, s, u, 1, vt, 1,
395  $ w, 1, rw, 1, iw, info)
396  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
397  infot = 5
398  CALL cgejsv( 'G', 'U', 'V', 'R', 'X', 'N',
399  $ 0, 0, a, 1, s, u, 1, vt, 1,
400  $ w, 1, rw, 1, iw, info)
401  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
402  infot = 6
403  CALL cgejsv( 'G', 'U', 'V', 'R', 'N', 'X',
404  $ 0, 0, a, 1, s, u, 1, vt, 1,
405  $ w, 1, rw, 1, iw, info)
406  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
407  infot = 7
408  CALL cgejsv( 'G', 'U', 'V', 'R', 'N', 'N',
409  $ -1, 0, a, 1, s, u, 1, vt, 1,
410  $ w, 1, rw, 1, iw, info)
411  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
412  infot = 8
413  CALL cgejsv( 'G', 'U', 'V', 'R', 'N', 'N',
414  $ 0, -1, a, 1, s, u, 1, vt, 1,
415  $ w, 1, rw, 1, iw, info)
416  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
417  infot = 10
418  CALL cgejsv( 'G', 'U', 'V', 'R', 'N', 'N',
419  $ 2, 1, a, 1, s, u, 1, vt, 1,
420  $ w, 1, rw, 1, iw, info)
421  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
422  infot = 13
423  CALL cgejsv( 'G', 'U', 'V', 'R', 'N', 'N',
424  $ 2, 2, a, 2, s, u, 1, vt, 2,
425  $ w, 1, rw, 1, iw, info)
426  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
427  infot = 15
428  CALL cgejsv( 'G', 'U', 'V', 'R', 'N', 'N',
429  $ 2, 2, a, 2, s, u, 2, vt, 1,
430  $ w, 1, rw, 1, iw, info)
431  CALL chkxer( 'CGEJSV', infot, nout, lerr, ok )
432  nt = 11
433  IF( ok ) THEN
434  WRITE( nout, fmt = 9999 )srnamt( 1:len_trim( srnamt ) ),
435  $ nt
436  ELSE
437  WRITE( nout, fmt = 9998 )
438  END IF
439 *
440 * Test CGESVDX
441 *
442  srnamt = 'CGESVDX'
443  infot = 1
444  CALL cgesvdx( 'X', 'N', 'A', 0, 0, a, 1, zero, zero,
445  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
446  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
447  infot = 2
448  CALL cgesvdx( 'N', 'X', 'A', 0, 0, a, 1, zero, zero,
449  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
450  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
451  infot = 3
452  CALL cgesvdx( 'N', 'N', 'X', 0, 0, a, 1, zero, zero,
453  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
454  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
455  infot = 4
456  CALL cgesvdx( 'N', 'N', 'A', -1, 0, a, 1, zero, zero,
457  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
458  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
459  infot = 5
460  CALL cgesvdx( 'N', 'N', 'A', 0, -1, a, 1, zero, zero,
461  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
462  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
463  infot = 7
464  CALL cgesvdx( 'N', 'N', 'A', 2, 1, a, 1, zero, zero,
465  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
466  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
467  infot = 8
468  CALL cgesvdx( 'N', 'N', 'V', 2, 1, a, 2, -one, zero,
469  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
470  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
471  infot = 9
472  CALL cgesvdx( 'N', 'N', 'V', 2, 1, a, 2, one, zero,
473  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
474  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
475  infot = 10
476  CALL cgesvdx( 'N', 'N', 'I', 2, 2, a, 2, zero, zero,
477  $ 0, 1, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
478  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
479  infot = 11
480  CALL cgesvdx( 'V', 'N', 'I', 2, 2, a, 2, zero, zero,
481  $ 1, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
482  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
483  infot = 15
484  CALL cgesvdx( 'V', 'N', 'A', 2, 2, a, 2, zero, zero,
485  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
486  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
487  infot = 17
488  CALL cgesvdx( 'N', 'V', 'A', 2, 2, a, 2, zero, zero,
489  $ 0, 0, ns, s, u, 1, vt, 1, w, 1, rw, iw, info )
490  CALL chkxer( 'CGESVDX', infot, nout, lerr, ok )
491  nt = 12
492  IF( ok ) THEN
493  WRITE( nout, fmt = 9999 )srnamt( 1:len_trim( srnamt ) ),
494  $ nt
495  ELSE
496  WRITE( nout, fmt = 9998 )
497  END IF
498  END IF
499 *
500 * Print a summary line.
501 *
502  IF( .NOT.lsamen( 2, c2, 'BD' ) ) THEN
503  IF( ok ) THEN
504  WRITE( nout, fmt = 9999 )srnamt( 1:len_trim( srnamt ) ),
505  $ nt
506  ELSE
507  WRITE( nout, fmt = 9998 )
508  END IF
509  END IF
510 *
511  9999 FORMAT( 1x, a, ' passed the tests of the error exits (', i3,
512  $ ' tests done)' )
513  9998 FORMAT( ' *** ', a, ' failed the tests of the error exits ***' )
514  RETURN
515 *
516 * End of CERRED
517 *
subroutine cgeev(JOBVL, JOBVR, N, A, LDA, W, VL, LDVL, VR, LDVR, WORK, LWORK, RWORK, INFO)
CGEEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for GE matrices ...
Definition: cgeev.f:181
subroutine cgesvd(JOBU, JOBVT, M, N, A, LDA, S, U, LDU, VT, LDVT, WORK, LWORK, RWORK, INFO)
CGESVD computes the singular value decomposition (SVD) for GE matrices
Definition: cgesvd.f:216
logical function cslect(Z)
CSLECT
Definition: cslect.f:58
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
subroutine cgesvdx(JOBU, JOBVT, RANGE, M, N, A, LDA, VL, VU, IL, IU, NS, S, U, LDU, VT, LDVT, WORK, LWORK, RWORK, IWORK, INFO)
CGESVDX computes the singular value decomposition (SVD) for GE matrices
Definition: cgesvdx.f:272
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine cgees(JOBVS, SORT, SELECT, N, A, LDA, SDIM, W, VS, LDVS, WORK, LWORK, RWORK, BWORK, INFO)
CGEES computes the eigenvalues, the Schur form, and, optionally, the matrix of Schur vectors for GE ...
Definition: cgees.f:199
subroutine cgejsv(JOBA, JOBU, JOBV, JOBR, JOBT, JOBP, M, N, A, LDA, SVA, U, LDU, V, LDV, CWORK, LWORK, RWORK, LRWORK, IWORK, INFO)
CGEJSV
Definition: cgejsv.f:519
subroutine cgeesx(JOBVS, SORT, SELECT, SENSE, N, A, LDA, SDIM, W, VS, LDVS, RCONDE, RCONDV, WORK, LWORK, RWORK, BWORK, INFO)
CGEESX computes the eigenvalues, the Schur form, and, optionally, the matrix of Schur vectors for GE...
Definition: cgeesx.f:241
subroutine cgeevx(BALANC, JOBVL, JOBVR, SENSE, N, A, LDA, W, VL, LDVL, VR, LDVR, ILO, IHI, SCALE, ABNRM, RCONDE, RCONDV, WORK, LWORK, RWORK, INFO)
CGEEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for GE matrices ...
Definition: cgeevx.f:289
subroutine cgesdd(JOBZ, M, N, A, LDA, S, U, LDU, VT, LDVT, WORK, LWORK, RWORK, IWORK, INFO)
CGESDD
Definition: cgesdd.f:228

Here is the call graph for this function:

Here is the caller graph for this function: