Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29227 Discussions

Function to determine if a string is numeric

a_leonard
Novice
5,741 Views
I am using the function below to determine whether a string is numeric or character. I have discovered that the string "/" will return true. Does anyone know of any other special cases that might not work as expected?

FUNCTION is_numeric(string)
IMPLICIT NONE
CHARACTER(len=*), INTENT(IN) :: string
LOGICAL :: is_numeric
REAL :: x
INTEGER :: e
READ(string,*,IOSTAT=e) x
is_numeric = e == 0
END FUNCTION is_numeric

I would have thought that the slash would return a negative (end of record) value.

From "Rules for List-Directed Sequential READ Statements":

If a slash ( / ) is encountered during execution, the READ statement is terminated, and any remaining input list items are unchanged.

0 Kudos
17 Replies
jimdempseyatthecove
Honored Contributor III
5,741 Views
Try:

FUNCTION is_numeric(string)
IMPLICIT NONE
CHARACTER(len=*), INTENT(IN) :: string
LOGICAL :: is_numeric
REAL :: x
INTEGER :: e
is_numeric = .false.
READ(string,*,IOSTAT=e, ADVANCE='NO', EOR=999) x
is_numeric = e == 0
999 CONTINUE
END FUNCTION is_numeric

What do you expect for a string containing

'1234 abcd'

Jim Dempsey
0 Kudos
jimdempseyatthecove
Honored Contributor III
5,741 Views
An alternative technique:

FUNCTION is_numeric(string)
USE ieee_arithmetic
IMPLICIT NONE
CHARACTER(len=*), INTENT(IN) :: string
LOGICAL :: is_numeric
REAL :: x
INTEGER :: e
x = FOR_S_NAN
READ(string,*,IOSTAT=e) x
is_numeric = ((e == 0) .and. (.NOT. ISNAN(X)))
END FUNCTION is_numeric

Jim Dempsey
0 Kudos
Steven_L_Intel1
Employee
5,741 Views
Do not use list-directed input (format *) for this. Period. It is much more lenient than you want.

You could use I format if it must be an integer, or Fn.0 (where n is the width of the string) if it can be integer or floating.)
0 Kudos
nvaneck
New Contributor I
5,741 Views

Why not use VERIFY?

0 Kudos
a_leonard
Novice
5,741 Views
It looks like results of my function when compiled with 11.1 are different than when compiled with 11.0. Strings that are definitely not numeric (abc:1&0) are returning TRUE with IVF 11.0.

After taking the good doctor's advice about list-directed format, my function is now:

FUNCTION is_numeric(string)
IMPLICIT NONE
CHARACTER(len=*), INTENT(IN) :: string
LOGICAL :: is_numeric
REAL :: x
INTEGER :: e,n
CHARACTER(len=12) :: fmt

n=LEN_TRIM(string)
WRITE(fmt,'("(F",I0,".0)")') n
READ(string,fmt,IOSTAT=e) x
is_numeric = e == 0
END FUNCTION is_numeric

This seems to work fine until it got the string "d1", which it seems to have converted as if it were "0.0D1", which is not what I want.

The following should be recognized as numeric:

1
1.0
1.0e0

The following should be recognized as strings

1A
d1

0 Kudos
Steven_L_Intel1
Employee
5,741 Views
Yes, we tightened list-directed input some, including strings that started with D, E or Q, but you can still get into trouble, for example, commas, slashes, 3*4, etc. I'll say it again - DO NOT USE LIST-DIRECTED INPUT FOR VALIDATION. If I had a nickel for every time someone ran into trouble doing this I could retire now.
0 Kudos
John_B__Walter
Beginner
5,741 Views
Also, the value 1d1 is 10.0, a valid numeric value, so if you want that rejected, your going to have to do more.

another comment, you can simplify

n=LEN_TRIM(string)
WRITE(fmt,'("(F",I0,".0)")') n
READ(string,fmt,IOSTAT=e) x

replacing it with

n=LEN_TRIM(string)
READ(string, '(F.0)', IOSTAT=e) x

A question for Steve: while playing with this a little I did a read(*, '(q,A80)') to a character (len=20) variable, and while the length variable was properly filled with the number of characters typed, they were not read into the shorter character variable, it was blanked. So is this proper behavior per the FORTRAN standard, or is it a bug?

0 Kudos
a_leonard
Novice
5,741 Views
This is standard Fortran?

READ(string, '(F.0)', IOSTAT=e) x
0 Kudos
Steven_L_Intel1
Employee
5,741 Views
John,

That behavior (the shorter variable being blank) is specified by the standard. What happens is that the field width is 80 (you said A80) Since the field width (80) is greater than the width of the variable (20), the rightmost 20 characters of the input field is used. Assuming you typed in fewer than 60 characters, that means that the variable will be assigned blanks.

To correct this, just use A rather than A80.
0 Kudos
Steven_L_Intel1
Employee
5,741 Views
Quoting a.leonard
This is standard Fortran?

READ(string, '(F.0)', IOSTAT=e) x

No. That's a DEC extension called Variable Format Expression.

0 Kudos
a_leonard
Novice
5,741 Views
Also, the value 1d1 is 10.0, a valid numeric value, so if you want that rejected, your going to have to do more.

I'm OK with "1E1", "1D1", or even "1Q1" as a number (10.0), but I'm going to say that any string starting with a letter - including E, D, and Q - is not a number, even if the I/O conversion works.

I also don't want to have "+" and "-" be considered numbers because it will completly mess up some logic to parse equations.

I have added logic to check for these "special" situations. There are some others ("1 2 3" is read as 123.0) that look a bit odd to me, but I won't worry about it.

0 Kudos
John_B__Walter
Beginner
5,741 Views
It doesn't look like you're going to find some magic solution.

What you need is entirely dependent on what exactly you have to deal with. For instance, what do you want it to do with embeded spaces?

It begins to look like you might be as well off to examine the string character by character, looping over the position in the string from 1 to the length of the string. If you initiallized is_numeric=.FALSE. before the loop, as soon as you found something that defined the string as not a numeric value you could exit from the loop and return from the function. If you completed the loop without finding a problem you'd set is_numeric=.TRUE. before returning from the function.
0 Kudos
Steven_L_Intel1
Employee
5,741 Views
An internal read with a format of (BN,Fn.0) where n is the width of the string, should do for most purposes. This will ignore embedded blanks, however.
0 Kudos
nvaneck
New Contributor I
5,741 Views

Use

numeric=verify(string(verify(string,' '):),'0123456789') .eq.0

Or just convert it...

k=iconv8(string,ierr)

INTEGER(8) FUNCTION ICONV8(STRING,IERR)

INTEGER(4) I,J,L

CHARACTER STRING*(*)

LOGICAL IERR,NEG

INTEGER(4),PARAMETER :: MINUS=-3,PLUS=-5,BLANK=-16

ICONV8=0

NEG = .FALSE.

IERR = .FALSE.

L=LEN(STRING)

DO I=1,L

J=ICHAR(STRING(I:I))-48

IF (J .GE. 0 .AND. J .LT. 10) THEN

ICONV8=ICONV8*10+J

ELSEIF (J .EQ. MINUS .AND. ICONV8 .EQ. 0D0 .AND. I.NE.L) THEN

NEG = .TRUE.

ELSEIF (I.EQ.L .OR. ICONV8.GT.0 .OR. (J.NE.BLANK.AND.J.NE.PLUS)) THEN

IERR = .TRUE.

RETURN

ENDIF

END DO

IF (NEG) ICONV8 = -ICONV8

END

0 Kudos
WSinc
New Contributor I
5,741 Views
I used ICHAR (intrinsic function) to determine if a particular character is a numeric.

Numerals 0 to 9 have the range 32 to 41, I believe. 0 -->32, 9 -->41, etc.


Anything outside that range is Non-numeric.
By "numeric" did you mean the decimal point, plus and minus signs as well?

So, just scan that string, and check for values inside or outside that range.
Of course, you have read the string into memory first.

Yours; Bill
0 Kudos
John_B__Walter
Beginner
5,741 Views
Quoting a.leonard
I'm OK with "1E1", "1D1", or even "1Q1" as a number (10.0), but I'm going to say that any string starting with a letter - including E, D, and Q - is not a number, even if the I/O conversion works.

I also don't want to have "+" and "-" be considered numbers because it will completly mess up some logic to parse equations.

I have added logic to check for these "special" situations. There are some others ("1 2 3" is read as 123.0) that look a bit odd to me, but I won't worry about it.

you can, of course, check for embedded spaces with the intrinsic function scan. something like
integer I, J, N
I = verify(string,' ') ! location of first non-space
N = len_trim(string) ! location of last non-space, equivalent to verify(string,' ',back=.true.)
J = scan(string(I:N),' ') ! check relevant portion of string for any embedded strings
! J == 0 if there are no embedded spaces

Of course if the embedded spaces are meaningless, and you want "1 2 3" to be read as "123", then your current read accomplishes that. Your original list directed read would have read it as "1", ignoring everything after the space, or more precisely reading them into subsequent variables if any were present.

But so that Steve doesn't have to say it this time, DON'T USE LIST DIRECTED, the convenience is really not worth the pitfalls that await you, unless you really have nothing better to do than discover errors in your program long after you thought you were done developing it.
0 Kudos
nvaneck
New Contributor I
5,741 Views
It's easy enough to write a routine similar to the one I listed in a prior response for integers which handles decimal points and exponential notation. I have one if you're interested.
0 Kudos
Reply