tree_graph__hexadecimal_to_segment Subroutine

private pure subroutine tree_graph__hexadecimal_to_segment(self, seglist)

This procedure handles a escape sequence with '\x'.

Type Bound

tree_t

Arguments

Type IntentOptional Attributes Name
class(tree_t), intent(inout) :: self
type(segment_t), intent(inout), allocatable :: seglist(:)

Source Code

   pure subroutine tree_graph__hexadecimal_to_segment(self, seglist)
      implicit none
      class(tree_t), intent(inout) :: self
      type(segment_t), intent(inout), allocatable :: seglist(:)
      
      character(:), allocatable :: hex
      integer :: i
      logical :: is_two_digit, is_longer_digit

      hex = ''

      call self%tape%get_token()

      is_longer_digit = self%tape%current_token == tk_lcurlybrace
      is_two_digit = .not. is_longer_digit

      if (is_longer_digit) call self%tape%get_token()

      hex = self%tape%token_char(1:1) ! First, get the second digit.
      i = 2

      reader: do while(.true.)
         if (is_two_digit .and. i >= 3) exit reader
         call self%tape%get_token()

         if (is_longer_digit .and. self%tape%current_token /= tk_rcurlybrace .and. self%tape%current_token /= tk_char) then
            self%is_valid = .false.
            self%code = SYNTAX_ERR_CURLYBRACE_MISSING
            return
         end if

         if (self%tape%current_token == tk_rcurlybrace) exit reader
         hex = hex//self%tape%token_char(1:1)
         i = i + 1
      end do reader

      allocate(seglist(1))
      call hex2seg(trim(hex), seglist(1), self%code)

      if (self%code /= SYNTAX_VALID) then
         self%is_valid = .false.
         return
      end if

      self%is_valid = seglist(1) .in. SEG_WHOLE

      if (.not. self%is_valid) self%code  = SYNTAX_ERR_UNICODE_EXCEED


   end subroutine tree_graph__hexadecimal_to_segment