Skip to content

Commit

Permalink
SORBDB6: improve numerical stability
Browse files Browse the repository at this point in the history
* 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
  • Loading branch information
christoph-conrads committed Jan 30, 2022
1 parent cf2b28f commit 8ea160d
Showing 1 changed file with 30 additions and 39 deletions.
69 changes: 30 additions & 39 deletions SRC/sorbdb6.f
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,9 @@
*> with respect to the columns of
*> Q = [ Q1 ] .
*> [ Q2 ]
*> The columns of Q must be orthonormal. The orthogonalized vector will
*> be zero if and only if it lies entirely in the range of Q.
*> The Euclidean norm of X must be one and the columns of Q must be
*> orthonormal. The orthogonalized vector will be zero if and only if it
*> lies entirely in the range of Q.
*>
*> The projection is computed with at most two iterations of the
*> classical Gram-Schmidt algorithm, see
Expand Down Expand Up @@ -172,14 +173,17 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
* =====================================================================
*
* .. Parameters ..
REAL ALPHASQ, REALZERO
PARAMETER ( ALPHASQ = 0.01E0, REALZERO = 0.0E0 )
REAL ALPHA, REALZERO
PARAMETER ( ALPHA = 0.1E0, REALZERO = 0.0E0 )
REAL NEGONE, ONE, ZERO
PARAMETER ( NEGONE = -1.0E0, ONE = 1.0E0, ZERO = 0.0E0 )
* ..
* .. Local Scalars ..
INTEGER I, IX
REAL NORMSQ1, NORMSQ2, SCL1, SCL2, SSQ1, SSQ2
REAL EPS, NORM, NORM_NEW, SCL, SSQ
* ..
* .. External Functions ..
REAL SLAMCH
* ..
* .. External Subroutines ..
EXTERNAL SGEMV, SLASSQ, XERBLA
Expand Down Expand Up @@ -214,26 +218,17 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
CALL XERBLA( 'SORBDB6', -INFO )
RETURN
END IF
*
EPS = SLAMCH( 'Precision' )
*
* First, project X onto the orthogonal complement of Q's column
* space
*
SCL1 = REALZERO
SSQ1 = REALZERO
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
SCL2 = REALZERO
SSQ2 = REALZERO
CALL SLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
NORMSQ1 = SCL1**2*SSQ1 + SCL2**2*SSQ2
IF ( NORMSQ1 .EQ. 0 ) THEN
DO IX = 1, 1 + (M1-1)*INCX1, INCX1
X1( IX ) = ZERO
END DO
DO IX = 1, 1 + (M2-1)*INCX2, INCX2
X2( IX ) = ZERO
END DO
RETURN
END IF
* Christoph Conrads: In debugging mode the norm should be computed
* and an assertion added comparing the norm with one. Alas, Fortran
* never made it into 1989 when assert() was introduced into the C
* programming language.
NORM = 1.0E0
*
IF( M1 .EQ. 0 ) THEN
DO I = 1, N
Expand All @@ -251,23 +246,21 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
CALL SGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
$ INCX2 )
*
SCL1 = REALZERO
SSQ1 = REALZERO
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
SCL2 = REALZERO
SSQ2 = REALZERO
CALL SLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
SCL = REALZERO
SSQ = REALZERO
CALL SLASSQ( M1, X1, INCX1, SCL, SSQ )
CALL SLASSQ( M2, X2, INCX2, SCL, SSQ )
NORM_NEW = SCL * SQRT(SSQ)
*
* If projection is sufficiently large in norm, then stop.
* If projection is zero, then stop.
* Otherwise, project again.
*
IF( NORMSQ2 .GE. ALPHASQ*NORMSQ1 ) THEN
IF( NORM_NEW .GE. ALPHA * NORM ) THEN
RETURN
END IF
*
IF( NORMSQ2 .EQ. ZERO ) THEN
IF( NORMSQ2 .LE. N * EPS * NORM ) THEN
DO IX = 1, 1 + (M1-1)*INCX1, INCX1
X1( IX ) = ZERO
END DO
Expand All @@ -277,7 +270,7 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
RETURN
END IF
*
NORMSQ1 = NORMSQ2
NORM = NORM_NEW
*
DO I = 1, N
WORK(I) = ZERO
Expand All @@ -299,19 +292,17 @@ SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
CALL SGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
$ INCX2 )
*
SCL1 = REALZERO
SSQ1 = REALZERO
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
SCL2 = REALZERO
SSQ2 = REALZERO
CALL SLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
SCL = REALZERO
SSQ = REALZERO
CALL SLASSQ( M1, X1, INCX1, SCL, SSQ )
CALL SLASSQ( M2, X2, INCX2, SCL, SSQ )
NORM_NEW = SCL * SQRT(SSQ)
*
* If second projection is sufficiently large in norm, then do
* nothing more. Alternatively, if it shrunk significantly, then
* truncate it to zero.
*
IF( NORMSQ2 .LT. ALPHASQ*NORMSQ1 ) THEN
IF( NORM_NEW .LT. ALPHA * NORM ) THEN
DO IX = 1, 1 + (M1-1)*INCX1, INCX1
X1(IX) = ZERO
END DO
Expand Down

0 comments on commit 8ea160d

Please sign in to comment.