LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dsvdch()

subroutine dsvdch ( integer n,
double precision, dimension( * ) s,
double precision, dimension( * ) e,
double precision, dimension( * ) svd,
double precision tol,
integer info )

DSVDCH

Purpose:
!>
!> DSVDCH checks to see if SVD(1) ,..., SVD(N) are accurate singular
!> values of the bidiagonal matrix B with diagonal entries
!> S(1) ,..., S(N) and superdiagonal entries E(1) ,..., E(N-1)).
!> It does this by expanding each SVD(I) into an interval
!> [SVD(I) * (1-EPS) , SVD(I) * (1+EPS)], merging overlapping intervals
!> if any, and using Sturm sequences to count and verify whether each
!> resulting interval has the correct number of singular values (using
!> DSVDCT). Here EPS=TOL*MAX(N/10,1)*MAZHEP, where MACHEP is the
!> machine precision. The routine assumes the singular values are sorted
!> with SVD(1) the largest and SVD(N) smallest.  If each interval
!> contains the correct number of singular values, INFO = 0 is returned,
!> otherwise INFO is the index of the first singular value in the first
!> bad interval.
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The dimension of the bidiagonal matrix B.
!> 
[in]S
!>          S is DOUBLE PRECISION array, dimension (N)
!>          The diagonal entries of the bidiagonal matrix B.
!> 
[in]E
!>          E is DOUBLE PRECISION array, dimension (N-1)
!>          The superdiagonal entries of the bidiagonal matrix B.
!> 
[in]SVD
!>          SVD is DOUBLE PRECISION array, dimension (N)
!>          The computed singular values to be checked.
!> 
[in]TOL
!>          TOL is DOUBLE PRECISION
!>          Error tolerance for checking, a multiplier of the
!>          machine precision.
!> 
[out]INFO
!>          INFO is INTEGER
!>          =0 if the singular values are all correct (to within
!>             1 +- TOL*MAZHEPS)
!>          >0 if the interval containing the INFO-th singular value
!>             contains the incorrect number of singular values.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 96 of file dsvdch.f.

97*
98* -- LAPACK test routine --
99* -- LAPACK is a software package provided by Univ. of Tennessee, --
100* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
101*
102* .. Scalar Arguments ..
103 INTEGER INFO, N
104 DOUBLE PRECISION TOL
105* ..
106* .. Array Arguments ..
107 DOUBLE PRECISION E( * ), S( * ), SVD( * )
108* ..
109*
110* =====================================================================
111*
112* .. Parameters ..
113 DOUBLE PRECISION ONE
114 parameter( one = 1.0d0 )
115 DOUBLE PRECISION ZERO
116 parameter( zero = 0.0d0 )
117* ..
118* .. Local Scalars ..
119 INTEGER BPNT, COUNT, NUML, NUMU, TPNT
120 DOUBLE PRECISION EPS, LOWER, OVFL, TUPPR, UNFL, UNFLEP, UPPER
121* ..
122* .. External Functions ..
123 DOUBLE PRECISION DLAMCH
124 EXTERNAL dlamch
125* ..
126* .. External Subroutines ..
127 EXTERNAL dsvdct
128* ..
129* .. Intrinsic Functions ..
130 INTRINSIC max, sqrt
131* ..
132* .. Executable Statements ..
133*
134* Get machine constants
135*
136 info = 0
137 IF( n.LE.0 )
138 $ RETURN
139 unfl = dlamch( 'Safe minimum' )
140 ovfl = dlamch( 'Overflow' )
141 eps = dlamch( 'Epsilon' )*dlamch( 'Base' )
142*
143* UNFLEP is chosen so that when an eigenvalue is multiplied by the
144* scale factor sqrt(OVFL)*sqrt(sqrt(UNFL))/MX in DSVDCT, it exceeds
145* sqrt(UNFL), which is the lower limit for DSVDCT.
146*
147 unflep = ( sqrt( sqrt( unfl ) ) / sqrt( ovfl ) )*svd( 1 ) +
148 $ unfl / eps
149*
150* The value of EPS works best when TOL .GE. 10.
151*
152 eps = tol*max( n / 10, 1 )*eps
153*
154* TPNT points to singular value at right endpoint of interval
155* BPNT points to singular value at left endpoint of interval
156*
157 tpnt = 1
158 bpnt = 1
159*
160* Begin loop over all intervals
161*
162 10 CONTINUE
163 upper = ( one+eps )*svd( tpnt ) + unflep
164 lower = ( one-eps )*svd( bpnt ) - unflep
165 IF( lower.LE.unflep )
166 $ lower = -upper
167*
168* Begin loop merging overlapping intervals
169*
170 20 CONTINUE
171 IF( bpnt.EQ.n )
172 $ GO TO 30
173 tuppr = ( one+eps )*svd( bpnt+1 ) + unflep
174 IF( tuppr.LT.lower )
175 $ GO TO 30
176*
177* Merge
178*
179 bpnt = bpnt + 1
180 lower = ( one-eps )*svd( bpnt ) - unflep
181 IF( lower.LE.unflep )
182 $ lower = -upper
183 GO TO 20
184 30 CONTINUE
185*
186* Count singular values in interval [ LOWER, UPPER ]
187*
188 CALL dsvdct( n, s, e, lower, numl )
189 CALL dsvdct( n, s, e, upper, numu )
190 count = numu - numl
191 IF( lower.LT.zero )
192 $ count = count / 2
193 IF( count.NE.bpnt-tpnt+1 ) THEN
194*
195* Wrong number of singular values in interval
196*
197 info = tpnt
198 GO TO 40
199 END IF
200 tpnt = bpnt + 1
201 bpnt = tpnt
202 IF( tpnt.LE.n )
203 $ GO TO 10
204 40 CONTINUE
205 RETURN
206*
207* End of DSVDCH
208*
subroutine dsvdct(n, s, e, shift, num)
DSVDCT
Definition dsvdct.f:87
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
Here is the call graph for this function:
Here is the caller graph for this function: