automaton__compute_reachable_state Function

private pure function automaton__compute_reachable_state(self, curr_i, symbol) result(state_set)

This function calculates a set of possible NFA states from the current DFA state by the input character symbol.

It scans through the NFA states and finds the set of reachable states by the given input symbol, excluding ε-transitions.

Type Bound

automaton_t

Arguments

Type IntentOptional Attributes Name
class(automaton_t), intent(in) :: self
integer(kind=int32), intent(in) :: curr_i
character(len=*), intent(in) :: symbol

Return Value type(nfa_state_set_t)


Source Code

   pure function automaton__compute_reachable_state(self, curr_i, symbol) result(state_set)
      use :: forgex_segment_m, only: operator(.in.), operator(/=)
      use :: forgex_nfa_node_m, only: nfa_state_node_t, nfa_transition_t
      use :: forgex_lazy_dfa_node_m, only: dfa_transition_t
      implicit none
      class(automaton_t), intent(in) :: self
      integer(int32),     intent(in) :: curr_i      ! current index of dfa
      character(*),       intent(in) :: symbol

      type(nfa_state_set_t)  :: state_set    ! RESULT variable
      type(nfa_state_set_t)  :: current_set
      integer                :: i, j, k

      ! temporary variables ... to increase the cache hit rate
      type(nfa_state_node_t)       :: n_node       ! This variable simulates a pointer.
      type(segment_t), allocatable :: segs(:)
      type(nfa_transition_t)       :: n_tra


      call init_state_set(state_set, self%nfa%nfa_top)

      current_set = self%dfa%nodes(curr_i)%nfa_set

      ! Scan the entire NFA states.
      outer: do i = 1, self%nfa%nfa_top

         ! If the i-th element of current state set is true, process the i-th NFA node.
         if (check_nfa_state(current_set, i)) then

            ! Copy to a temporary variable.
            n_node = self%nfa%nodes(i)

            if (.not. allocated(n_node%forward)) cycle

            ! Scan the all transitions belong to the NFA state node.
            middle: do j = 1, n_node%forward_top

               ! Copy to a temporary variable of type(nfa_transition_t)
               n_tra = n_node%forward(j)


               ! If it has a destination,
               if (n_tra%dst /= NFA_NULL_TRANSITION) then

                  ! Investigate the all of segments which transition has.
                  inner: do k = 1, n_tra%c_top

                     ! Copy to a temporary variable fo type(segment_t).
                     ! Note the implicit reallocation.
                     segs = n_tra%c

                     ! If the symbol is in the segment list `segs` or if the segment is epsilon,
                     if ( symbol_to_segment(symbol) .in. segs) then

                        ! Add the index of the NFA state node to `state_set` of type(nfa_state_set_t).
                        call add_nfa_state(state_set, n_node%forward(j)%dst)

                     end if

                  end do inner

               end if

            end do middle

         end if
      end do outer

   end function automaton__compute_reachable_state