package_config_t Derived Type

type, public, extends(serializable_t) :: package_config_t

Package meta data


Components

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

Author meta data

type(build_config_t), public :: build

Build configuration data

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

Copyright meta data

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

Dependency meta data

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

Development dependency meta data

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

Example meta data

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

Executable meta data

type(fortran_config_t), public :: fortran

Fortran meta data

type(install_config_t), public :: install

Installation configuration data

type(library_config_t), public, allocatable :: library

Library meta data

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

License meta data

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

Maintainer meta data

type(metapackage_config_t), public :: meta

Metapackage data

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

Name of the package

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

Preprocess meta data

type(profile_config_t), public, allocatable :: profiles(:)

Profiles meta data

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

Test meta data

type(version_t), public :: version

Package version


Type-Bound Procedures

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

    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 Duplicate profile names are possible, as multiple profiles are possible with the same name, same compiler, etc. So, use a unique name here 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(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 :: 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)

    Read all packages Read all packages Read all packages Read all packages Read all packages Read all packages 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

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(serializable_t) :: package_config_t

        !> Name of the package
        character(len=:), allocatable :: name

        !> Package version
        type(version_t) :: version

        !> Build configuration data
        type(build_config_t) :: build

        !> Metapackage data
        type(metapackage_config_t) :: meta

        !> Installation configuration data
        type(install_config_t) :: install

        !> Fortran meta data
        type(fortran_config_t) :: fortran

        !> License meta data
        character(len=:), allocatable :: license

        !> Author meta data
        character(len=:), allocatable :: author

        !> Maintainer meta data
        character(len=:), allocatable :: maintainer

        !> Copyright meta data
        character(len=:), allocatable :: copyright

        !> Library meta data
        type(library_config_t), allocatable :: library

        !> Executable meta data
        type(executable_config_t), allocatable :: executable(:)

        !> Dependency meta data
        type(dependency_config_t), allocatable :: dependency(:)

        !> Development dependency meta data
        type(dependency_config_t), allocatable :: dev_dependency(:)

        !> Profiles meta data
        type(profile_config_t), allocatable :: profiles(:)

        !> Example meta data
        type(example_config_t), allocatable :: example(:)

        !> Test meta data
        type(test_config_t), allocatable :: test(:)

        !> Preprocess meta data
        type(preprocess_config_t), allocatable :: preprocess(:)

    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

    end type package_config_t