ascii2seg Subroutine

private pure subroutine ascii2seg(self, segments)

Type Bound

ascii_t

Arguments

Type IntentOptional Attributes Name
class(ascii_t), intent(in) :: self
type(segment_t), intent(inout), allocatable :: segments(:)

Source Code

   pure subroutine ascii2seg(self, segments)
      use :: forgex_segment_m, only: segment_t
      implicit none
      class(ascii_t), intent(in) :: self
      type(segment_t), intent(inout), allocatable :: segments(:)
      
      type(segment_t), allocatable :: tmp(:)
      logical :: in_range
      integer :: i, j, jb, je, k

      in_range = .false.

      allocate(tmp(ASCII_SIZE_BIT/2 + 1))

      k = 0
      i = 1
      do i = 0, ASCII_SIZE-1
         do j = 0, bits_64-1
            if (btest(self%a(i), j)) then
               if (.not. in_range) then
                  jb = i*bits_64 + j
                  in_range = .true.
               end if
            else
               if (in_range) then
                  je = i*bits_64+j-1
                  k = k + 1
                  tmp(k)%min = jb
                  tmp(k)%max = je
                  in_range = .false.
               end if 
            end if
         end do 
      end do

      if (in_range) then
         k = k + 1
         tmp(k)%min = jb
         tmp(k)%max = (i-1)*bits_64 + (bits_64-1)
      end if
      if (k > 0) then
         allocate(segments(k))
         segments(1:k) = tmp(1:k)
      end if
   end subroutine ascii2seg