tree_t Derived Type

type, public :: tree_t

This derived-type contains all node of syntax-tree in the tree_node_t type array nodes.


Components

Type Visibility Attributes Name Initial
integer, public :: code = SYNTAX_VALID
logical, public :: is_valid = .true.
type(tree_node_t), public, allocatable :: nodes(:)
integer, public :: num_alloc = 0
integer, public :: paren_balance
type(tape_t), public :: tape
integer, public :: top = INVALID_INDEX

Type-Bound Procedures

procedure, public :: build => tree_graph__build_syntax_tree

  • private pure subroutine tree_graph__build_syntax_tree(self, pattern)

    This procedure builds an AST corresponding to a given (regular expression) pattern from it.

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self
    character(len=*), intent(in) :: pattern

procedure, public :: caret_dollar => tree_graph__make_tree_caret_dollar

  • private pure subroutine tree_graph__make_tree_caret_dollar(self)

    This function constructs a tree node for carriage return (CR) and line feed (LF) characters.

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: char_class => tree_graph__char_class

  • private pure subroutine tree_graph__char_class(self)

    This subroutine treats character class expression, and does not call any other recursive procedures.

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: connect_left => tree_graph__connect_left

  • private pure subroutine tree_graph__connect_left(self, parent, child)

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self
    integer, intent(in) :: parent
    integer, intent(in) :: child

procedure, public :: connect_right => tree_graph__connect_right

  • private pure subroutine tree_graph__connect_right(self, parent, child)

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self
    integer, intent(in) :: parent
    integer, intent(in) :: child

procedure, public :: crlf => tree_graph__make_tree_crlf

procedure, public :: deallocate => tree_graph__deallocate

  • private pure subroutine tree_graph__deallocate(self)

    This procedure deallocates nodes of tree_t

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: get_top => tree_graph__get_top

procedure, public :: hex2cp => tree_graph__hexadecimal_to_codepoint

procedure, public :: hex2seg => tree_graph__hexadecimal_to_segment

  • private pure subroutine tree_graph__hexadecimal_to_segment(self, seglist)

    This procedure handles a escape sequence with '\x'.

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self
    type(segment_t), intent(inout), allocatable :: seglist(:)

procedure, public :: primary => tree_graph__primary

  • private pure recursive subroutine tree_graph__primary(self)

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: print => print_tree_wrap

  • private subroutine print_tree_wrap(self, uni)

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(in) :: self
    integer, intent(in) :: uni

procedure, public :: property => tree_graph__unicode_property

procedure, public :: reallocate => tree_graph__reallocate

  • private pure subroutine tree_graph__reallocate(self)

    This procedure handles the reallcation of the tree_node_t type array within the component of the tree_t object. However, it is not be used in v4.2.

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: regex => tree_graph__regex

  • private pure recursive subroutine tree_graph__regex(self)

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: register => tree_graph__register_node

procedure, public :: register_connector => tree_graph__register_connector

procedure, public :: shorthand => tree_graph__shorthand

  • private pure subroutine tree_graph__shorthand(self)

    This function handles shorthand escape sequences (\t, \n, \r, \d, \D, \w, \W, \s, \S). It does not call any other recursive procedures.

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: suffix_op => tree_graph__suffix_op

  • private pure recursive subroutine tree_graph__suffix_op(self)

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: term => tree_graph__term

  • private pure recursive subroutine tree_graph__term(self)

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self

procedure, public :: times => tree_graph__times

  • private pure subroutine tree_graph__times(self)

    This subroutine handles a quantifier range, and does not call any other recursive procedures.

    Arguments

    Type IntentOptional Attributes Name
    class(tree_t), intent(inout) :: self