[comp.lang.fortran] Checking a string for an integer

dsroberts@biivax.dp.beckman.com (04/02/91)

I would like to take a 3 byte string and find out if it contains only ascii
digits for number or if letters were entered.  On VMS, the DCL command would be

result = f$integer (string)

which would put the numeric equivalent in result, or return an error.  I don't
find an obvious way to do this in FORTRAN.  Any suggestions?  I am not averse
to a VMS system service, btw.

And, just in case I am missing some better alternative, what I am trying to
accomplish is to find out if this 3 byte string contains a number in a valid
range (in this case 1-254) or not.  The only requirement is that I start with a
3-byte string.  Pointers to the appropriate pages in the VMS FORTRAN manuals
would be appreciated :-)
-- 
---------------------------------------------------------------------------
   Don Roberts                   Internet:  dsroberts@beckman.com
   Beckman Instruments, Inc.     Yellnet:   714/961-3029
   2500 Harbor Bl. Mailstop X-12 FAX:       714/961-3351
   Fullerton, CA  92634          Disclaimer:  Always
---------------------------------------------------------------------------

8099pierzina@vmsd.csd.mu.edu (Todd Pierzina) (04/02/91)

In article <1991Apr1.104227.243@biivax.dp.beckman.com>, dsroberts@biivax.dp.beckman.com writes:
>I would like to take a 3 byte string and find out if it contains only ascii
>digits for number or if letters were entered.  On VMS, the DCL command would be
>result = f$integer (string)
>which would put the numeric equivalent in result, or return an error.  I don't
>find an obvious way to do this in FORTRAN...
>And, just in case I am missing some better alternative, what I am trying to
>accomplish is to find out if this 3 byte string contains a number in a valid
>range (in this case 1-254) or not.  The only requirement is that I start with a
>3-byte string... 

    character String*3
    integer i, iostat

    ...

    read (String, '(I3)', err=1000, iostat=iostat) i
    if ((1 .lt. 1) .or. (i .gt. 254)) then goto 1010

1000	[not numeric error handler]
1010	[out of range error handler]

Todd Pierzina                 8099pierzina@vms.csd.mu.edu
Student Programmer            robertf@marque.mu.edu
Marquette University          todd@studsys.mu.edu
[Looking through old issues of Readers' Digest for a cute saying]

jerry@heyman.austin.ibm.com (Jerry Heyman) (04/02/91)

In article <1991Apr1.104227.243@biivax.dp.beckman.com> dsroberts@biivax.dp.beckman.com writes:
>I would like to take a 3 byte string and find out if it contains only ascii
>digits for number or if letters were entered.  On VMS, the DCL command would be
>
>result = f$integer (string)
>

You could always use an internal READ statement.  You would also have to
specifiy an error state on the READ to handle alphabetic input when its not
expected.

Something like:

      READ (string, 'I3', error=xxx) result

where xxx is a line number where the code should branch to if an error occurs.
Its been a while since I tried this, so the syntax might be a little rough, but
you get the general idea.

jerry
-- 
Jerry Heyman                         Internet : jerry@ajones.austin.ibm.com
PSP Development Environment Tools    VNET     : HEYMAN at AUSTIN
Austin, TX  78758                    IBM T-R  : jerry@heyman.austin.ibm.com
*** All opinions expressed are exactly that - my opinions and NOT IBM's

ereiamjh@jhunix.HCF.JHU.EDU (Tom B. O'Toole) (04/02/91)

In article <1991Apr1.104227.243@biivax.dp.beckman.com> dsroberts@biivax.dp.beckman.com writes:
>I would like to take a 3 byte string and find out if it contains only ascii
>digits for number or if letters were entered.  On VMS, the DCL command would be
>
>result = f$integer (string)
>
It's very easy to do. You basically do something like:
	character*3 string
...
	read(string,*,err=99)input
...
99	WRITE(6,*) 'a non integer string representation'

This is an 'internal' read, and is a lot more intuitive than the old
encode/decode statements. You replace the unit number with 
a character variable.  Documentation is in the chapter on 
input/output statments. Note: old versions
of the VMS fortran runtime system would not let you use an implicit format
specifier, you would have had to use I3 or similar. I'm not sure when this was
fixed. 
-- 
Tom O'Toole - ecf_stbo@jhuvms.bitnet - JHUVMS system programmer 
Homewood Computing Facilities, Johns Hopkins University, Balto. Md. 21218 
ease!Trim!eeeaaaassse!trimtrimtrimeeeeeeaaaaassetrimease!trim!ease!trimeaase

KENCB@SLACVM.SLAC.STANFORD.EDU (04/02/91)

In article <1991Apr1.104227.243@biivax.dp.beckman.com>,
dsroberts@biivax.dp.beckman.com says:
>
>I would like to take a 3 byte string and find out if it contains only ascii
>digits for number or if letters were entered.  On VMS, the DCL command would
>be
>
>result = f$integer (string)
>
>which would put the numeric equivalent in result, or return an error.  I don't
>find an obvious way to do this in FORTRAN.  Any suggestions?  I am not averse
>to a VMS system service, btw.
>

    How about using the OTS$CVT_TI_L system service.  OTS will return
a FALSE status if it can't convert the text string.   Sample code:

        INTEGER*4   IVAL, OTS$CVT_TI_L
        CHARACTER*3 CVAL
          .
          .
        READ (5,*) CVAL
        IF (OTS$CVT_TI_L (CVAL, IVAL, %VAL(4), %VAL('11'X))) THEN
          IF (IVAL.GE.1 .AND. IVAL.LE.254) THEN
            .
            .
          ELSE
            .
          ENDIF
        ELSE
          .
        ENDIF


Do a $HELP RTL OTS$ OTS$CVT_TI_L for details on the 3rd and 4th arguments.

                     Ken

 Dr. Kenneth H. Fairfield        Internet: Fairfield@Tpc.Slac.Stanford.Edu
 SLAC, P.O.Box 4349, Bin 98      DECnet:   45047::FAIRFIELD (TPC::)
 Stanford, CA   94309            BITNET    Fairfield@SlacTpc
 "These opinions are worth what you paid for 'em...
         ...and they are mine, not SLAC's, Stanford's, nor the DOE's..."

gpwrmdh@gp.co.nz (04/02/91)

In article <1991Apr1.104227.243@biivax.dp.beckman.com>, dsroberts@biivax.dp.beckman.com writes:
> I would like to take a 3 byte string and find out if it contains only ascii
> digits for number or if letters were entered.  On VMS, the DCL command would be
> 
> result = f$integer (string)
> 
> which would put the numeric equivalent in result, or return an error.  I don't
> find an obvious way to do this in FORTRAN.  Any suggestions?  I am not averse
> to a VMS system service, btw.

Here is a simple example program:

	program test
	implicit none
	
	character*3 in
	integer out, status

	write (*, fmt='(''$number: '')')

	read (*, fmt='(a3)') in
	read (unit=in, fmt='(i3)', iostat=status) out

	if (status .eq. 0) then
	    type *, 'Converted ok'
	    type *, 'Number = ', out
	    type *, 'Returned status = ', status
	    if (out .gt. 254) type *, 'Number too big'
	else
	    type *, 'Error converting number'
	    type *, 'Status = ', status
	end if

	end

Basically, you use the READ statement to convert the string to internal 
format, and check the returned status - success returns a 0. You will 
probably want more error checking than I have put in the above.

The error code returned for invalid numbers is code 64, meaning "input 
conversion error".

> 
> And, just in case I am missing some better alternative, what I am trying to
> accomplish is to find out if this 3 byte string contains a number in a valid
> range (in this case 1-254) or not.  The only requirement is that I start with a
> 3-byte string.  Pointers to the appropriate pages in the VMS FORTRAN manuals
> would be appreciated :-)

Section 4.2.3.2 of the Fortran User's manual (V5.0) has a little about
internal i/o, and also section 7.2.4 of the Fortran Reference Manual.

> -- 
> ---------------------------------------------------------------------------
>    Don Roberts                   Internet:  dsroberts@beckman.com
>    Beckman Instruments, Inc.     Yellnet:   714/961-3029
>    2500 Harbor Bl. Mailstop X-12 FAX:       714/961-3351
>    Fullerton, CA  92634          Disclaimer:  Always
> ---------------------------------------------------------------------------
-- 
----------------------------------------------------------------------------
Martin D. Hunt			
GP Print Limited		USEnet address : martinh@gp.co.nz
Wellington			PSI address    : PSI%0530147000028::martinh
New Zealand			Phone	       : +64 4 4965790
-----------------------------------------------------------------------------

mparisi@ripple.jpl.nasa.gov (Mark Parisi) (04/02/91)

In article <009467BE.E4367B40@vmsd.csd.mu.edu>,
8099pierzina@vmsd.csd.mu.edu (Todd Pierzina) writes:
|>    read (String, '(I3)', err=1000, iostat=iostat) i

This doesn't work quite as well as you might think.

In VMS Fortran, this will pass anything which resembles a valid 
real or integer format, including:

	"1E2"
	"D  "
	"Q  "

If you are really worried about checking for valid input, you are 
best off checking that each character in the string is between
"0" and "9".  (You will probably want to allow blanks in some 
places, this will complicate things.)

The intrinsic function INDEX is useful for performing this 
check:

	CHARACTER*(*) DIGITS
	PARAMETER (DIGITS = '0123456789')

	INTEGER I
	LOGICAL VALID
	...

	VALID = .TRUE.
	DO 10 I = 1, LEN(STR)
	   IF INDEX(DIGITS, STR(I:I) .EQ. 0) VALID = .FALSE.
10	CONTINUE

... you get the idea.

		-- Mark Parisi (mparisi@ripple.jpl.nasa.gov)

ags@seaman.cc.purdue.edu (Dave Seaman) (04/02/91)

In article <7875@jhunix.HCF.JHU.EDU> ereiamjh@jhunix.HCF.JHU.EDU (Tom B. O'Toole) writes:

>It's very easy to do. You basically do something like:
>	character*3 string
>...
>	read(string,*,err=99)input
>...
>99	WRITE(6,*) 'a non integer string representation'

It's not quite as easy as that, because Fortran 77 does not allow list-directed
I/O on internal files.  Therefore, you need to use an actual format in the
read statement.

--
Dave Seaman
ags@seaman.cc.purdue.edu

Ross Taylor <taylor@sun.soe.clarkson.edu> (04/02/91)

Here's my contribution to this discussion: two routines for converting
strings of any length to integers or real numbers.  there are no
read statements and as far as I know the code is completely standard
F77.

Ross Taylor
Department of Chemical Engineering
Clarkson University
Potsdam, NY 13699 (yes, we have our own zip code)

taylor@sun.soe.clarkson.edu

C     *******************************************************************
C     *                                                                 *
C     *    SUBROUTINE CHRTOI                                            *
C     *                                                                 *
C     *******************************************************************
C
      SUBROUTINE CHRTOI (INT, STRING, IERR)
C
C     Function
C     --------
C
C        To return an integer stored as a character string
C
C     Arguments
C     ---------
C
C        INT     - The integer in numeric form (output)
C        STRING  - The character string (input)
C        IERR    - Error flag set to 1 if non-numeric character found
C
C     Remarks
C     -------
C
C        Code written by ross taylor, delft, march 7, 1988
C        Inspired by code written by malcolm woodman
C
      CHARACTER*(*) STRING
C
C     Initialize integer
C
      INT  = 0
      IERR = 0
C
C     Determine length of character string
C
      LENGTH = LEN(STRING)
C
C     Check for sign in position 1
C
      L1 = 1
      IF (STRING(1:1) .EQ. '-' .OR. STRING(1:1) .EQ. '+') L1 = 2
      L2 = LENGTH + L1
C
      DO 1 I = L1, LENGTH
C
         K = L2 - I
C
C     Starting from the last character
C     Convert to integer (ichar returns ascii code) (0 = 48; 9 = 57)
C
         KK = ICHAR (STRING(K:K)) - 48
C
C     Check for non-numeric characters
C
         IF (KK .LT. 0 .OR. KK .GT. 9) THEN
            INT  = 0
            IERR = 1
            RETURN
         ENDIF
C
C     Add current contribution to int
C
         INT = INT + KK * 10 ** (I-L1)
C
    1 CONTINUE
C
      IF (STRING(1:1) .EQ. '-') INT = - INT
C
      RETURN
      END
C
C     *******************************************************************
C     *                                                                 *
C     *    subroutine chrtor                                            *
C     *                                                                 *
C     *******************************************************************
C
      SUBROUTINE CHRTOR (REAL, STRING, IERR)
C
C     Function
C     --------
C
C        To return a real number stored as a character string
C
C     Arguments
C     ---------
C
C        REAL    - The number in numeric form    (output)
C        STRING  - The character string          (input)
C        IERR    - Error flag set to 1 if non-numeric character found
C
C     Remarks
C     -------
C
C        This subroutine works by breaking up the input character string
C        Into three segments: the integer part, the decimal part and the
C        Exponent.  subroutine chrtoi is used to convert all three
C        Character strings to intgers and the results combined to give the
C        Real number output
C
C        This code written by ross taylor, delft, march 8, 1988
C        Inspired by code written by malcolm woodman
C
C     Notation
C     --------
C
C        INT    - The value of the integer contribution
C        IEXP   - The exponent
C        IDEC   - The decimal contribution
C        IERR   - Error flag set to unity if non-numeric character found
C        ISTART - Location in string of first character of current part
C
C         The following character strings all give the same result
C
C         10   10.  10.0   10.d0   10d0  1d1       =       10.0
C
C
      IMPLICIT DOUBLE PRECISION (A-H, O-Z)
C
      CHARACTER*(*) STRING
C
C     Initialize various items
C
      INT    = 0
      IDEC   = 0
      IEXP   = 0
      IERR   = 0
      ISTART = 1
      REAL   = 0.D0
C
C     Determine length of input character string
C
      LENGTH = LEN(STRING)
C
C     Look for decimal point to mark end of integer part
C
      IPOINT = INDEX(STRING,'.')
C
C     Look for 'd' or 'e' to mark exponent
C
      IPEXP = INDEX(STRING,'D')
C
      IF (IPEXP .EQ. 0) IPEXP = INDEX(STRING,'E')
      IF (IPEXP .EQ. 0) IPEXP = INDEX(STRING,'d')
      IF (IPEXP .EQ. 0) IPEXP = INDEX(STRING,'e')
C
C     Convert character string to integer
C
      IF (IPOINT .NE. 0) THEN
         CALL CHRTOI (INT, STRING(ISTART:IPOINT-1), IERR)
      ELSE IF (IPEXP .NE. 0) THEN
         CALL CHRTOI (INT, STRING(ISTART:IPEXP-1), IERR)
      ELSE
         CALL CHRTOI (INT, STRING(ISTART:LENGTH), IERR)
      ENDIF
C
      IF (IERR .NE. 0) THEN
          REAL = 0.D0
          RETURN
      ENDIF
C
      REAL = DBLE(INT)
C
C     Next, the decimal part of the result
C
      IF (IPOINT .NE. 0) THEN
C
         ISTART = IPOINT + 1
C
C     Determine length of decimal part
C
         IF (IPEXP .GT. IPOINT) THEN
            LENDEC = IPEXP - IPOINT
         ELSE
            LENDEC = LENGTH - IPOINT
         ENDIF
C
C     Convert character string to integer
C
         IF (LENDEC .GT. 0) THEN
            CALL CHRTOI (IDEC,STRING(ISTART:ISTART+LENDEC-1),IERR)
         ENDIF
C
         IF (IERR .NE. 0) THEN
             DEC = 0.D0
         ENDIF
C
         DEC = DBLE(IDEC) / 10.0 ** LENDEC
C
         IF (STRING(1:1) .EQ. '-') THEN
            REAL = REAL - DEC
         ELSE
            REAL = REAL + DEC
         ENDIF
C
      ENDIF
C
C     Finally, the exponent (if present)
C
      IF (IPEXP .GT. 0) THEN
C
         ISTART = IPEXP + 1
C
C     Convert character string to integer
C
         CALL CHRTOI (IEXP,STRING(ISTART:LENGTH),IERR)
C
         IF (IERR .NE. 0) THEN
            IEXP = 0
            RETURN
         ENDIF
C
         REAL = REAL * 10.D0 ** IEXP
C
      ENDIF
C
      RETURN
      END

dsroberts@biivax.dp.beckman.com (04/02/91)

Many thanks to the legion who responded to my posting.  To summarize, the two
most useful (for my purposes) suggestions:

- Use LIB$CVT_DTB (a VMS RTL service) I received two responses with this
- Use Internal READ (with format (BN,I3) so I can have left justification)
  I think I must have received 1000 responses with this. 

The library routine is a little better for my uses.  Now, can you PLEASE stop
responding ? :-)
-- 
---------------------------------------------------------------------------
   Don Roberts                   Internet:  dsroberts@beckman.com
   Beckman Instruments, Inc.     Yellnet:   714/961-3029
   2500 Harbor Bl. Mailstop X-12 FAX:       714/961-3351
   Fullerton, CA  92634          Disclaimer:  Always
---------------------------------------------------------------------------