automaton__epsilon_closure Subroutine

private pure recursive subroutine automaton__epsilon_closure(self, closure, n_index)

Compute the ε-closure for a set of NFA states.

The ε-closure is the set of NFA states reachable from a given set of NFA states via ε-transition. This subroutine calculates the ε-closure and stores it in the closure parameter.

Type Bound

automaton_t

Arguments

Type IntentOptional Attributes Name
class(automaton_t), intent(inout) :: self
type(nfa_state_set_t), intent(inout) :: closure
integer, intent(in) :: n_index

Source Code

   pure recursive subroutine automaton__epsilon_closure(self, closure, n_index)
      use :: forgex_nfa_node_m
      implicit none
      class(automaton_t), intent(inout) :: self
      type(nfa_state_set_t), intent(inout) :: closure
      integer, intent(in) :: n_index

      type(nfa_state_node_t) :: n_node
      type(nfa_transition_t) :: n_tra
      integer :: dst
      integer :: j

      call add_nfa_state(closure, n_index)

      ! n_node = self%nfa%graph(n_index)

      if (.not. allocated(self%nfa%graph(n_index)%forward)) return

       ! すべての順方向の遷移をスキャンする
      do j = 1, self%nfa%graph(n_index)%forward_top
         ! 一時変数にコピー
         ! n_tra = self%nfa%graph(n_index)%forward(j)

         ! if (.not. allocated(self%nfa%graph(n_index)%forward(j)%c%sps)) cycle

         dst = self%nfa%graph(n_index)%forward(j)%dst

         if (dst == NFA_NULL_TRANSITION) cycle

         ! if (any(self%nfa%graph(n_index)%forward(j)%c%sps == SEG_EPSILON) &
         if (self%nfa%graph(n_index)%forward(j)%c%is_flagged_epsilon() &
         .and. .not. check_nfa_state(closure, dst)) then

            if (dst /= NFA_NULL_TRANSITION) then
               call self%epsilon_closure(closure, dst)
            end if
         end if

      end do

   end subroutine automaton__epsilon_closure