LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cchkbk.f
Go to the documentation of this file.
1 *> \brief \b CCHKBK
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 CCHKBK( NIN, NOUT )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER NIN, NOUT
15 * ..
16 *
17 *
18 *> \par Purpose:
19 * =============
20 *>
21 *> \verbatim
22 *>
23 *> CCHKBK tests CGEBAK, a routine for backward transformation of
24 *> the computed right or left eigenvectors if the orginal matrix
25 *> was preprocessed by balance subroutine CGEBAL.
26 *> \endverbatim
27 *
28 * Arguments:
29 * ==========
30 *
31 *> \param[in] NIN
32 *> \verbatim
33 *> NIN is INTEGER
34 *> The logical unit number for input. NIN > 0.
35 *> \endverbatim
36 *>
37 *> \param[in] NOUT
38 *> \verbatim
39 *> NOUT is INTEGER
40 *> The logical unit number for output. NOUT > 0.
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 *> \date November 2011
52 *
53 *> \ingroup complex_eig
54 *
55 * =====================================================================
56  SUBROUTINE cchkbk( NIN, NOUT )
57 *
58 * -- LAPACK test routine (version 3.4.0) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * November 2011
62 *
63 * .. Scalar Arguments ..
64  INTEGER NIN, NOUT
65 * ..
66 *
67 * ======================================================================
68 *
69 * .. Parameters ..
70  INTEGER LDE
71  parameter ( lde = 20 )
72  REAL ZERO
73  parameter ( zero = 0.0e0 )
74 * ..
75 * .. Local Scalars ..
76  INTEGER I, IHI, ILO, INFO, J, KNT, N, NINFO
77  REAL EPS, RMAX, SAFMIN, VMAX, X
78  COMPLEX CDUM
79 * ..
80 * .. Local Arrays ..
81  INTEGER LMAX( 2 )
82  REAL SCALE( lde )
83  COMPLEX E( lde, lde ), EIN( lde, lde )
84 * ..
85 * .. External Functions ..
86  REAL SLAMCH
87  EXTERNAL slamch
88 * ..
89 * .. External Subroutines ..
90  EXTERNAL cgebak
91 * ..
92 * .. Intrinsic Functions ..
93  INTRINSIC abs, aimag, max, real
94 * ..
95 * .. Statement Functions ..
96  REAL CABS1
97 * ..
98 * .. Statement Function definitions ..
99  cabs1( cdum ) = abs( REAL( CDUM ) ) + abs( AIMAG( cdum ) )
100 * ..
101 * .. Executable Statements ..
102 *
103  lmax( 1 ) = 0
104  lmax( 2 ) = 0
105  ninfo = 0
106  knt = 0
107  rmax = zero
108  eps = slamch( 'E' )
109  safmin = slamch( 'S' )
110 *
111  10 CONTINUE
112 *
113  READ( nin, fmt = * )n, ilo, ihi
114  IF( n.EQ.0 )
115  $ GO TO 60
116 *
117  READ( nin, fmt = * )( scale( i ), i = 1, n )
118  DO 20 i = 1, n
119  READ( nin, fmt = * )( e( i, j ), j = 1, n )
120  20 CONTINUE
121 *
122  DO 30 i = 1, n
123  READ( nin, fmt = * )( ein( i, j ), j = 1, n )
124  30 CONTINUE
125 *
126  knt = knt + 1
127  CALL cgebak( 'B', 'R', n, ilo, ihi, scale, n, e, lde, info )
128 *
129  IF( info.NE.0 ) THEN
130  ninfo = ninfo + 1
131  lmax( 1 ) = knt
132  END IF
133 *
134  vmax = zero
135  DO 50 i = 1, n
136  DO 40 j = 1, n
137  x = cabs1( e( i, j )-ein( i, j ) ) / eps
138  IF( cabs1( e( i, j ) ).GT.safmin )
139  $ x = x / cabs1( e( i, j ) )
140  vmax = max( vmax, x )
141  40 CONTINUE
142  50 CONTINUE
143 *
144  IF( vmax.GT.rmax ) THEN
145  lmax( 2 ) = knt
146  rmax = vmax
147  END IF
148 *
149  GO TO 10
150 *
151  60 CONTINUE
152 *
153  WRITE( nout, fmt = 9999 )
154  9999 FORMAT( 1x, '.. test output of CGEBAK .. ' )
155 *
156  WRITE( nout, fmt = 9998 )rmax
157  9998 FORMAT( 1x, 'value of largest test error = ', e12.3 )
158  WRITE( nout, fmt = 9997 )lmax( 1 )
159  9997 FORMAT( 1x, 'example number where info is not zero = ', i4 )
160  WRITE( nout, fmt = 9996 )lmax( 2 )
161  9996 FORMAT( 1x, 'example number having largest error = ', i4 )
162  WRITE( nout, fmt = 9995 )ninfo
163  9995 FORMAT( 1x, 'number of examples where info is not 0 = ', i4 )
164  WRITE( nout, fmt = 9994 )knt
165  9994 FORMAT( 1x, 'total number of examples tested = ', i4 )
166 *
167  RETURN
168 *
169 * End of CCHKBK
170 *
171  END
subroutine cgebak(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV, INFO)
CGEBAK
Definition: cgebak.f:133
subroutine cchkbk(NIN, NOUT)
CCHKBK
Definition: cchkbk.f:57