nfa__add_transition Subroutine

private pure subroutine nfa__add_transition(self, nfa_graph, src, dst, c)

Note

Note that the return value of the size function on an unallocated array is undefined.

Type Bound

nfa_state_node_t

Arguments

Type IntentOptional Attributes Name
class(nfa_state_node_t), intent(inout) :: self
type(nfa_state_node_t), intent(inout) :: nfa_graph(:)
integer(kind=int32), intent(in) :: src
integer(kind=int32), intent(in) :: dst
type(segment_t), intent(in) :: c

Source Code

   pure subroutine nfa__add_transition(self,nfa_graph, src, dst, c)
      use :: forgex_parameters_m, only: NFA_TRANSITION_UNIT
      implicit none
      class(nfa_state_node_t), intent(inout) :: self
      type(nfa_state_node_t), intent(inout) :: nfa_graph(:)
      integer(int32), intent(in) :: src, dst
      type(segment_t) ,intent(in) :: c

      integer(int32) :: j, jj, k

      !== Forward transition process
      j = NFA_NULL_TRANSITION
      if (allocated(self%forward) .and. c /= SEG_EPSILON) then
         ! ε遷移でない場合、同じ行き先の遷移があるかどうか検索する
         do jj = 1, self%forward_top
            if ( dst == self%forward(jj)%dst .and. self%forward(jj)%c_top < NFA_C_SIZE) then
               ! セグメント配列のサイズを超える場合には新しい遷移にセグメントを追加する
               j = jj
            end if
         end do
      end if

      if (j == NFA_NULL_TRANSITION) then
         j = self%forward_top
      end if

      !> @note Note that the return value of the size function on an unallocated array is undefined.
      if (.not. allocated(self%forward)) then
         ! Reallocate the forward array component.
         call self%realloc_f()
      endif

      if (j >= size(self%forward, dim=1)) then
         ! Reallocate the forward array component.
         call self%realloc_f()
      endif

      if (.not. allocated(self%forward(j)%c))  then
         allocate(self%forward(j)%c(1:NFA_C_SIZE))
      end if

      self%forward(j)%c_top = self%forward(j)%c_top + 1  ! Increment
      k = self%forward(j)%c_top

      self%forward(j)%c(k) = c
      self%forward(j)%dst = dst
      self%forward(j)%is_registered = .true.

      if (j == self%forward_top) self%forward_top = self%forward_top + 1

      !== Backward transition process
      j = NFA_NULL_TRANSITION
      if (allocated(nfa_graph(dst)%backward) .and. c /= SEG_EPSILON) then
         do jj = 1, nfa_graph(dst)%backward_top
            if (src == nfa_graph(dst)%backward(jj)%dst .and. nfa_graph(dst)%backward(jj)%c_top < NFA_C_SIZE) j = jj
               ! セグメント配列のサイズを超える場合には新しい遷移にセグメントを追加する
         end do
      end if

      if (j == NFA_NULL_TRANSITION) then
         j = nfa_graph(dst)%backward_top
      end if

      if (.not. allocated(nfa_graph(dst)%backward)) then
         ! Reallocate backward array component.
         call nfa_graph(dst)%realloc_b
      end if

      if (j >= size(nfa_graph(dst)%backward, dim=1)) then
         ! Reallocate backward array component.
         call nfa_graph(dst)%realloc_b
      endif

      if (.not. allocated(nfa_graph(dst)%backward(j)%c))  allocate(nfa_graph(dst)%backward(j)%c(NFA_C_SIZE))

      nfa_graph(dst)%backward(j)%c_top = nfa_graph(dst)%backward(j)%c_top + 1
      k = nfa_graph(dst)%backward(j)%c_top

      nfa_graph(dst)%backward(j)%c(k) = c
      nfa_graph(dst)%backward(j)%dst = src
      nfa_graph(dst)%backward(j)%is_registered = .true.

      if(j == nfa_graph(dst)%backward_top) nfa_graph(dst)%backward_top = nfa_graph(dst)%backward_top + 1
   end subroutine nfa__add_transition