metapackage_t Derived Type

type, public :: metapackage_t

Type for describing a source file


Components

Type Visibility Attributes Name Initial
type(string_t), public :: cflags
type(string_t), public :: cxxflags
type(dependency_config_t), public, allocatable :: dependency(:)

List of Development dependency meta data. Metapackage dependencies are never exported from the model

type(string_t), public, allocatable :: external_modules(:)
type(string_t), public :: fflags
type(string_t), public :: flags

List of compiler flags and options to be added

type(fortran_features_t), public, allocatable :: fortran

Special fortran features

logical, public :: has_build_flags = .false.
logical, public :: has_c_flags = .false.
logical, public :: has_cxx_flags = .false.
logical, public :: has_dependencies = .false.
logical, public :: has_external_modules = .false.
logical, public :: has_fortran_flags = .false.
logical, public :: has_include_dirs = .false.
logical, public :: has_link_flags = .false.
logical, public :: has_link_libraries = .false.
logical, public :: has_run_command = .false.
type(string_t), public, allocatable :: incl_dirs(:)
type(string_t), public :: link_flags
type(string_t), public, allocatable :: link_libs(:)
type(string_t), public :: run_command
type(version_t), public, allocatable :: version

Package version (if supported)


Type-Bound Procedures

procedure, public :: destroy

Clean metapackage structure

  • public elemental subroutine destroy(this)

    Arguments

    Type IntentOptional Attributes Name
    class(metapackage_t), intent(inout) :: this

generic, public :: resolve => resolve_cmd, resolve_model, resolve_package_config

  • private subroutine resolve_cmd(self, settings, error)

    Resolve metapackage dependencies into the command line settings

    Arguments

    Type IntentOptional Attributes Name
    class(metapackage_t), intent(in) :: self
    class(fpm_cmd_settings), intent(inout) :: settings
    type(error_t), intent(out), allocatable :: error
  • private subroutine resolve_model(self, model, error)

    Resolve metapackage dependencies into the model

    Arguments

    Type IntentOptional Attributes Name
    class(metapackage_t), intent(in) :: self
    type(fpm_model_t), intent(inout) :: model
    type(error_t), intent(out), allocatable :: error
  • private subroutine resolve_package_config(self, package, error)

    Arguments

    Type IntentOptional Attributes Name
    class(metapackage_t), intent(in) :: self
    type(package_config_t), intent(inout) :: package
    type(error_t), intent(out), allocatable :: error

Source Code

    type, public :: metapackage_t

    !> Package version (if supported)
    type(version_t), allocatable :: version

        logical :: has_link_libraries   = .false.
        logical :: has_link_flags       = .false.
        logical :: has_build_flags      = .false.
        logical :: has_fortran_flags    = .false.
        logical :: has_c_flags          = .false.
        logical :: has_cxx_flags        = .false.
        logical :: has_include_dirs     = .false.
        logical :: has_dependencies     = .false.
        logical :: has_run_command      = .false.
        logical :: has_external_modules = .false.

        !> List of compiler flags and options to be added
        type(string_t) :: flags
        type(string_t) :: fflags
        type(string_t) :: cflags
        type(string_t) :: cxxflags
        type(string_t) :: link_flags
        type(string_t) :: run_command
        type(string_t), allocatable :: incl_dirs(:)
        type(string_t), allocatable :: link_libs(:)
        type(string_t), allocatable :: external_modules(:)

        !> Special fortran features
        type(fortran_features_t), allocatable :: fortran

        !> List of Development dependency meta data.
        !> Metapackage dependencies are never exported from the model
        type(dependency_config_t), allocatable :: dependency(:)

        contains

            !> Clean metapackage structure
            procedure :: destroy

            !> Add metapackage dependencies to the model
            procedure, private :: resolve_cmd
            procedure, private :: resolve_model
            procedure, private :: resolve_package_config
            generic :: resolve => resolve_cmd,resolve_model,resolve_package_config

    end type metapackage_t