LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zchkbl.f
Go to the documentation of this file.
1*> \brief \b ZCHKBL
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 ZCHKBL( NIN, NOUT )
12*
13* .. Scalar Arguments ..
14* INTEGER NIN, NOUT
15* ..
16*
17*
18*> \par Purpose:
19* =============
20*>
21*> \verbatim
22*>
23*> ZCHKBL tests ZGEBAL, a routine for balancing a general complex
24*> matrix and isolating some of its eigenvalues.
25*> \endverbatim
26*
27* Arguments:
28* ==========
29*
30*> \param[in] NIN
31*> \verbatim
32*> NIN is INTEGER
33*> The logical unit number for input. NIN > 0.
34*> \endverbatim
35*>
36*> \param[in] NOUT
37*> \verbatim
38*> NOUT is INTEGER
39*> The logical unit number for output. NOUT > 0.
40*> \endverbatim
41*
42* Authors:
43* ========
44*
45*> \author Univ. of Tennessee
46*> \author Univ. of California Berkeley
47*> \author Univ. of Colorado Denver
48*> \author NAG Ltd.
49*
50*> \ingroup complex16_eig
51*
52* =====================================================================
53 SUBROUTINE zchkbl( NIN, NOUT )
54*
55* -- LAPACK test routine --
56* -- LAPACK is a software package provided by Univ. of Tennessee, --
57* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
58*
59* .. Scalar Arguments ..
60 INTEGER NIN, NOUT
61* ..
62*
63* ======================================================================
64*
65* .. Parameters ..
66 INTEGER LDA
67 parameter( lda = 20 )
68 DOUBLE PRECISION ZERO
69 parameter( zero = 0.0d+0 )
70* ..
71* .. Local Scalars ..
72 INTEGER I, IHI, IHIIN, ILO, ILOIN, INFO, J, KNT, N,
73 $ NINFO
74 DOUBLE PRECISION ANORM, MEPS, RMAX, SFMIN, TEMP, VMAX
75 COMPLEX*16 CDUM
76* ..
77* .. Local Arrays ..
78 INTEGER LMAX( 3 )
79 DOUBLE PRECISION DUMMY( 1 ), SCALE( LDA ), SCALIN( LDA )
80 COMPLEX*16 A( LDA, LDA ), AIN( LDA, LDA )
81* ..
82* .. External Functions ..
83 DOUBLE PRECISION DLAMCH, ZLANGE
84 EXTERNAL dlamch, zlange
85* ..
86* .. External Subroutines ..
87 EXTERNAL zgebal
88* ..
89* .. Intrinsic Functions ..
90 INTRINSIC abs, dble, dimag, max
91* ..
92* .. Statement Functions ..
93 DOUBLE PRECISION CABS1
94* ..
95* .. Statement Function definitions ..
96 cabs1( cdum ) = abs( dble( cdum ) ) + abs( dimag( cdum ) )
97* ..
98* .. Executable Statements ..
99*
100 lmax( 1 ) = 0
101 lmax( 2 ) = 0
102 lmax( 3 ) = 0
103 ninfo = 0
104 knt = 0
105 rmax = zero
106 vmax = zero
107 sfmin = dlamch( 'S' )
108 meps = dlamch( 'E' )
109*
110 10 CONTINUE
111*
112 READ( nin, fmt = * )n
113 IF( n.EQ.0 )
114 $ GO TO 70
115 DO 20 i = 1, n
116 READ( nin, fmt = * )( a( i, j ), j = 1, n )
117 20 CONTINUE
118*
119 READ( nin, fmt = * )iloin, ihiin
120 DO 30 i = 1, n
121 READ( nin, fmt = * )( ain( i, j ), j = 1, n )
122 30 CONTINUE
123 READ( nin, fmt = * )( scalin( i ), i = 1, n )
124*
125 anorm = zlange( 'M', n, n, a, lda, dummy )
126 knt = knt + 1
127 CALL zgebal( 'B', n, a, lda, ilo, ihi, scale, info )
128*
129 IF( info.NE.0 ) THEN
130 ninfo = ninfo + 1
131 lmax( 1 ) = knt
132 END IF
133*
134 IF( ilo.NE.iloin .OR. ihi.NE.ihiin ) THEN
135 ninfo = ninfo + 1
136 lmax( 2 ) = knt
137 END IF
138*
139 DO 50 i = 1, n
140 DO 40 j = 1, n
141 temp = max( cabs1( a( i, j ) ), cabs1( ain( i, j ) ) )
142 temp = max( temp, sfmin )
143 vmax = max( vmax, cabs1( a( i, j )-ain( i, j ) ) / temp )
144 40 CONTINUE
145 50 CONTINUE
146*
147 DO 60 i = 1, n
148 temp = max( scale( i ), scalin( i ) )
149 temp = max( temp, sfmin )
150 vmax = max( vmax, abs( scale( i )-scalin( i ) ) / temp )
151 60 CONTINUE
152*
153 IF( vmax.GT.rmax ) THEN
154 lmax( 3 ) = knt
155 rmax = vmax
156 END IF
157*
158 GO TO 10
159*
160 70 CONTINUE
161*
162 WRITE( nout, fmt = 9999 )
163 9999 FORMAT( 1x, '.. test output of ZGEBAL .. ' )
164*
165 WRITE( nout, fmt = 9998 )rmax
166 9998 FORMAT( 1x, 'value of largest test error = ', d12.3 )
167 WRITE( nout, fmt = 9997 )lmax( 1 )
168 9997 FORMAT( 1x, 'example number where info is not zero = ', i4 )
169 WRITE( nout, fmt = 9996 )lmax( 2 )
170 9996 FORMAT( 1x, 'example number where ILO or IHI wrong = ', i4 )
171 WRITE( nout, fmt = 9995 )lmax( 3 )
172 9995 FORMAT( 1x, 'example number having largest error = ', i4 )
173 WRITE( nout, fmt = 9994 )ninfo
174 9994 FORMAT( 1x, 'number of examples where info is not 0 = ', i4 )
175 WRITE( nout, fmt = 9993 )knt
176 9993 FORMAT( 1x, 'total number of examples tested = ', i4 )
177*
178 RETURN
179*
180* End of ZCHKBL
181*
182 END
subroutine zgebal(job, n, a, lda, ilo, ihi, scale, info)
ZGEBAL
Definition zgebal.f:165
subroutine zchkbl(nin, nout)
ZCHKBL
Definition zchkbl.f:54