fpm_toml Module

Interface to TOML processing library

This module acts as a proxy to the toml-f public Fortran API and allows to selectively expose components from the library to fpm. The interaction with toml-f data types outside of this module should be limited to tables, arrays and key-lists, most of the necessary interactions are implemented in the building interface with the get_value and set_value procedures.

This module allows to implement features necessary for fpm, which are not yet available in upstream toml-f.

For more details on the library used see the TOML-Fortran developer pages.


Uses


Interfaces

public interface add_table

add_table: fpm interface

  • private subroutine add_table_fpm(table, key, ptr, error, whereAt)

    Function wrapper to add a toml table and return an fpm error

    Nullify pointer

    Arguments

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

    Instance of the TOML data structure

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

    Table key

    type(toml_table), intent(out), pointer :: ptr

    The character variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

public interface get_value

get_value: fpm interface

  • private subroutine get_logical(table, key, var, error, whereAt)

    Function wrapper to get a logical variable from a toml table, returning an fpm error

    Arguments

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

    Instance of the TOML data structure

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

    The key

    logical, intent(inout) :: var

    The variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

  • private subroutine get_integer(table, key, var, error, whereAt)

    Function wrapper to get a default integer variable from a toml table, returning an fpm error

    Arguments

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

    Instance of the TOML data structure

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

    The key

    integer, intent(inout) :: var

    The variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

  • private subroutine get_integer_64(table, key, var, error, whereAt)

    Function wrapper to get a integer(int64) variable from a toml table, returning an fpm error

    Arguments

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

    Instance of the TOML data structure

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

    The key

    integer(kind=int64), intent(inout) :: var

    The variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

public interface set_string

  • private subroutine set_character(table, key, var, error, whereAt)

    Function wrapper to set a character(len=:), allocatable variable to a toml table

    Check the key is not empty

    Arguments

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

    Instance of the TOML data structure

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

    List of keys to check.

    character(len=*), intent(in), optional :: var

    The character variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

  • private subroutine set_string_type(table, key, var, error, whereAt)

    Function wrapper to set a character(len=:), allocatable variable to a toml table

    Arguments

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

    Instance of the TOML data structure

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

    List of keys to check.

    type(string_t), intent(in) :: var

    The character variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

public interface set_value

set_value: fpm interface

  • private subroutine set_logical(table, key, var, error, whereAt)

    Function wrapper to set a logical variable to a toml table, returning an fpm error

    Arguments

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

    Instance of the TOML data structure

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

    The key

    logical, intent(in) :: var

    The variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

  • private subroutine set_integer(table, key, var, error, whereAt)

    Function wrapper to set a default integer variable to a toml table, returning an fpm error

    Arguments

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

    Instance of the TOML data structure

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

    The key

    integer, intent(in) :: var

    The variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description

  • private subroutine set_integer_64(table, key, var, error, whereAt)

    Function wrapper to set a default integer variable to a toml table, returning an fpm error

    Arguments

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

    Instance of the TOML data structure

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

    The key

    integer(kind=int64), intent(in) :: var

    The variable

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

    Error handling

    character(len=*), intent(in), optional :: whereAt

    Optional description


Derived Types

type, public, abstract ::  serializable_t

An abstract interface for any fpm class that should be fully serializable to/from TOML/JSON

Type-Bound Procedures

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit
procedure(to_toml), public, deferred :: dump_to_toml ../../

Dump to TOML table, unit, file

generic, public :: load => load_from_toml, load_from_file, load_from_unit
procedure(from_toml), public, deferred :: load_from_toml ../../

Load from TOML table, unit, file

generic, public :: operator(==) => serializable_is_same
procedure(is_equal), public, deferred :: serializable_is_same ../../

Serializable entities need a way to check that they’re equal

procedure, public, non_overridable :: test_serialization ../../

Test load/write roundtrip


Functions

public function name_is_json(filename)

Choose between JSON or TOML based on a file name

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename

Return Value logical


Subroutines

public subroutine check_keys(table, valid_keys, error)

Check if table contains only keys that are part of the list. If a key is found that is not part of the list, an error is allocated.

Arguments

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

Instance of the TOML data structure

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

List of keys to check.

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

Error handling

public subroutine get_list(table, key, list, error)

Arguments

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

Instance of the TOML data structure

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

Key to read from

type(string_t), intent(out), allocatable :: list(:)

List of strings to read

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

Error handling

public subroutine read_package_file(table, manifest, error)

Process the configuration file to a TOML data structure

Arguments

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

TOML data structure

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

Name of the package configuration file

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

Error status of the operation

public subroutine set_list(table, key, list, error)

Set no key if array is not present

Read more…

Arguments

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

Instance of the toml table

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

Key to save to

type(string_t), intent(in), allocatable :: list(:)

Instance of the string array

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

Error handling