M_calculator

NAME

M_calculator(3fm) - [M_calculator::INTRO] module of routines for parsing expressions and returning values

SYNOPSIS

    use M_calculator, only : calculator
    ! convenience routines
    use M_calculator, only : expression
    use M_calculator, only : inum0, rnum0, dnum0, snum0

DESCRIPTION

The M_calculator module and related functions evaluate CHARACTER strings containing FORTRAN-like expressions and returns numeric and string values.

Using this interface it is easy to make free-format and order-independent input interfaces where values can be expressions and variable names instead of simple formatted numbers.

The primary routine CALCULATOR(3f) acts like a powerful desk-top calculator. It supports named variables and has several arrays (of 55555 elements each). Many standard FORTRAN functions are available, plus access to user-written functions is permitted via user-supplied routines via set_mysub(3f) and set_myfunc(3f).

The programmer (generally) uses just the CALCULATOR(3f) routine or several convenience routines (INUM0,RNUM0,SNUM0,,EXPRESSION) that simplify making the most common type of calls to CALCULATOR(3f).

PROCEDURES

CONSTANTS

The variables used to hold the X,Y,$X,$Y, … arrays and the dictionaries of variable names and string names and their associated values:

   ! max length of expression or variable value as a string
   integer,parameter,public :: iclen_calc=512
   ! number of variables in X() and Y() array
   integer,parameter,public :: ixy_calc=55555
   ! max length of a variable name
   integer,parameter,public :: icname_calc=20
   ! x array for procedure funcs_
   real(kind=dp),save,public :: x(ixy_calc)=0.0_dp
   ! y array for procedure funcs_
   real(kind=dp),save,public :: y(ixy_calc)=0.0_dp
   !  lengths of the string variable values
   integer,save,public,allocatable :: values_len(:)
   !  string variable values
   character(len=:),save,public,allocatable :: values(:)

USAGE

Calculator Expressions

The calculator interface allows input values to be numeric or string expressions using Fortran-like syntax instead of just simple variables.

Named variables may be created. Several arrays of 55555 elements each exist. The majority of FORTRAN intrinsic functions are available, Custom routines may be made available for each application using the interface.

A summary of the syntax rules for the expressions :

Each of the types will be discussed separately.

VARIABLE NAMES

Names must be 1 to 20 characters long, and are case-sensitive. The numbr of names permitted is only limited by the available memory. Numeric variable names should be composed of the letters a-z and underscores and numbers. String variables are similar but start with a dollar sign($). Names must not end in a “digit-E” combination. For example:

       A=sin(3.1416/2)
       big=200.333E200
       $name="Thomas Jefferson"

Variables may be defined by equating them to an expression. To define or redefine a variable called FRED, simply enter:

       FRED=300*4/500

The last value assigned to a variable will be used to evaluate the expression on the left of the equals sign when this expression redefines the variable. For example:

       A=2
       > 2
       A
       > 2
       A=A+A
       > 4
       A=A+A
       > 8

To allow FORTRAN-type E-format numeric entry and yet not cause the calculator routine to do an excessive amount of checking, a variable name ending in the letter E must not have a digit (012345789) in front of that ending E. Attempting to define such a variable name will produce an error. This limitation prevents the calculator from becoming confused by whether 12E+3 is a variable called 12E plus 3 or the exponential number 12E3=12000.

CURRENT VALUE

The variable name ‘?’ is automatically set by the program to contain the last calculated value. This current-value register may be used like any variable or number. It is 0 at program initialization. Example:

      300+500)
      > 800
      1/4)*?
      > 200
      +?
      > 400

THE X AND Y ARRAYS

Two arrays called X and Y are available that can contain up to 55555 values each. The arrays are originally initialized to all zeros. To set values in the arrays, use the xstore (or ystore) command. The format of the commands is

       xstore(start,ex1,ex2,ex3)
       ystore(start,ex1,ex2,ex3)

where start=array address to start storing at and ex(i) are expressions.

The current value is assigned the last value stored. In addition there are similar string arrays and functions that can hold up to 50 255-character strings:

     xstore( 10 , 1/10 , 2/20 , 3/10 )
        ^
        !
        *-------Start storing evaluated expressions sequentially,
                beginning at x(10).

REFERENCING AN ARRAY VALUE

The values stored into the arrays may be referenced by subscript. For example:

     xstore(1,10,20,30)
     > 30
     fred=x(1)+x(2)+x(3)
     > 60

NOTES:

  1. x and y array values cannot be used on the left of equal signs.
       x(10)=5   #  IS ILLEGAL
    
  2. The current value is set to the value of the last expression by the xstore and ystore commands

INTRINSICS

supported Fortran intrinsics

The majority of intrinsic Fortran numeric functions are available. At a minimum the following are recognized (Deviations of the calculator routines from the standard intrinsics are noted):

Arc or anti-trigonometric functions
Trigonometric functions
Hyperbolic trigonometric functions
Powers and logarithms
Maximum/Minimum
Directly effecting sign of value
Converting to a whole number
Bessel functions
Miscellaneous
Error function

ADDITIONAL PROCEDURES

In addition to standard Fortran intrinsics, many other functions are supported …

conversion functions
logical functions

For example:

     a=if(ge(b,c),a,d)

means return a if b is greater than or equal to c else return d.

lexical logical functions
miscellaneous functions
Random numbers

MISCELLANEOUS COMMANDS

Displaying variable values: dump

The current value and all defined variable names are displayed via the dump command.

Listing Available Functions: funcs

A display of all available functions can be obtained when executing CALCULATOR(3f) by entering the command ‘funcs’. No descriptions are provided.

ADDING FUNCTIONS

Any program that calls CALCULATOR(3f) directly or indirectly (via JUCALX (), INUM0(), RNUM0(), SNUM0()) can extend the functions available by supplying two routines:

  1. SUBSTITUTE_SUBROUTINE(3f) - This user-supplied routine is a hook for programmers to add their own functions to CALCULATOR(3f) without having to change CALCULATOR(3f) directly. It is passed the name of unknown functions and their parameter lists if the expression ‘ownmode(1)’ is passed to the calculator. If you do not need to add custom functions to the calculator this is not required. A user-defined function call be created and called with call set_mysub(SUBROUTINE_NAME) The routine must be defined with an explicit interface available in the calling unit.
  2. SUBSTITUTE_C(3f) - This user-supplied function is here to optimize performance of a particular program and everyone else should typically ignore it. In a special case a non-standard function needed added that was called so heavily that it was important that it be called more efficiently than a user defined function placed in SUBSTITUTE_SUBROUTINE(3f) is. It allows for the function “c” to be defined and given an array and an array size as arguments. By default the “c” function just returns zero. A replacement can be defined by creating a function with similar arguments and calling call set_myfunc(FUNCTION_NAME). The routine must be defined with an explicit interface available in the calling unit.

The following program shows a simple but complete line-mode calculator program.

    ./compute # run example program
    a=10 a/2 3**4
    sin(3.1416/4)
    PI=2*asin(1)
    diameter=20.3+8/4
    circumference=PI*diameter
    funcs dump
    # use end-of-file (typically control-D) to exit program ctrl-D
     program demo_M_calculator

     !     line mode calculator that calls calculator
     !
     use M_calculator, only: calculator,iclen_calc
     use M_calculator, only : rnum0
     use M_calculator, only : set_mysub, set_myfunc
     implicit none
     integer, parameter        :: k_dbl = SELECTED_REAL_KIND(15,300) ! real*8
     character(len=iclen_calc) :: event, line
     character(len=iclen_calc) :: outlin
     integer                   :: ios
     integer                   :: ierr
     real(kind=k_dbl)          :: rvalue
     character(len=80)         :: string
        INFINITE: do
          read(*,'(a)',iostat=ios)line
          if(ios.ne.0)exit INFINITE
          call calculator(line,outlin,event,rvalue,ierr)
          ! line   -- input expression
          ! outlin -- result as a string
          ! event  --
          ! rvalue -- result as a numeric value
          ! ierr   -- return status
          !
          ! several different meaning to the status flag ...
          select case(ierr)
          case(0)  ! a numeric value was returned without error
            write(6,'(a,a,a)')trim(outlin),' = ',trim(line)
          case(2)  ! a string value was returned without error
            write(6,'(a)')trim(event)
          case(1)  ! a request for a message has been returned
              ! (from DUMP or FUNC)
            write(6,'(a,a)')'message===>',trim(event)
          case(-1) ! an error has occurred
            write(6,'(a,a)')'error===>',trim(event)
          case default ! this should not occur
            write(6,'(a)')'warning===> unexpected ierr value from calculator'
          end select
            enddo INFINITE

            string='A=sind(30)'
            rvalue=rnum0(string,ierr)
            if(ierr.eq.0)then
          write(*,*) rvalue
            else
          write(*,*) 'error evaluating '//trim(string)
            endif
            rvalue=rnum0('A',ierr)
            write(*,*) rvalue

            ! OPTIONAL: contains example routines for adding user-defined
            !           functions.
            !
            call set_mysub(my_functions)
            call set_myfunc(c)
    contains
    subroutine my_functions(func,iflen,args,iargstp,n,fval,ctmp,ier)
    ! extend functions available to the calculator routine
    !
    !  if the function ownmode(1) is called this subroutine
    !  will be accessed to do user-written functions.
    !
    !  func(iend-1)=procedure name.  func should not be changed.
    !  iflen=length of procedure name.
    !  args=array of 100 elements containing procedure arguments.
    !  iargstp=type of argument(1=numeric value,2=position of string value)
    !  n=integer number of parameters
    !  x=array of 55555 x values
    !  y=array of 55555 y values
    !  fval=value to replace function call
    !  ctmp=string to return when returning a string value
    !  ier=returned error flag value.
    !      set to -1 if an error occurs.
    !      set to  0 if a number is returned
    !      set to  2 if a string is returned
    !
    use M_calculator, only: x,y,values,values_len,iclen_calc
    integer, parameter           :: k_dbl = SELECTED_REAL_KIND(15,300) ! real*8
    ! values: the values of string variables
    ! values_len: the lengths of the string variable values
    character(len=*),intent(in)  :: func
    integer,intent(in)           :: iflen
    real(kind=k_dbl),intent(in)  :: args(100)
    integer,intent(in)           :: iargstp(100)
    integer,intent(in)           :: n
    real(kind=k_dbl)             :: fval
    character(len=*)             :: ctmp
    integer                      :: ier

    integer                      :: iwhich
    integer                      :: i10
    integer                      :: ilen
    character(len=iclen_calc)    :: temp1
       fval=0.0d0
       !-----------------------------------------------------------------------
       write(*,*)'*my_functions* unknown function ', func(1:iflen)
       write(*,*)'function name length is..',iflen
       write(*,*)'number of arguments .....',n
       do i10=1,n
          if(iargstp(i10).eq.0)then
             write(*,*)i10,' VALUE=',args(i10)
          elseif(iargstp(i10).eq.2)then
             iwhich=int(args(i10))
             ilen=values_len(iwhich)
             write(*,*)i10,' STRING='//values(iwhich)(:ilen)
          else
             write(*,*)'unknown parameter type is ',iargstp(i10)
          endif
       enddo
    end subroutine my_functions
    !
    real function c(fval,n)
    implicit none
    !  a built-in calculator function called c must be satisfied.
    !  write whatever you want here as a function
    integer, parameter          :: k_dbl = SELECTED_REAL_KIND(15,300) !  real*8
    integer,intent(in)          :: n
    real(kind=k_dbl),intent(in) :: fval(n)
       c=0.0_k_dbl
    end function c
    !
    end program demo_M_calculator