LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ssvdch ( integer  N,
real, dimension( * )  S,
real, dimension( * )  E,
real, dimension( * )  SVD,
real  TOL,
integer  INFO 
)

SSVDCH

Purpose:
 SSVDCH 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
 SSVDCT). Here EPS=TOL*MAX(N/10,1)*MACHEP, 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 REAL array, dimension (N)
          The diagonal entries of the bidiagonal matrix B.
[in]E
          E is REAL array, dimension (N-1)
          The superdiagonal entries of the bidiagonal matrix B.
[in]SVD
          SVD is REAL array, dimension (N)
          The computed singular values to be checked.
[in]TOL
          TOL is REAL
          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*MACHEPS)
          >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.
Date
November 2011

Definition at line 99 of file ssvdch.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: