new_meta_config Subroutine

public subroutine new_meta_config(self, table, meta_allowed, error)

Construct a new build configuration from a TOML data structure

The toml table is not checked here because it already passed the “new_dependencies” check

Arguments

Type IntentOptional Attributes Name
type(metapackage_config_t), intent(out) :: self

Instance of the build configuration

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

Instance of the TOML data structure

logical, intent(in) :: meta_allowed(:)

List of keys allowed to be metapackages

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

Error handling


Source Code

    subroutine new_meta_config(self, table, meta_allowed, error)

        !> Instance of the build configuration
        type(metapackage_config_t), intent(out) :: self

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

        !> List of keys allowed to be metapackages
        logical, intent(in) :: meta_allowed(:)

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

        integer :: stat

        !> The toml table is not checked here because it already passed
        !> the "new_dependencies" check
        call new_meta_request(self%openmp, "openmp", table, meta_allowed, error)
        if (allocated(error)) return

        call new_meta_request(self%stdlib, "stdlib", table, meta_allowed, error)
        if (allocated(error)) return

        call new_meta_request(self%minpack, "minpack", table, meta_allowed, error)
        if (allocated(error)) return

        call new_meta_request(self%mpi, "mpi", table, meta_allowed, error)
        if (allocated(error)) return

    end subroutine new_meta_config