fparser Derived Type

type, public :: fparser

The function parser class.


Inherits

type~~fparser~~InheritsGraph type~fparser fparser type~stack_func_container stack_func_container type~fparser->type~stack_func_container bytecode_ops type~list_of_errors list_of_errors type~fparser->type~list_of_errors error_msg type~error error type~list_of_errors->type~error head

Inherited by

type~~fparser~~InheritedByGraph type~fparser fparser type~fparser_array fparser_array type~fparser_array->type~fparser f

Contents

Source Code


Components

TypeVisibilityAttributesNameInitial
type(stack_func_container), public, dimension(:), allocatable:: bytecode_ops

array of function pointers

integer, public, dimension(:), allocatable:: bytecode

array of integers

integer, public :: bytecodesize =0
real(kind=wp), public, dimension(:), allocatable:: immed
integer, public :: immedsize =0
real(kind=wp), public, dimension(:), allocatable:: stack
integer, public :: stacksize =0
integer, public :: stackptr =0
type(list_of_errors), public :: error_msg

list of error messages


Type-Bound Procedures

procedure, public :: parse => parse_function

  • private subroutine parse_function(me, funcstr, var, case_sensitive)

    Parse the function string funcstr and compile it into bytecode

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me
    character(len=*), intent(in) :: funcstr

    function string

    character(len=*), intent(in), dimension(:):: var

    array with variable names

    logical, intent(in), optional :: case_sensitive

    are the variables case sensitive? [default is false]

procedure, public :: evaluate => evaluate_function

  • private subroutine evaluate_function(me, val, res)

    Evaluate bytecode of function for the values passed in array val.

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me
    real(kind=wp), intent(in), dimension(:):: val

    variable values

    real(kind=wp), intent(out) :: res

    result

procedure, public :: destroy => destroy_parser

  • private pure elemental subroutine destroy_parser(me)

    fparser destructor.

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me

procedure, public :: error

  • private pure elemental function error(me)

    Returns true if there are any errors in the class.

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(in) :: me

    Return Value logical

    true if there are any errors in the class

procedure, public :: print_errors

  • private subroutine print_errors(me, iunit)

    Prints the error messages (if any) in the class.

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me
    integer, intent(in) :: iunit

    unit number for printing (assumed to be open)

procedure, public :: clear_errors

  • private pure elemental subroutine clear_errors(me)

    Clears any error messages in the class.

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me

procedure, public :: compile_substr

  • private recursive subroutine compile_substr(me, f, b, e, var)

    Compile i-th function string f into bytecode

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me
    character(len=*), intent(in) :: f

    function substring

    integer, intent(in) :: b

    begin position substring

    integer, intent(in) :: e

    end position substring

    character(len=*), intent(in), dimension(:):: var

    array with variable names

procedure, public :: compile

  • private subroutine compile(me, f, var)

    Compile function string f into bytecode

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me
    character(len=*), intent(in) :: f

    function string

    character(len=*), intent(in), dimension(:):: var

    array with variable names

procedure, public :: check_syntax

  • private recursive subroutine check_syntax(me, func, funcstr, var, ipos)

    Check syntax of function string.

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me
    character(len=*), intent(in) :: func

    function string without spaces

    character(len=*), intent(in) :: funcstr

    original function string

    character(len=*), intent(in), dimension(:):: var

    array with variable names

    integer, intent(in), dimension(:):: ipos

procedure, public :: add_error

  • private subroutine add_error(me, j, ipos, funcstr, msg)

    add error message to the class.

    Arguments

    TypeIntentOptionalAttributesName
    class(fparser), intent(inout) :: me
    integer, intent(in) :: j
    integer, intent(in), dimension(:):: ipos
    character(len=*), intent(in) :: funcstr

    original function string

    character(len=*), intent(in), optional :: msg

Source Code

    type,public :: fparser

        private

        type(stack_func_container),dimension(:),allocatable :: bytecode_ops  !! array of function pointers
        integer,dimension(:),allocatable :: bytecode  !! array of integers
        integer :: bytecodesize = 0

        real(wp),dimension(:),allocatable :: immed
        integer :: immedsize = 0

        real(wp),dimension(:),allocatable :: stack
        integer :: stacksize = 0
        integer :: stackptr = 0

        type(list_of_errors) :: error_msg       !! list of error messages

    contains

        private

        procedure,public :: parse    => parse_function
        procedure,public :: evaluate => evaluate_function
        procedure,public :: destroy  => destroy_parser
        procedure,public :: error
        procedure,public :: print_errors
        procedure,public :: clear_errors

        procedure :: compile_substr
        procedure :: compile
        procedure :: check_syntax
        procedure :: add_error

    end type fparser