merge_table Subroutine

public recursive subroutine merge_table(lhs, rhs, config)

Merge TOML tables by appending their values

Arguments

Type IntentOptional Attributes Name
class(toml_table), intent(inout) :: lhs

Instance of table to merge into

class(toml_table), intent(inout) :: rhs

Instance of table to be merged

type(toml_merge_config), intent(in), optional :: config

Merge policy


Source Code

recursive subroutine merge_table(lhs, rhs, config)

   !> Instance of table to merge into
   class(toml_table), intent(inout) :: lhs

   !> Instance of table to be merged
   class(toml_table), intent(inout) :: rhs

   !> Merge policy
   type(toml_merge_config), intent(in), optional :: config

   type(toml_merge_config) :: policy
   type(toml_key), allocatable :: list(:)
   class(toml_value), pointer :: ptr1, ptr2
   class(toml_keyval), pointer :: kv
   class(toml_value), allocatable :: tmp
   logical :: has_key
   integer :: i, n, stat

   policy = toml_merge_config()
   if (present(config)) policy = config

   call rhs%get_keys(list)
   n = size(list, 1)

   do i = 1, n
      if (allocated(tmp)) deallocate(tmp)
      call rhs%get(list(i)%key, ptr1)
      has_key = lhs%has_key(list(i)%key)
      select type(ptr1)
      class is(toml_keyval)
         if (has_key .and. policy%keyval == merge_policy%overwrite) then
            call lhs%delete(list(i)%key)
            has_key = .false.
         end if
         if (.not.has_key) then
            allocate(tmp, source=ptr1)
            kv => cast_to_keyval(tmp)
            kv%origin_value = 0
            kv%origin = 0
            call lhs%push_back(tmp, stat)
         end if

      class is(toml_array)
         if (has_key .and. policy%array == merge_policy%overwrite) then
            call lhs%delete(list(i)%key)
            has_key = .false.
         end if
         if (has_key .and. policy%array == merge_policy%append) then
            call lhs%get(list(i)%key, ptr2)
            select type(ptr2)
            class is(toml_array)
               call merge_array(ptr2, ptr1)
            end select
         end if
         if (.not.has_key) then
            allocate(tmp, source=ptr1)
            tmp%origin = 0
            call lhs%push_back(tmp, stat)
         end if

      class is(toml_table)
         if (has_key .and. policy%table == merge_policy%overwrite) then
            call lhs%delete(list(i)%key)
            has_key = .false.
         end if
         if (has_key .and. policy%table == merge_policy%append) then
            call lhs%get(list(i)%key, ptr2)
            select type(ptr2)
            class is(toml_table)
               call merge_table(ptr2, ptr1, policy)
            end select
         end if
         if (.not.has_key) then
            allocate(tmp, source=ptr1)
            tmp%origin = 0
            call lhs%push_back(tmp, stat)
         end if
      end select
   end do

end subroutine merge_table