generate_nfa Subroutine

public pure recursive subroutine generate_nfa(tree, idx, nfa, entry_i, exit_i)

Arguments

Type IntentOptional Attributes Name
type(tree_t), intent(in) :: tree
integer(kind=int32), intent(in) :: idx
type(nfa_graph_t), intent(inout) :: nfa
integer(kind=int32), intent(in) :: entry_i
integer(kind=int32), intent(in) :: exit_i

Source Code

   pure recursive subroutine generate_nfa(tree, idx, nfa, entry_i, exit_i)
      use :: forgex_enums_m, only: op_char, op_empty, op_closure, op_concat, op_repeat, op_union
      use :: forgex_parameters_m, only: INFINITE, INVALID_INDEX

      implicit none
      type(tree_t), intent(in) :: tree
      integer(int32), intent(in) :: idx
      type(nfa_graph_t), intent(inout) :: nfa
      integer(int32), intent(in) :: entry_i, exit_i

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

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

      select case(tree%nodes(i)%op)
      case (op_char)
         ! Handle character operations by adding transition for each character.
         call nfa%graph(entry_i)%add_transition(entry_i, exit_i, tree%nodes(i)%c)
      
      case (op_empty)
         ! Handle empty opration by adding an epsilon transition
         call nfa%graph(entry_i)%add_transition(entry_i, exit_i, [SEG_EPSILON])
      
      case (op_closure)
         ! Handle closure (Kleene star) operations by creating new node and adding appropriate transition
         call generate_nfa_closure(tree, idx, nfa, entry_i, exit_i)
      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, entry_i, exit_i)
         call generate_nfa(tree, tree%nodes(i)%right_i, nfa, entry_i, exit_i)

      case (op_concat)
         ! Handle concatenation operations by recursively generating NFA for left and right subtrees.
         call generate_nfa_concatenate(tree, idx, nfa, entry_i, exit_i)
      
      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 nfa%new_nfa_node()

               if (nfa%is_exceeded()) call nfa%reallocate()

               node1 = nfa%top
               call generate_nfa(tree, tree%nodes(i)%left_i, nfa, 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 nfa%new_nfa_node()
               if (nfa%is_exceeded()) call nfa%reallocate()
               node2 = nfa%top

               call generate_nfa(tree, tree%nodes(i)%left_i, nfa, entry_local, node2)
               call nfa%graph(node2)%add_transition(node2, exit_i, [SEG_EPSILON])

               entry_local = node2
            end do
            

            if (min_repeat == 0) then
               call nfa%graph(entry_i)%add_transition(entry_i, exit_i, [SEG_EPSILON])
            end if

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

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