feature_config_t Derived Type

type, public, extends(serializable_t) :: feature_config_t

Feature configuration data


Components

Type Visibility Attributes Name Initial
type(build_config_t), public, allocatable :: build

Build configuration

character(len=:), public, allocatable :: c_flags
character(len=:), public, allocatable :: cxx_flags
logical, public :: default = .false.

Is this feature enabled by default

type(dependency_config_t), public, allocatable :: dependency(:)

Dependencies

character(len=:), public, allocatable :: description
type(dependency_config_t), public, allocatable :: dev_dependency(:)

Development dependencies

type(example_config_t), public, allocatable :: example(:)

Examples

type(executable_config_t), public, allocatable :: executable(:)

Executable configurations

character(len=:), public, allocatable :: flags

Compiler flags

type(fortran_config_t), public, allocatable :: fortran

Fortran configuration

type(install_config_t), public, allocatable :: install

Installation configuration

type(library_config_t), public, allocatable :: library

Library configuration

character(len=:), public, allocatable :: link_time_flags
type(metapackage_config_t), public :: meta

Metapackage data

character(len=:), public, allocatable :: name

Feature identity

type(platform_config_t), public :: platform

Compiler/OS targeting (consistent with profile_config_t pattern)

type(preprocess_config_t), public, allocatable :: preprocess(:)

Preprocessor configuration

type(string_t), public, allocatable :: requires_features(:)

Feature dependencies

type(test_config_t), public, allocatable :: test(:)

Tests


Type-Bound Procedures

procedure, public, nopass :: check

Check validity of the TOML table

  • private subroutine check(table, error)

    Check local schema for allowed entries

    Arguments

    Type IntentOptional Attributes Name
    type(toml_table), intent(inout) :: table

    Instance of the TOML data structure

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

    Error handling

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit

  • private subroutine srcfile_dump_to_toml(self, table, error)

    Dump dependency to toml table

    Arguments

    Type IntentOptional Attributes Name
    class(srcfile_t), intent(inout) :: self

    Instance of the serializable object

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

    Data structure

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

    Error handling

  • private subroutine dump_to_file(self, file, error, json)

    Write serializable object to file

    Arguments

    Type IntentOptional Attributes Name
    class(serializable_t), intent(inout) :: self

    Instance of the dependency tree

    character(len=*), intent(in) :: file

    File name

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

    Error handling

    logical, intent(in), optional :: json

    Optional JSON format

  • private subroutine dump_to_unit(self, unit, error, json)

    Write serializable object to a formatted Fortran unit

    Arguments

    Type IntentOptional Attributes Name
    class(serializable_t), intent(inout) :: self

    Instance of the dependency tree

    integer, intent(in) :: unit

    Formatted unit

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

    Error handling

    logical, intent(in), optional :: json

    Optional JSON format requested?

procedure, public :: dump_to_toml

  • private subroutine dump_to_toml(self, table, error)

    Dump feature to toml table

    Because dependencies are named, fallback if this has no name So, serialization will work regardless of size(self%dep) == self%ndep
    Because dependencies are named, fallback if this has no name So, serialization will work regardless of size(self%dep) == self%ndep Because dependencies are named, fallback if this has no name So, serialization will work regardless of size(self%dep) == self%ndep Because dependencies are named, fallback if this has no name So, serialization will work regardless of size(self%dep) == self%ndep

    Arguments

    Type IntentOptional Attributes Name
    class(feature_config_t), intent(inout) :: self

    Instance of the serializable object

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

    Data structure

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

    Error handling

procedure, public :: info

Print information on this instance

  • private subroutine info(self, unit, verbosity)

    Write information on instance

    Arguments

    Type IntentOptional Attributes Name
    class(feature_config_t), intent(in) :: self

    Instance of the feature configuration

    integer, intent(in) :: unit

    Unit for IO

    integer, intent(in), optional :: verbosity

    Verbosity of the printout

generic, public :: load => load_from_toml, load_from_file, load_from_unit

  • private subroutine srcfile_load_from_toml(self, table, error)

    Read dependency from toml table (no checks made at this stage)

    Arguments

    Type IntentOptional Attributes Name
    class(srcfile_t), intent(inout) :: self

    Instance of the serializable object

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

    Data structure

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

    Error handling

  • private subroutine load_from_file(self, file, error, json)

    Read dependency tree from file

    Arguments

    Type IntentOptional Attributes Name
    class(serializable_t), intent(inout) :: self

    Instance of the dependency tree

    character(len=*), intent(in) :: file

    File name

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

    Error handling

    logical, intent(in), optional :: json

    Optional JSON format

  • private subroutine load_from_unit(self, unit, error, json)

    Read dependency tree from file init JSON interpreter Read object from TOML table

    use default TOML parser

    Read object from TOML table

    Arguments

    Type IntentOptional Attributes Name
    class(serializable_t), intent(inout) :: self

    Instance of the dependency tree

    integer, intent(in) :: unit

    File name

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

    Error handling

    logical, intent(in), optional :: json

    Optional JSON format

procedure, public :: load_from_toml

  • private subroutine load_from_toml(self, table, error)

    Read feature from toml table (no checks made at this stage)

    Read all packages Read all packages Read all packages Read all packages Read all packages Read all packages

    Arguments

    Type IntentOptional Attributes Name
    class(feature_config_t), intent(inout) :: self

    Instance of the serializable object

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

    Data structure

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

    Error handling

procedure, public :: manifest_name

Get manifest name

  • private function manifest_name(self) result(name)

    Return a name string as it would appear in the TOML manifest

    Arguments

    Type IntentOptional Attributes Name
    class(feature_config_t), intent(in) :: self

    Return Value character(len=:), allocatable

generic, public :: operator(==) => serializable_is_same

  • private function srcfile_is_same(this, that)

    Check that two source files are equal All checks passed!

    Arguments

    Type IntentOptional Attributes Name
    class(srcfile_t), intent(in) :: this
    class(serializable_t), intent(in) :: that

    Return Value logical

procedure, public :: serializable_is_same => feature_is_same

Serialization interface

  • private function feature_is_same(this, that)

    Check that two feature configs are equal

    Arguments

    Type IntentOptional Attributes Name
    class(feature_config_t), intent(in) :: this
    class(serializable_t), intent(in) :: that

    Return Value logical

procedure, public, non_overridable :: test_serialization

Test load/write roundtrip

  • private subroutine test_serialization(self, message, error)

    Test serialization of a serializable object Dump to scratch file Load from scratch file Check same

    Arguments

    Type IntentOptional Attributes Name
    class(serializable_t), intent(inout) :: self
    character(len=*), intent(in) :: message
    type(error_t), intent(out), allocatable :: error

Source Code

    type, extends(serializable_t) :: feature_config_t

        !> Feature identity  
        character(len=:), allocatable :: name
        character(len=:), allocatable :: description
        
        !> Compiler/OS targeting (consistent with profile_config_t pattern)
        type(platform_config_t) :: platform
        
        !> Build configuration
        type(build_config_t), allocatable :: build
        
        !> Installation configuration
        type(install_config_t), allocatable :: install
        
        !> Fortran configuration
        type(fortran_config_t), allocatable :: fortran
        
        !> Library configuration
        type(library_config_t), allocatable :: library
        
        !> Executable configurations
        type(executable_config_t), allocatable :: executable(:)
        
        !> Dependencies
        type(dependency_config_t), allocatable :: dependency(:)
        
        !> Development dependencies
        type(dependency_config_t), allocatable :: dev_dependency(:)
        
        !> Examples
        type(example_config_t), allocatable :: example(:)
        
        !> Tests
        type(test_config_t), allocatable :: test(:)
        
        !> Preprocessor configuration
        type(preprocess_config_t), allocatable :: preprocess(:)
        
        !> Metapackage data
        type(metapackage_config_t) :: meta        
        
        !> Compiler flags  
        character(len=:), allocatable :: flags
        character(len=:), allocatable :: c_flags  
        character(len=:), allocatable :: cxx_flags
        character(len=:), allocatable :: link_time_flags
        
        !> Feature dependencies
        type(string_t), allocatable :: requires_features(:)
        
        !> Is this feature enabled by default
        logical :: default = .false.
        
    contains

        !> Print information on this instance
        procedure :: info
        
        !> Check validity of the TOML table
        procedure, nopass :: check
        
        !> Get manifest name
        procedure :: manifest_name

        !> Serialization interface
        procedure :: serializable_is_same => feature_is_same
        procedure :: dump_to_toml
        procedure :: load_from_toml

    end type feature_config_t