new_features Subroutine

public subroutine new_features(features, table, root, error)

Construct new feature array from a TOML data structure

Arguments

Type IntentOptional Attributes Name
type(feature_config_t), intent(out), allocatable :: features(:)

Instance of the feature configuration array

type(toml_table), intent(inout) :: table

Instance of the TOML data structure

character(len=*), intent(in), optional :: root

Root directory of the manifest

type(error_t), intent(out), allocatable :: error

Error handling


Source Code

    subroutine new_features(features, table, root, error)

        !> Instance of the feature configuration array
        type(feature_config_t), allocatable, intent(out) :: features(:)

        !> Instance of the TOML data structure
        type(toml_table), intent(inout) :: table

        !> Root directory of the manifest
        character(len=*), intent(in), optional :: root

        !> Error handling
        type(error_t), allocatable, intent(out) :: error

        type(toml_table), pointer :: node
        type(toml_key), allocatable :: list(:)
        integer :: ifeature, stat

        call table%get_keys(list)

        if (size(list) < 1) then
            allocate(features(0))
            return
        end if

        allocate(features(size(list)))

        do ifeature = 1, size(list)
            call get_value(table, list(ifeature)%key, node, stat=stat)
            if (stat /= toml_stat%success) then
                call fatal_error(error, "Feature "//list(ifeature)%key//" must be a table entry")
                exit
            end if
            call new_feature(features(ifeature), node, root, error)
            if (allocated(error)) exit
        end do

    end subroutine new_features