do_matching_exactly Subroutine

public pure subroutine do_matching_exactly(automaton, string, res, prefix, suffix, runs_engine)

This subroutine is intended to be called from the forgex API module.

Arguments

Type IntentOptional Attributes Name
type(automaton_t), intent(inout) :: automaton
character(len=*), intent(in) :: string
logical, intent(inout) :: res
character(len=*), intent(in) :: prefix
character(len=*), intent(in) :: suffix
logical, intent(inout) :: runs_engine

Source Code

   pure subroutine do_matching_exactly(automaton, string, res, prefix, suffix, runs_engine)
      implicit none
      type(automaton_t),      intent(inout) :: automaton
      character(*),           intent(in)    :: string
      logical,                intent(inout) :: res
      character(*),           intent(in)    :: prefix, suffix
      logical,                intent(inout) :: runs_engine

      integer :: cur_i, dst_i ! current and destination index of DFA nodes
      integer :: ci           ! character index
      integer :: next_ci      ! next character index
      integer :: max_match    ! the highest index number matched

      ! This character string variable will have null characters added to the beginning and end.
      character(:), allocatable :: str

      integer :: len_pre, len_suf, n
      logical :: empty_pre, empty_post, matches_pre, matches_post

      runs_engine = .false.

      len_pre = len(prefix)
      len_suf = len(suffix)
      n = len(string)
      matches_pre = .true.
      matches_post = .true.

      ! Returns true immediately if the given prefix exactly matches the string.
      if (len(string) > 0 .and. len(prefix) >0 ) then
         if (prefix == string .and. len_pre == n) then
            res = .true.
            return
         end if
      end if
      
      ! Returns false if the prefix or suffix is ​​longer than the input string.
      if (len_pre > len(string) .or. len_suf > len(string)) then
            res = .false.
            return
      end if
      
      ! If prefix and suffix are empty strings, each flag is set.
      empty_pre   = prefix == ''
      empty_post  = suffix == ''

      ! If the string is not an empty string, branch the process.
      if (len(string) > 0) then
         if (.not. empty_pre) matches_pre = (string(1:len_pre) == prefix)
         if (.not. empty_post) matches_post = (string(n-len_suf+1:n) == suffix)
      else
         ! If the string is empty string, these flags are true if the prefix/suffix length is zero, false otherwise.
         matches_pre = (len(prefix) == 0)
         matches_post = (len(suffix) == 0)
      end if

      ! True if the prefix is empty or matches, and the suffix is empty or matches.
      runs_engine = (empty_pre .or. matches_pre) .and. (empty_post .or. matches_post)


      if (.not. runs_engine) then
         res = .false.
         return
      end if
      !==  The decision to run the engine ends here.  ==! 


      ! Initialize `cur_i` with automaton's initial index.
      cur_i = automaton%initial_index

      ! If the DFA have not been initialized, abort the program.
      if (cur_i == DFA_NOT_INIT) then
         error stop "DFA have not been initialized."
      end if

      ! If the input string is an empty string, returns a logical value
      ! indicating whether the current state is accepting or not.
      if (len(string) == 0) then
         res = automaton%dfa%nodes(cur_i)%accepted
         return
      end if

      ! Initialize counter variables.
      max_match = 0
      ci = 1
      str = char(0)//string//char(0)

      ! Loop and proceed with matching unless the current index is DFA_INVALID_INDEX.
      do while (cur_i /= DFA_INVALID_INDEX)

         ! If the current state acceptable, the value of `max_match` is updated with `i`.
         if (automaton%dfa%nodes(cur_i)%accepted) then
            max_match = ci
         end if

         if (ci > len(str)) exit

         ! Get the index of the next character and assign it to `next_ci`.
         next_ci = idxutf8(str, ci) + 1

         ! Lazy evaluation is performed by calling this procedure here.
         ! The index of destination DFA node is stored in the `dst_i` variable.
         call automaton%construct(cur_i, dst_i, str(ci:next_ci-1))

         ! If there is mismatch in the first byte of the NULL character, try again with the second byte.
         if (dst_i == DFA_INVALID_INDEX .and. ci == 1) then
            ci = 2
            next_ci = idxutf8(str, ci) + 1
            call automaton%construct(cur_i, dst_i, str(ci:next_ci-1))
         end if

         ! update counters
         cur_i = dst_i
         ci = next_ci

      end do
      ! If the maximum index of the match is two larger than length of the string,
      ! this function returns true, otherwise it returns false.
      if (max_match >= len(string)+2) then
         res = .true.
      else
         res = .false.
      end if
   end subroutine do_matching_exactly