new_collections Subroutine

public subroutine new_collections(collections, table, error)

Initialize multiple feature collections from manifest features table

Arguments

Type IntentOptional Attributes Name
type(feature_collection_t), intent(out), allocatable :: collections(:)
type(toml_table), intent(inout) :: table
type(error_t), intent(out), allocatable :: error

Source Code

    subroutine new_collections(collections, table, error)
        type(feature_collection_t), allocatable, intent(out) :: collections(:)
        type(toml_table), intent(inout) :: table
        type(error_t), allocatable, intent(out) :: error

        type(toml_key), allocatable :: keys(:)
        type(toml_table), pointer :: feature_table
        integer :: i, stat
        
        ! Get all top-level feature names from the features table
        call table%get_keys(keys)

        if (size(keys) == 0) then
            ! No features defined, return default collections
            call get_default_features(collections, error)
            return
        end if

        ! Create one collection per top-level feature name
        allocate(collections(size(keys)))
        
        do i = 1, size(keys)
            ! Get the subtable for this feature
            call get_value(table, keys(i)%key, feature_table, stat=stat)
            if (stat /= toml_stat%success) then
                call fatal_error(error, "Could not retrieve feature table for '"//keys(i)%key//"'")
                return
            end if
            
            ! Create collection from this feature's subtable
            call new_collection_from_subtable(collections(i), feature_table, keys(i)%key, error)
            if (allocated(error)) return
            
        end do
                
    end subroutine new_collections