Skip to content

Commit deed8f3

Browse files
SORBDB6: improve numerical stability
* Require unit-norm vector X for otherwise the following computations might underflow * Avoid over- and underflows in the computation of the Euclidean norm of X * Fix the Euclidean norm computation after the second Gram-Schmidt iteration * Consider round-off errors when checking for zero vectors * Update identifiers
1 parent 774e5a9 commit deed8f3

File tree

1 file changed

+30
-39
lines changed

1 file changed

+30
-39
lines changed

SRC/sorbdb6.f

Lines changed: 30 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -41,8 +41,9 @@
4141
*> with respect to the columns of
4242
*> Q = [ Q1 ] .
4343
*> [ Q2 ]
44-
*> The columns of Q must be orthonormal. The orthogonalized vector will
45-
*> be zero if and only if it lies entirely in the range of Q.
44+
*> The Euclidean norm of X must be one and the columns of Q must be
45+
*> orthonormal. The orthogonalized vector will be zero if and only if it
46+
*> lies entirely in the range of Q.
4647
*>
4748
*> The projection is computed with at most two iterations of the
4849
*> classical Gram-Schmidt algorithm, see
@@ -172,14 +173,17 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
172173
* =====================================================================
173174
*
174175
* .. Parameters ..
175-
REAL ALPHASQ, REALZERO
176-
PARAMETER ( ALPHASQ = 0.01E0, REALZERO = 0.0E0 )
176+
REAL ALPHA, REALZERO
177+
PARAMETER ( ALPHA = 0.1E0, REALZERO = 0.0E0 )
177178
REAL NEGONE, ONE, ZERO
178179
PARAMETER ( NEGONE = -1.0E0, ONE = 1.0E0, ZERO = 0.0E0 )
179180
* ..
180181
* .. Local Scalars ..
181182
INTEGER I, IX
182-
REAL NORMSQ1, NORMSQ2, SCL1, SCL2, SSQ1, SSQ2
183+
REAL EPS, NORM, NORM_NEW, SCL, SSQ
184+
* ..
185+
* .. External Functions ..
186+
REAL SLAMCH
183187
* ..
184188
* .. External Subroutines ..
185189
EXTERNAL SGEMV, SLASSQ, XERBLA
@@ -214,26 +218,17 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
214218
CALL XERBLA( 'SORBDB6', -INFO )
215219
RETURN
216220
END IF
221+
*
222+
EPS = SLAMCH( 'Precision' )
217223
*
218224
* First, project X onto the orthogonal complement of Q's column
219225
* space
220226
*
221-
SCL1 = REALZERO
222-
SSQ1 = REALZERO
223-
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
224-
SCL2 = REALZERO
225-
SSQ2 = REALZERO
226-
CALL SLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
227-
NORMSQ1 = SCL1**2*SSQ1 + SCL2**2*SSQ2
228-
IF ( NORMSQ1 .EQ. 0 ) THEN
229-
DO IX = 1, 1 + (M1-1)*INCX1, INCX1
230-
X1( IX ) = ZERO
231-
END DO
232-
DO IX = 1, 1 + (M2-1)*INCX2, INCX2
233-
X2( IX ) = ZERO
234-
END DO
235-
RETURN
236-
END IF
227+
* Christoph Conrads: In debugging mode the norm should be computed
228+
* and an assertion added comparing the norm with one. Alas, Fortran
229+
* never made it into 1989 when assert() was introduced into the C
230+
* programming language.
231+
NORM = 1.0E0
237232
*
238233
IF( M1 .EQ. 0 ) THEN
239234
DO I = 1, N
@@ -251,23 +246,21 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
251246
CALL SGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
252247
$ INCX2 )
253248
*
254-
SCL1 = REALZERO
255-
SSQ1 = REALZERO
256-
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
257-
SCL2 = REALZERO
258-
SSQ2 = REALZERO
259-
CALL SLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
260-
NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
249+
SCL = REALZERO
250+
SSQ = REALZERO
251+
CALL SLASSQ( M1, X1, INCX1, SCL, SSQ )
252+
CALL SLASSQ( M2, X2, INCX2, SCL, SSQ )
253+
NORM_NEW = SCL * SQRT(SSQ)
261254
*
262255
* If projection is sufficiently large in norm, then stop.
263256
* If projection is zero, then stop.
264257
* Otherwise, project again.
265258
*
266-
IF( NORMSQ2 .GE. ALPHASQ*NORMSQ1 ) THEN
259+
IF( NORM_NEW .GE. ALPHA * NORM ) THEN
267260
RETURN
268261
END IF
269262
*
270-
IF( NORMSQ2 .EQ. ZERO ) THEN
263+
IF( NORMSQ2 .LE. N * EPS * NORM ) THEN
271264
DO IX = 1, 1 + (M1-1)*INCX1, INCX1
272265
X1( IX ) = ZERO
273266
END DO
@@ -277,7 +270,7 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
277270
RETURN
278271
END IF
279272
*
280-
NORMSQ1 = NORMSQ2
273+
NORM = NORM_NEW
281274
*
282275
DO I = 1, N
283276
WORK(I) = ZERO
@@ -299,19 +292,17 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
299292
CALL SGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
300293
$ INCX2 )
301294
*
302-
SCL1 = REALZERO
303-
SSQ1 = REALZERO
304-
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
305-
SCL2 = REALZERO
306-
SSQ2 = REALZERO
307-
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
308-
NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
295+
SCL = REALZERO
296+
SSQ = REALZERO
297+
CALL SLASSQ( M1, X1, INCX1, SCL, SSQ )
298+
CALL SLASSQ( M2, X2, INCX2, SCL, SSQ )
299+
NORM_NEW = SCL * SQRT(SSQ)
309300
*
310301
* If second projection is sufficiently large in norm, then do
311302
* nothing more. Alternatively, if it shrunk significantly, then
312303
* truncate it to zero.
313304
*
314-
IF( NORMSQ2 .LT. ALPHASQ*NORMSQ1 ) THEN
305+
IF( NORM_NEW .LT. ALPHA * NORM ) THEN
315306
DO IX = 1, 1 + (M1-1)*INCX1, INCX1
316307
X1(IX) = ZERO
317308
END DO

0 commit comments

Comments
 (0)