Validating user input
Validating user input
(OP)
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.
INTELLIGENT WORK FORUMS
FOR ENGINEERING PROFESSIONALS Contact USThanks. We have received your request and will respond promptly. Come Join Us!Are you an
Engineering professional? Join Eng-Tips Forums!
*Eng-Tips's functionality depends on members receiving e-mail. By joining you are opting in to receive e-mail. Posting Guidelines |
|
Join your peers on the Internet's largest technical engineering professional community.
It's easy to join and it's free.
Here's Why Members Love Eng-Tips Forums:
Register now while it's still free!
Already a member? Close this window and log in.
RE: Validating user input
Dan
www.dtware.com
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 "K8"
! 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