M_calculator Module

NAME

calculator - [M_calculator] parse calculator expression and return numeric and string values (LICENSE:PD)

SYNOPSIS

subroutine calculator(inline,outlin,mssg,slast,ierr)

character(len=*),intent=(in)           :: inline
character(len=iclen_calc),intent=(out) :: outlin
character(len=iclen_calc),intent=(out) :: mssg
doubleprecision, intent=(out)          :: slast
integer, intent=(out)                  :: ierr

DESCRIPTION

CALCULATOR(3f) evaluates FORTRAN-like expressions. It can be used to add
calculator-like abilities to your program.

OPTIONS

 inline  INLINE is a string expression up to (iclen_calc=512) characters long.
         The syntax of an expression is described in
         the main document of the Calculator Library.
 outlin  Returned numeric value as a string when IERR=0.
 mssg    MSSG is a string that can serve several purposes
         o Returned string value when IERR=2
         o Error message string when IERR=-1
         o Message from 'funcs' or 'dump' command when IERR=1
 slast   SLAST has different meanings depending on whether a string or number
         is being returned
         o REAL value set to last successfully calculated value when IERR=0
         o Number of characters in returned string variable when IERR=2
 ierr    status flag.
           -1  An error occurred
            0  A numeric value was returned
            1  A message was returned
            2  A string value was returned

EXAMPLES

Example calculator program

   program demo_calculator
   !compute(1f): line mode calculator program (that calls calculator(3f))
   use M_calculator, only: calculator,iclen_calc
   ! iclen_calc : max length of expression or variable value as a string
   implicit none
   integer,parameter         :: dp=kind(0.0d0)
   character(len=iclen_calc) :: line
   character(len=iclen_calc) :: outlin
   character(len=iclen_calc) :: event
   real(kind=dp)             :: rvalue
   integer                   :: ierr
   ierr=0
   call calculator('ownmode(1)',outlin,event,rvalue,ierr)
   ! activate user-defined function interface
   INFINITE: do
      read(*,'(a)',end=999)line
      if(line.eq.'.')stop
      call calculator(line,outlin,event,rvalue,ierr)
      select case (ierr)
      ! several different meanings to the error flag returned by calculator
      case(0)
      ! a numeric value was returned without error
        write(*,'(a,a,a)')trim(outlin),' = ',trim(line)
      case(2)
      ! a string value was returned without error
        write(*,'(a)')trim(event(:int(rvalue)))
      case(1)
      ! a request for a message has been returned (from DUMP or FUNC)
        write(*,'(a,a)')'message===>',trim(event(:len_trim(event)))
      case(-1)
      ! an error has occurred
        write(*,'(a,a)')'error===>',trim(event(:len_trim(event)))
      case default
      ! this should not occur
        WRITE(6,'(A,i10)')'*CALCULATOR* UNEXPECTED IERR VALUE ',IERR
      end select
   enddo INFINITE
   999 continue
   end program demo_calculator

SEE ALSO

 see INUM0(),RNUM0(),SNUM0(),,EXPRESSION().

AUTHOR

John S. Urban

LICENSE

Public Domain

AUTHOR John S. Urban

VERSION 1.0 19971123,20161218

implicit doubleprecision (a-h,o-z)



Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: iclen_calc = 512
integer, public, parameter :: icname_calc = 20
integer, public, parameter :: ixy_calc = 55555
character(len=:), public, allocatable, save :: values(:)
integer, public, save, allocatable :: values_len(:)
real(kind=dp), public, save :: x(ixy_calc) = 0.0_dp
real(kind=dp), public, save :: y(ixy_calc) = 0.0_dp

Interfaces

public interface insert

  • private subroutine insert_c(list, value, place)

    Arguments

    Type IntentOptional Attributes Name
    character(len=:), allocatable :: list(:)
    character(len=*), intent(in) :: value
    integer, intent(in) :: place
  • private subroutine insert_d(list, value, place)

    Arguments

    Type IntentOptional Attributes Name
    doubleprecision, allocatable :: list(:)
    doubleprecision, intent(in) :: value
    integer, intent(in) :: place
  • private subroutine insert_i(list, value, place)

    Arguments

    Type IntentOptional Attributes Name
    integer, allocatable :: list(:)
    integer, intent(in) :: value
    integer, intent(in) :: place

public interface locate

  • private subroutine locate_c(list, value, place, ier, errmsg)

    Arguments

    Type IntentOptional Attributes Name
    character(len=:), allocatable :: list(:)
    character(len=*), intent(in) :: value
    integer, intent(out) :: place
    integer, intent(out), optional :: ier
    character(len=*), intent(out), optional :: errmsg
  • private subroutine locate_d(list, value, place, ier, errmsg)

    Arguments

    Type IntentOptional Attributes Name
    doubleprecision, allocatable :: list(:)
    doubleprecision, intent(in) :: value
    integer, intent(out) :: place
    integer, intent(out), optional :: ier
    character(len=*), intent(out), optional :: errmsg

public interface remove

  • private subroutine remove_c(list, place)

    Arguments

    Type IntentOptional Attributes Name
    character(len=:), allocatable :: list(:)
    integer, intent(in) :: place
  • private subroutine remove_d(list, place)

    Arguments

    Type IntentOptional Attributes Name
    doubleprecision, allocatable :: list(:)
    integer, intent(in) :: place
  • private subroutine remove_i(list, place)

    Arguments

    Type IntentOptional Attributes Name
    integer, allocatable :: list(:)
    integer, intent(in) :: place

public interface replace

  • private subroutine replace_c(list, value, place)

    Arguments

    Type IntentOptional Attributes Name
    character(len=:), allocatable :: list(:)
    character(len=*), intent(in) :: value
    integer, intent(in) :: place
  • private subroutine replace_d(list, value, place)

    Arguments

    Type IntentOptional Attributes Name
    doubleprecision, allocatable :: list(:)
    doubleprecision, intent(in) :: value
    integer, intent(in) :: place
  • private subroutine replace_i(list, value, place)

    Arguments

    Type IntentOptional Attributes Name
    integer, allocatable :: list(:)
    integer, intent(in) :: value
    integer, intent(in) :: place

Abstract Interfaces

abstract interface

  • public function c_interface(args, n)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: args(n)
    integer, intent(in) :: n

    Return Value real

abstract interface

  • public subroutine juown1_interface(func, iflen, args, iargstp, n, fval, ctmp, ier)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: func
    integer, intent(in) :: iflen
    real(kind=dp), intent(in) :: args(100)
    integer, intent(in) :: iargstp(100)
    integer, intent(in) :: n
    real(kind=dp) :: fval
    character(len=*) :: ctmp
    integer :: ier

Functions

public function dnum0(inline, ierr)

doubleprecision function dnum0(inline,ierr)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inline
integer, intent(out), optional :: ierr

Return Value doubleprecision

public function inum0(inline, ierr)

integer function inum0(inline,ierr)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inline
integer, intent(out), optional :: ierr

Return Value integer

public function rnum0(inline, ierr)

Sample program

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inline
integer, intent(out), optional :: ierr

Return Value real

public function snum0(inline0, ierr)

function snum0(inline0,ierr)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inline0
integer, intent(out), optional :: ierr

Return Value character(len=:), allocatable


Subroutines

public recursive subroutine calculator(inline, outlin, mssg, slast, ierr)

!!!!! could return string values directly instead of thru message field !!!!! make sure normal output values are not left indeterminate

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inline
character(len=iclen_calc), intent(out) :: outlin
character(len=iclen_calc), intent(out) :: mssg
real(kind=dp), intent(out) :: slast
integer, intent(out) :: ierr

public recursive subroutine expression(inlin0, outval, outlin0, ierr, ilen)

Results:

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inlin0
doubleprecision :: outval
character(len=*) :: outlin0
integer, intent(out) :: ierr
integer, intent(out) :: ilen

public subroutine set_myfunc(proc)

Arguments

Type IntentOptional Attributes Name
procedure(c_interface) :: proc

public subroutine set_mysub(proc)

Arguments

Type IntentOptional Attributes Name
procedure(juown1_interface) :: proc

public subroutine stuff(varnam, value, ioflag)

subroutine stuff(varnam,val,ioflag)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: varnam
class(*), intent(in) :: value
character(len=*), intent(in), optional :: ioflag

public subroutine stuffa(varnam, string, ioflag)

subroutine stuffa(varnam,string,ioflag)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: varnam
character(len=*), intent(in) :: string
character(len=*), intent(in), optional :: ioflag