automaton__construct_dfa Subroutine

private pure subroutine automaton__construct_dfa(self, curr_i, dst_i, symbol, d_tra)

This subroutine gets the destination index of DFA nodes from the current index with given symbol, adding a DFA node if necessary.

It calculates the set of NFA states that can be reached from the current node for the given symbol, excluding epsilon transitions, and then registers the new DFA state node if it has not already been registered. Finally, it adds the transition from the current node to the destination node in the DFA graph.

Type Bound

automaton_t

Arguments

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

Source Code

   pure subroutine automaton__construct_dfa (self, curr_i, dst_i, symbol, d_tra)
      use :: forgex_lazy_dfa_node_m, only: dfa_transition_t
      implicit none
      class(automaton_t), intent(inout) :: self
      integer(int32),     intent(in)    :: curr_i
      integer(int32),     intent(inout) :: dst_i
      character(*),       intent(in)    :: symbol
      type(dfa_transition_t), intent(in) :: d_tra
      type(nfa_state_set_t) :: nfa_set

      integer(int32) :: prev_i

      dst_i = DFA_INVALID_INDEX
      prev_i = curr_i

      nfa_set = d_tra%nfa_set

      ! ε遷移との和集合を取り、d_tra%nfa_setに格納する。
      ! Combine the state set with epsilon-transitions and store in `d_tra%nfa_set`.
      call self%nfa%collect_epsilon_transition(nfa_set)

      ! 空のNFA状態集合の登録を禁止する
      if (.not. any(nfa_set%vec)) then
         dst_i = DFA_INVALID_INDEX
         return
      end if

      dst_i = self%dfa%registered(nfa_set)

      ! まだDFA状態が登録されていない場合は、新しく登録する。
      ! If the destination index is DFA_INVALID_INDEX, register a new DFA node.
      if (dst_i == DFA_INVALID_INDEX) then
         call self%register_state(nfa_set, dst_i)
      end if

      ! If the destination index is DFA_INVALID_INDEX, the registration is failed.
      if (dst_i == DFA_INVALID_INDEX) error stop "DFA registration failed."

      if (self%dfa%nodes(prev_i)%is_registered_tra(dst_i, symbol)) return

      ! 遷移を追加する
      ! Add a DFA transition from `prev` to `next` for the given `symbol`.
      ! call self%dfa%add_transition(d_tra%nfa_set, prev_i, dst_i,  &
      !        which_segment_symbol_belong(self%all_segments, symbol))
      call self%dfa%add_transition(nfa_set, prev_i, dst_i, symbol)
   end subroutine automaton__construct_dfa