generate_nfa Subroutine

public pure recursive subroutine generate_nfa(tree, idx, nfa_graph, nfa_top, entry, exit)

Arguments

Type IntentOptional Attributes Name
type(tree_t), intent(in) :: tree
integer(kind=int32), intent(in) :: idx
type(nfa_state_node_t), intent(inout), allocatable :: nfa_graph(:)
integer(kind=int32), intent(inout) :: nfa_top
integer(kind=int32), intent(in) :: entry
integer(kind=int32), intent(in) :: exit

Source Code

   pure recursive subroutine generate_nfa(tree, idx, nfa_graph, nfa_top, entry, exit)
      use :: forgex_enums_m
      use :: forgex_parameters_m
      implicit none
      type(tree_t),  intent(in) :: tree
      type(nfa_state_node_t), allocatable, intent(inout) :: nfa_graph(:)
      integer(int32), intent(in) :: idx
      integer(int32), intent(inout) :: nfa_top
      integer(int32), intent(in) :: entry
      integer(int32), intent(in) :: exit

      integer :: i
      integer :: k
      integer :: node1
      integer :: node2
      integer :: entry_local

      if (idx == INVALID_INDEX) return
      i = idx
      entry_local = entry

      select case(tree%nodes(i)%op)
      case (op_char)
         if (.not. allocated(tree%nodes(i)%c)) then
            error stop "ERROR: Character node of the AST do not have actual character list."
         end if
         ! Handle character operations by adding transition for each character.
         do k = 1, size(tree%nodes(i)%c, dim=1)
            call nfa_graph(entry)%add_transition(nfa_graph, entry, exit, tree%nodes(i)%c(k))
         end do

      case (op_empty)
         ! Handle empty opration by adding an epsilon transition
         call nfa_graph(entry)%add_transition(nfa_graph, entry, exit, SEG_EPSILON)

      case (op_union)
         ! Handle union operation by recursively generating NFA for left and right subtrees.
         call generate_nfa(tree, tree%nodes(i)%left_i, nfa_graph, nfa_top, entry, exit)
         call generate_nfa(tree, tree%nodes(i)%right_i, nfa_graph, nfa_top, entry, exit)

      case (op_closure)
         ! Handle closure (Kleene star) operations by creating new node and adding appropriate transition
         call generate_nfa_closure(tree, idx, nfa_graph, nfa_top, entry, exit)


      case (op_concat)
         ! Handle concatenation operations by recursively generating NFA for left and right subtrees.
         call generate_nfa_concatenate(tree, idx, nfa_graph, nfa_top, entry, exit)

      case (op_repeat)
         block
            integer(int32) :: min_repeat, max_repeat, j
            integer(int32) :: num_1st_repeat, num_2nd_repeat
            min_repeat = tree%nodes(i)%min_repeat
            max_repeat = tree%nodes(i)%max_repeat

            num_1st_repeat = min_repeat-1
            if (max_repeat == INFINITE) then
               num_1st_repeat = num_1st_repeat +1
            end if

            do j = 1, num_1st_repeat
               call make_nfa_node(nfa_top)
               if (is_exceeded(nfa_top, nfa_graph)) call reallocate_nfa(nfa_graph)
               node1 = nfa_top
               call generate_nfa(tree, tree%nodes(i)%left_i, nfa_graph, nfa_top, entry_local, node1)
               entry_local = node1
            end do

            if (min_repeat == 0) then
               num_2nd_repeat = max_repeat - 1
            else
               num_2nd_repeat = max_repeat - min_repeat
            end if

            do j = 1, num_2nd_repeat
               call make_nfa_node(nfa_top)
               if (is_exceeded(nfa_top, nfa_graph)) call reallocate_nfa(nfa_graph)
               node2 = nfa_top

               call generate_nfa(tree, tree%nodes(i)%left_i, nfa_graph, nfa_top, entry_local, node2)
               call nfa_graph(node2)%add_transition(nfa_graph, node2, exit, SEG_EPSILON)
               entry_local = node2
            end do
            

            if (min_repeat == 0) then
               call nfa_graph(entry)%add_transition(nfa_graph, entry, exit, SEG_EPSILON)
            end if

            if (max_repeat == INFINITE) then
               call generate_nfa_closure(tree, idx, nfa_graph, nfa_top, entry_local, exit)
            else
               call generate_nfa(tree, tree%nodes(i)%left_i, nfa_graph, nfa_top, entry_local, exit)
            end if

         end block
      case default ! for case (op_not_init)
         ! Handle unexpected cases.
         error stop "This will not heppen in 'generate_nfa'."
      end select
   end subroutine generate_nfa