Continue to Site

Eng-Tips is the largest engineering community on the Internet

Intelligent Work Forums for Engineering Professionals

  • Congratulations waross on being selected by the Eng-Tips community for having the most helpful posts in the forums last week. Way to Go!

Validating user input

Status
Not open for further replies.

dozer

Structural
Apr 9, 2001
502
Does anyone have a function similiar to Visual Basic's "IsNumeric" for Fortran? I'm trying to validate input from a dialog box and find the READ statements IOSTAT and ERR kind of klunky.
 
Replies continue below

Recommended for you

Here's a simple little routine that will help you validate real numbers. It is written in Fortran 90/95. You'll want k8 to be equal to 8 for most double precision variables on most PC computers. Make it 4 for single precision on most PC computers. This code is tested and used on software which I've written. If you're using Fortran 77, you'll need to do some alterations. The intent of the code below should be sufficient for you to figure out how to alter it appropriately.

Dan :)


SUBROUTINE Validate_Real_k8 ( StrNum, value, valid )
!***********************************************
! Check to see that a character string represents a valid real number
! Valid real numbers have the following attributes:
!
! They are representable by the fortran compiler used with this code.
! ie. No error is flagged when attempting to use a READ statement on
! the data, <StrNum>.
! They do NOT begin or end with the any of the following letters:
! eEdDqQ
! They do not contain embedded blank characters.
! If <StrNum> is all blanks, that is still considered a valid number.
!
! Input:
! StrNum = Character string which is supposed to represent a valid
! real number. StrNum is not altered by this routine.
! StrNum may be up to 50 character digits (including decimal, etc)
! Output:
! valid = .true. if num is a valid real number or is all spaces.
! = .false. otherwise.
! value = Numeric value from StrNum if valid is .true.
! = 0.0 if the value from StrNum if valid = .false.
! = A variable with a Kind Type of &quot;K8&quot;
! Uses:
! KindTypes = module holding valid kind type parameters
!*************************************************
USE KindTypes
IMPLICIT NONE
Character(*), intent(in) :: StrNum
Real(k8), intent(inout) :: value
Logical, intent(out) :: valid
Character(Len(StrNum)) :: num
Integer :: io
Character(1) :: fd, ld

num = ADJUSTL ( StrNum )
Read ( num, '(F50.0)', iostat=io ) value
IF ( io /= 0 ) THEN
! the entered value is not a valid 'real' number
valid = .false.
value = 0.0
RETURN
END IF

io = Len_Trim ( num )
fd = num(1:1) ! first digit
ld = num(io:io) ! last digit
IF ( fd=='e' .OR. fd== 'E' .OR. ld=='e' .OR. ld== 'E' .OR. &
fd=='d' .OR. fd== 'D' .OR. ld=='d' .OR. ld== 'D' .OR. &
fd=='q' .OR. fd== 'Q' .OR. ld=='q' .OR. ld== 'Q' .OR. &
INDEX(num(1:io),' ') /= 0 ) THEN
! Some compilers will accept a real number starting or ending
! with just a 'd' or an 'e'. I don't consider this a valid entry
! LF95 ver 5.5 does this. Also, LF95,5.0 allows q or Q to be
! used to denote exponentiation just as E and D are used.
valid = .false.
value = 0.0
ELSE
valid = .true.
END IF
END SUBROUTINE Validate_Real_k8
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor