Skip to content

Commit

Permalink
Merge pull request #926 from weslleyspereira/fix-nan-propag-gecon
Browse files Browse the repository at this point in the history
GECON returns 1 if RCOND is NaN
  • Loading branch information
weslleyspereira authored Nov 11, 2023
2 parents 6261d62 + 68eafc6 commit 2382be4
Show file tree
Hide file tree
Showing 4 changed files with 124 additions and 24 deletions.
37 changes: 31 additions & 6 deletions SRC/cgecon.f
Original file line number Diff line number Diff line change
Expand Up @@ -105,8 +105,15 @@
*> \verbatim
*> INFO is INTEGER
*> = 0: successful exit
*> < 0: if INFO = -i, the i-th argument had an illegal value
*> =-5: if ANORM is NAN or negative.
*> < 0: if INFO = -i, the i-th argument had an illegal value.
*> NaNs are illegal values for ANORM, and they propagate to
*> the output parameter RCOND.
*> Infinity is illegal for ANORM, and it propagates to the output
*> parameter RCOND as 0.
*> = 1: if RCOND = NaN, or
*> RCOND = Inf, or
*> the computed norm of the inverse of A is 0.
*> In the latter, RCOND = 0 is returned.
*> \endverbatim
*
* Authors:
Expand Down Expand Up @@ -147,7 +154,7 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
LOGICAL ONENRM
CHARACTER NORMIN
INTEGER IX, KASE, KASE1
REAL AINVNM, SCALE, SL, SMLNUM, SU
REAL AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
COMPLEX ZDUM
* ..
* .. Local Arrays ..
Expand All @@ -172,6 +179,8 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
* ..
* .. Executable Statements ..
*
HUGEVAL = SLAMCH( 'Overflow' )
*
* Test the input parameters.
*
Expand All @@ -183,7 +192,7 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
INFO = -2
ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
INFO = -4
ELSE IF( ANORM.LT.ZERO .OR. SISNAN( ANORM ) ) THEN
ELSE IF( ANORM.LT.ZERO ) THEN
INFO = -5
END IF
IF( INFO.NE.0 ) THEN
Expand All @@ -199,6 +208,13 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
RETURN
ELSE IF( ANORM.EQ.ZERO ) THEN
RETURN
ELSE IF( SISNAN( ANORM ) ) THEN
RCOND = ANORM
INFO = -5
RETURN
ELSE IF( ANORM.GT.HUGEVAL ) THEN
INFO = -5
RETURN
END IF
*
SMLNUM = SLAMCH( 'Safe minimum' )
Expand Down Expand Up @@ -256,8 +272,17 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
*
* Compute the estimate of the reciprocal condition number.
*
IF( AINVNM.NE.ZERO )
$ RCOND = ( ONE / AINVNM ) / ANORM
IF( AINVNM.NE.ZERO ) THEN
RCOND = ( ONE / AINVNM ) / ANORM
ELSE
INFO = 1
RETURN
END IF
*
* Check for NaNs and Infs
*
IF( SISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
$ INFO = 1
*
20 CONTINUE
RETURN
Expand Down
37 changes: 31 additions & 6 deletions SRC/dgecon.f
Original file line number Diff line number Diff line change
Expand Up @@ -105,8 +105,15 @@
*> \verbatim
*> INFO is INTEGER
*> = 0: successful exit
*> < 0: if INFO = -i, the i-th argument had an illegal value
*> =-5: if ANORM is NAN or negative.
*> < 0: if INFO = -i, the i-th argument had an illegal value.
*> NaNs are illegal values for ANORM, and they propagate to
*> the output parameter RCOND.
*> Infinity is illegal for ANORM, and it propagates to the output
*> parameter RCOND as 0.
*> = 1: if RCOND = NaN, or
*> RCOND = Inf, or
*> the computed norm of the inverse of A is 0.
*> In the latter, RCOND = 0 is returned.
*> \endverbatim
*
* Authors:
Expand Down Expand Up @@ -147,7 +154,7 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
LOGICAL ONENRM
CHARACTER NORMIN
INTEGER IX, KASE, KASE1
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
* ..
* .. Local Arrays ..
INTEGER ISAVE( 3 )
Expand All @@ -165,6 +172,8 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
INTRINSIC ABS, MAX
* ..
* .. Executable Statements ..
*
HUGEVAL = DLAMCH( 'Overflow' )
*
* Test the input parameters.
*
Expand All @@ -176,7 +185,7 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
INFO = -2
ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
INFO = -4
ELSE IF( ANORM.LT.ZERO .OR. DISNAN( ANORM ) ) THEN
ELSE IF( ANORM.LT.ZERO ) THEN
INFO = -5
END IF
IF( INFO.NE.0 ) THEN
Expand All @@ -192,6 +201,13 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
RETURN
ELSE IF( ANORM.EQ.ZERO ) THEN
RETURN
ELSE IF( DISNAN( ANORM ) ) THEN
RCOND = ANORM
INFO = -5
RETURN
ELSE IF( ANORM.GT.HUGEVAL ) THEN
INFO = -5
RETURN
END IF
*
SMLNUM = DLAMCH( 'Safe minimum' )
Expand Down Expand Up @@ -248,8 +264,17 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
*
* Compute the estimate of the reciprocal condition number.
*
IF( AINVNM.NE.ZERO )
$ RCOND = ( ONE / AINVNM ) / ANORM
IF( AINVNM.NE.ZERO ) THEN
RCOND = ( ONE / AINVNM ) / ANORM
ELSE
INFO = 1
RETURN
END IF
*
* Check for NaNs and Infs
*
IF( DISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
$ INFO = 1
*
20 CONTINUE
RETURN
Expand Down
37 changes: 31 additions & 6 deletions SRC/sgecon.f
Original file line number Diff line number Diff line change
Expand Up @@ -105,8 +105,15 @@
*> \verbatim
*> INFO is INTEGER
*> = 0: successful exit
*> < 0: if INFO = -i, the i-th argument had an illegal value
*> =-5: if ANORM is NAN or negative.
*> < 0: if INFO = -i, the i-th argument had an illegal value.
*> NaNs are illegal values for ANORM, and they propagate to
*> the output parameter RCOND.
*> Infinity is illegal for ANORM, and it propagates to the output
*> parameter RCOND as 0.
*> = 1: if RCOND = NaN, or
*> RCOND = Inf, or
*> the computed norm of the inverse of A is 0.
*> In the latter, RCOND = 0 is returned.
*> \endverbatim
*
* Authors:
Expand Down Expand Up @@ -147,7 +154,7 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
LOGICAL ONENRM
CHARACTER NORMIN
INTEGER IX, KASE, KASE1
REAL AINVNM, SCALE, SL, SMLNUM, SU
REAL AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
* ..
* .. Local Arrays ..
INTEGER ISAVE( 3 )
Expand All @@ -165,6 +172,8 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
INTRINSIC ABS, MAX
* ..
* .. Executable Statements ..
*
HUGEVAL = SLAMCH( 'Overflow' )
*
* Test the input parameters.
*
Expand All @@ -176,7 +185,7 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
INFO = -2
ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
INFO = -4
ELSE IF( ANORM.LT.ZERO .OR. SISNAN( ANORM ) ) THEN
ELSE IF( ANORM.LT.ZERO ) THEN
INFO = -5
END IF
IF( INFO.NE.0 ) THEN
Expand All @@ -192,6 +201,13 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
RETURN
ELSE IF( ANORM.EQ.ZERO ) THEN
RETURN
ELSE IF( SISNAN( ANORM ) ) THEN
RCOND = ANORM
INFO = -5
RETURN
ELSE IF( ANORM.GT.HUGEVAL ) THEN
INFO = -5
RETURN
END IF
*
SMLNUM = SLAMCH( 'Safe minimum' )
Expand Down Expand Up @@ -248,8 +264,17 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
*
* Compute the estimate of the reciprocal condition number.
*
IF( AINVNM.NE.ZERO )
$ RCOND = ( ONE / AINVNM ) / ANORM
IF( AINVNM.NE.ZERO ) THEN
RCOND = ( ONE / AINVNM ) / ANORM
ELSE
INFO = 1
RETURN
END IF
*
* Check for NaNs and Infs
*
IF( SISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
$ INFO = 1
*
20 CONTINUE
RETURN
Expand Down
37 changes: 31 additions & 6 deletions SRC/zgecon.f
Original file line number Diff line number Diff line change
Expand Up @@ -105,8 +105,15 @@
*> \verbatim
*> INFO is INTEGER
*> = 0: successful exit
*> < 0: if INFO = -i, the i-th argument had an illegal value
*> =-5: if ANORM is NAN or negative.
*> < 0: if INFO = -i, the i-th argument had an illegal value.
*> NaNs are illegal values for ANORM, and they propagate to
*> the output parameter RCOND.
*> Infinity is illegal for ANORM, and it propagates to the output
*> parameter RCOND as 0.
*> = 1: if RCOND = NaN, or
*> RCOND = Inf, or
*> the computed norm of the inverse of A is 0.
*> In the latter, RCOND = 0 is returned.
*> \endverbatim
*
* Authors:
Expand Down Expand Up @@ -147,7 +154,7 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
LOGICAL ONENRM
CHARACTER NORMIN
INTEGER IX, KASE, KASE1
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
COMPLEX*16 ZDUM
* ..
* .. Local Arrays ..
Expand All @@ -172,6 +179,8 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
* ..
* .. Executable Statements ..
*
HUGEVAL = DLAMCH( 'Overflow' )
*
* Test the input parameters.
*
Expand All @@ -183,7 +192,7 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
INFO = -2
ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
INFO = -4
ELSE IF( ANORM.LT.ZERO .OR. DISNAN( ANORM ) ) THEN
ELSE IF( ANORM.LT.ZERO ) THEN
INFO = -5
END IF
IF( INFO.NE.0 ) THEN
Expand All @@ -199,6 +208,13 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
RETURN
ELSE IF( ANORM.EQ.ZERO ) THEN
RETURN
ELSE IF( DISNAN( ANORM ) ) THEN
RCOND = ANORM
INFO = -5
RETURN
ELSE IF( ANORM.GT.HUGEVAL ) THEN
INFO = -5
RETURN
END IF
*
SMLNUM = DLAMCH( 'Safe minimum' )
Expand Down Expand Up @@ -256,8 +272,17 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
*
* Compute the estimate of the reciprocal condition number.
*
IF( AINVNM.NE.ZERO )
$ RCOND = ( ONE / AINVNM ) / ANORM
IF( AINVNM.NE.ZERO ) THEN
RCOND = ( ONE / AINVNM ) / ANORM
ELSE
INFO = 1
RETURN
END IF
*
* Check for NaNs and Infs
*
IF( DISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
$ INFO = 1
*
20 CONTINUE
RETURN
Expand Down

0 comments on commit 2382be4

Please sign in to comment.