package_config_t Derived Type

type, public, extends(feature_config_t) :: package_config_t

Package meta data Package configuration data - extends a feature_config_t to represent the “default” package feature. The following are now inherited from feature_config_t: name (but for package it’s the package name), description, compiler, os_type (defaults to id_all, OS_ALL for packages) library, executable(:), dependency(:), dev_dependency(:), example(:), test(:), preprocess(:) flags, c_flags, cxx_flags, link_time_flags, requires_features(:)


Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: author
type(build_config_t), public, allocatable :: build

Build configuration

character(len=:), public, allocatable :: c_flags
character(len=:), public, allocatable :: copyright
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

type(feature_collection_t), public, allocatable :: features(:)

Additional feature collections beyond the default package feature

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 :: license

Package metadata (package-specific)

character(len=:), public, allocatable :: link_time_flags
character(len=:), public, allocatable :: maintainer
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(profile_config_t), public, allocatable :: profiles(:)

Profiles (collections of features)

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

Feature dependencies

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

Tests

type(version_t), public :: version

Package version (name is inherited from feature_config_t%name)


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 manifest to toml table

    Duplicate profile names are possible, as multiple profiles are possible with the same name, same compiler, etc. So, use a unique name here

    Arguments

    Type IntentOptional Attributes Name
    class(package_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 :: export_config

Export package configuration with features applied

  • private function export_config(self, platform, features) result(cfg)

    Export package configuration for a given (OS+compiler) platform

    Arguments

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

    Instance of the package configuration

    type(platform_config_t), intent(in) :: platform

    Target platform

    type(string_t), intent(in), optional :: features(:)

    Optional list of features to apply (currently idle)

    Return Value type(package_config_t)

procedure, public :: info

Print information on this instance

  • private subroutine info(self, unit, verbosity)

    Write information on instance

    Arguments

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

    Instance of the package 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 manifest from toml table (no checks made at this stage)

    Load base fields Read all packages

    Arguments

    Type IntentOptional Attributes Name
    class(package_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 => manifest_is_same

Serialization interface

  • private function manifest_is_same(this, that)

    All checks passed!

    Arguments

    Type IntentOptional Attributes Name
    class(package_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(feature_config_t) :: package_config_t

        !> Package version (name is inherited from feature_config_t%name)
        type(version_t) :: version

        !> Package metadata (package-specific)  
        character(len=:), allocatable :: license
        character(len=:), allocatable :: author
        character(len=:), allocatable :: maintainer
        character(len=:), allocatable :: copyright

        !> Additional feature collections beyond the default package feature
        type(feature_collection_t), allocatable :: features(:)

        !> Profiles (collections of features)
        type(profile_config_t), allocatable :: profiles(:)

    contains

        !> Print information on this instance
        procedure :: info

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

        !> Export package configuration with features applied
        procedure :: export_config

    end type package_config_t