Skip to content

Commit 68eafc6

Browse files
Makes NaN an illegal value for ANORM on input of GECON. Let NaNs propagate in the computation of RCOND
1 parent 09abbd0 commit 68eafc6

File tree

4 files changed

+96
-32
lines changed

4 files changed

+96
-32
lines changed

SRC/cgecon.f

Lines changed: 24 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -105,8 +105,15 @@
105105
*> \verbatim
106106
*> INFO is INTEGER
107107
*> = 0: successful exit
108-
*> < 0: if INFO = -i, the i-th argument had an illegal value
109-
*> = 1: RCOND = NaN.
108+
*> < 0: if INFO = -i, the i-th argument had an illegal value.
109+
*> NaNs are illegal values for ANORM, and they propagate to
110+
*> the output parameter RCOND.
111+
*> Infinity is illegal for ANORM, and it propagates to the output
112+
*> parameter RCOND as 0.
113+
*> = 1: if RCOND = NaN, or
114+
*> RCOND = Inf, or
115+
*> the computed norm of the inverse of A is 0.
116+
*> In the latter, RCOND = 0 is returned.
110117
*> \endverbatim
111118
*
112119
* Authors:
@@ -147,7 +154,7 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
147154
LOGICAL ONENRM
148155
CHARACTER NORMIN
149156
INTEGER IX, KASE, KASE1
150-
REAL AINVNM, SCALE, SL, SMLNUM, SU
157+
REAL AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
151158
COMPLEX ZDUM
152159
* ..
153160
* .. Local Arrays ..
@@ -172,6 +179,8 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
172179
CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
173180
* ..
174181
* .. Executable Statements ..
182+
*
183+
HUGEVAL = SLAMCH( 'Overflow' )
175184
*
176185
* Test the input parameters.
177186
*
@@ -201,7 +210,10 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
201210
RETURN
202211
ELSE IF( SISNAN( ANORM ) ) THEN
203212
RCOND = ANORM
204-
INFO = 1
213+
INFO = -5
214+
RETURN
215+
ELSE IF( ANORM.GT.HUGEVAL ) THEN
216+
INFO = -5
205217
RETURN
206218
END IF
207219
*
@@ -260,12 +272,16 @@ SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
260272
*
261273
* Compute the estimate of the reciprocal condition number.
262274
*
263-
IF( AINVNM.NE.ZERO )
264-
$ RCOND = ( ONE / AINVNM ) / ANORM
275+
IF( AINVNM.NE.ZERO ) THEN
276+
RCOND = ( ONE / AINVNM ) / ANORM
277+
ELSE
278+
INFO = 1
279+
RETURN
280+
END IF
265281
*
266-
* Check for NaNs
282+
* Check for NaNs and Infs
267283
*
268-
IF( SISNAN( RCOND ) )
284+
IF( SISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
269285
$ INFO = 1
270286
*
271287
20 CONTINUE

SRC/dgecon.f

Lines changed: 24 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -105,8 +105,15 @@
105105
*> \verbatim
106106
*> INFO is INTEGER
107107
*> = 0: successful exit
108-
*> < 0: if INFO = -i, the i-th argument had an illegal value
109-
*> = 1: RCOND = NaN.
108+
*> < 0: if INFO = -i, the i-th argument had an illegal value.
109+
*> NaNs are illegal values for ANORM, and they propagate to
110+
*> the output parameter RCOND.
111+
*> Infinity is illegal for ANORM, and it propagates to the output
112+
*> parameter RCOND as 0.
113+
*> = 1: if RCOND = NaN, or
114+
*> RCOND = Inf, or
115+
*> the computed norm of the inverse of A is 0.
116+
*> In the latter, RCOND = 0 is returned.
110117
*> \endverbatim
111118
*
112119
* Authors:
@@ -147,7 +154,7 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
147154
LOGICAL ONENRM
148155
CHARACTER NORMIN
149156
INTEGER IX, KASE, KASE1
150-
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU
157+
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
151158
* ..
152159
* .. Local Arrays ..
153160
INTEGER ISAVE( 3 )
@@ -165,6 +172,8 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
165172
INTRINSIC ABS, MAX
166173
* ..
167174
* .. Executable Statements ..
175+
*
176+
HUGEVAL = DLAMCH( 'Overflow' )
168177
*
169178
* Test the input parameters.
170179
*
@@ -194,7 +203,10 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
194203
RETURN
195204
ELSE IF( DISNAN( ANORM ) ) THEN
196205
RCOND = ANORM
197-
INFO = 1
206+
INFO = -5
207+
RETURN
208+
ELSE IF( ANORM.GT.HUGEVAL ) THEN
209+
INFO = -5
198210
RETURN
199211
END IF
200212
*
@@ -252,12 +264,16 @@ SUBROUTINE DGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
252264
*
253265
* Compute the estimate of the reciprocal condition number.
254266
*
255-
IF( AINVNM.NE.ZERO )
256-
$ RCOND = ( ONE / AINVNM ) / ANORM
267+
IF( AINVNM.NE.ZERO ) THEN
268+
RCOND = ( ONE / AINVNM ) / ANORM
269+
ELSE
270+
INFO = 1
271+
RETURN
272+
END IF
257273
*
258-
* Check for NaNs
274+
* Check for NaNs and Infs
259275
*
260-
IF( DISNAN( RCOND ) )
276+
IF( DISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
261277
$ INFO = 1
262278
*
263279
20 CONTINUE

SRC/sgecon.f

Lines changed: 24 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -105,8 +105,15 @@
105105
*> \verbatim
106106
*> INFO is INTEGER
107107
*> = 0: successful exit
108-
*> < 0: if INFO = -i, the i-th argument had an illegal value
109-
*> = 1: RCOND = NaN.
108+
*> < 0: if INFO = -i, the i-th argument had an illegal value.
109+
*> NaNs are illegal values for ANORM, and they propagate to
110+
*> the output parameter RCOND.
111+
*> Infinity is illegal for ANORM, and it propagates to the output
112+
*> parameter RCOND as 0.
113+
*> = 1: if RCOND = NaN, or
114+
*> RCOND = Inf, or
115+
*> the computed norm of the inverse of A is 0.
116+
*> In the latter, RCOND = 0 is returned.
110117
*> \endverbatim
111118
*
112119
* Authors:
@@ -147,7 +154,7 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
147154
LOGICAL ONENRM
148155
CHARACTER NORMIN
149156
INTEGER IX, KASE, KASE1
150-
REAL AINVNM, SCALE, SL, SMLNUM, SU
157+
REAL AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
151158
* ..
152159
* .. Local Arrays ..
153160
INTEGER ISAVE( 3 )
@@ -165,6 +172,8 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
165172
INTRINSIC ABS, MAX
166173
* ..
167174
* .. Executable Statements ..
175+
*
176+
HUGEVAL = SLAMCH( 'Overflow' )
168177
*
169178
* Test the input parameters.
170179
*
@@ -194,7 +203,10 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
194203
RETURN
195204
ELSE IF( SISNAN( ANORM ) ) THEN
196205
RCOND = ANORM
197-
INFO = 1
206+
INFO = -5
207+
RETURN
208+
ELSE IF( ANORM.GT.HUGEVAL ) THEN
209+
INFO = -5
198210
RETURN
199211
END IF
200212
*
@@ -252,12 +264,16 @@ SUBROUTINE SGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, IWORK,
252264
*
253265
* Compute the estimate of the reciprocal condition number.
254266
*
255-
IF( AINVNM.NE.ZERO )
256-
$ RCOND = ( ONE / AINVNM ) / ANORM
267+
IF( AINVNM.NE.ZERO ) THEN
268+
RCOND = ( ONE / AINVNM ) / ANORM
269+
ELSE
270+
INFO = 1
271+
RETURN
272+
END IF
257273
*
258-
* Check for NaNs
274+
* Check for NaNs and Infs
259275
*
260-
IF( SISNAN( RCOND ) )
276+
IF( SISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
261277
$ INFO = 1
262278
*
263279
20 CONTINUE

SRC/zgecon.f

Lines changed: 24 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -105,8 +105,15 @@
105105
*> \verbatim
106106
*> INFO is INTEGER
107107
*> = 0: successful exit
108-
*> < 0: if INFO = -i, the i-th argument had an illegal value
109-
*> = 1: RCOND = NaN.
108+
*> < 0: if INFO = -i, the i-th argument had an illegal value.
109+
*> NaNs are illegal values for ANORM, and they propagate to
110+
*> the output parameter RCOND.
111+
*> Infinity is illegal for ANORM, and it propagates to the output
112+
*> parameter RCOND as 0.
113+
*> = 1: if RCOND = NaN, or
114+
*> RCOND = Inf, or
115+
*> the computed norm of the inverse of A is 0.
116+
*> In the latter, RCOND = 0 is returned.
110117
*> \endverbatim
111118
*
112119
* Authors:
@@ -147,7 +154,7 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
147154
LOGICAL ONENRM
148155
CHARACTER NORMIN
149156
INTEGER IX, KASE, KASE1
150-
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU
157+
DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
151158
COMPLEX*16 ZDUM
152159
* ..
153160
* .. Local Arrays ..
@@ -172,6 +179,8 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
172179
CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
173180
* ..
174181
* .. Executable Statements ..
182+
*
183+
HUGEVAL = DLAMCH( 'Overflow' )
175184
*
176185
* Test the input parameters.
177186
*
@@ -201,7 +210,10 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
201210
RETURN
202211
ELSE IF( DISNAN( ANORM ) ) THEN
203212
RCOND = ANORM
204-
INFO = 1
213+
INFO = -5
214+
RETURN
215+
ELSE IF( ANORM.GT.HUGEVAL ) THEN
216+
INFO = -5
205217
RETURN
206218
END IF
207219
*
@@ -260,12 +272,16 @@ SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
260272
*
261273
* Compute the estimate of the reciprocal condition number.
262274
*
263-
IF( AINVNM.NE.ZERO )
264-
$ RCOND = ( ONE / AINVNM ) / ANORM
275+
IF( AINVNM.NE.ZERO ) THEN
276+
RCOND = ( ONE / AINVNM ) / ANORM
277+
ELSE
278+
INFO = 1
279+
RETURN
280+
END IF
265281
*
266-
* Check for NaNs
282+
* Check for NaNs and Infs
267283
*
268-
IF( DISNAN( RCOND ) )
284+
IF( DISNAN( RCOND ) .OR. RCOND.GT.HUGEVAL )
269285
$ INFO = 1
270286
*
271287
20 CONTINUE

0 commit comments

Comments
 (0)