Merge pull request #4309 from martin-frbg/lapack926

Change ?GECON to return INFO=1 if RCOND is NaN (Reference-LAPACK PR 926)
This commit is contained in:
Martin Kroeker 2023-11-12 15:28:16 +01:00 committed by GitHub
commit feeb10435b
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 128 additions and 28 deletions

View File

@ -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:
@ -117,7 +124,7 @@
*> \author Univ. of Colorado Denver
*> \author NAG Ltd.
*
*> \ingroup complexGEcomputational
*> \ingroup gecon
*
* =====================================================================
SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
@ -147,7 +154,7 @@
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 ..
@ -172,6 +179,8 @@
CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
* ..
* .. Executable Statements ..
*
HUGEVAL = SLAMCH( 'Overflow' )
*
* Test the input parameters.
*
@ -183,7 +192,7 @@
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
@ -199,6 +208,13 @@
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' )
@ -256,8 +272,17 @@
*
* 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

View File

@ -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:
@ -117,7 +124,7 @@
*> \author Univ. of Colorado Denver
*> \author NAG Ltd.
*
*> \ingroup doubleGEcomputational
*> \ingroup gecon
*
* =====================================================================
SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
@ -147,7 +154,7 @@
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 )
@ -165,6 +172,8 @@
INTRINSIC ABS, MAX
* ..
* .. Executable Statements ..
*
HUGEVAL = DLAMCH( 'Overflow' )
*
* Test the input parameters.
*
@ -176,7 +185,7 @@
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
@ -192,6 +201,13 @@
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' )
@ -248,8 +264,17 @@
*
* 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

View File

@ -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:
@ -117,7 +124,7 @@
*> \author Univ. of Colorado Denver
*> \author NAG Ltd.
*
*> \ingroup realGEcomputational
*> \ingroup gecon
*
* =====================================================================
SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
@ -147,7 +154,7 @@
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 )
@ -165,6 +172,8 @@
INTRINSIC ABS, MAX
* ..
* .. Executable Statements ..
*
HUGEVAL = SLAMCH( 'Overflow' )
*
* Test the input parameters.
*
@ -176,7 +185,7 @@
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
@ -192,6 +201,13 @@
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' )
@ -248,8 +264,17 @@
*
* 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

View File

@ -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:
@ -117,7 +124,7 @@
*> \author Univ. of Colorado Denver
*> \author NAG Ltd.
*
*> \ingroup complex16GEcomputational
*> \ingroup gecon
*
* =====================================================================
SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
@ -147,7 +154,7 @@
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 ..
@ -172,6 +179,8 @@
CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
* ..
* .. Executable Statements ..
*
HUGEVAL = DLAMCH( 'Overflow' )
*
* Test the input parameters.
*
@ -183,7 +192,7 @@
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
@ -199,6 +208,13 @@
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' )
@ -256,8 +272,17 @@
*
* 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