Working with tables#

The central data structures in TOML are tables, they contain a map from a key (string) to any supported data type in TOML. These recipes describe common scenarios for retrieving data from tables using the TOML Fortran library.

Accessing nested tables#

Using nested tables provides the possibility to better group configuration data. Since the TOML format always requires the full qualified path in each table header, it is easy for the user to identify where the current settings belong to. On the other hand, deeply nested tables with long table paths or path components make them more difficult to use and a good balance of short and expressive table names and meaningful subtables is required.

An example of an electronic structure code implementing different Hamiltonians is given below.

[hamiltonian.dftb]
scc = {}
skf.format = "mio-1-1/{}-{}.skf"

[analysis]
calculate-forces = true

The deepest nested subtable with entries in this example is the hamiltonian.dftb.skf path.

Such layout in the configuration file will usually be mirrored in the actual implementation, with every table corresponding to a derived type describing the input. For the example above in total six derived types for the individual tables are defined as

src/input.f90#
  !> Input for the Slater-Koster integral tables
  type :: skf_input
    !> Format string to find Slater-Koster files
    character(len=:), allocatable :: format_string
    ! ... more settings for the Slater-Koster input
  end type skf_input

  !> Input for the self-consistent charge iterations
  type :: scc_input
    !> Convergence tolerance for energy minimization
    real :: tolerance
    ! ... more settings for the SCC input
  end type scc_input

  !> Input for DFTB Hamiltonian
  type :: dftb_input
    !> Self-consistent field specific settings
    type(scc_input), allocatable :: scc
    !> Slater-Koster table specific settings
    type(skf_input) :: skf
    ! ... more settings for the DFTB input
  end type dftb_input

  !> Input for the Hamiltonian used in the simulation
  type :: hamiltonian_input
    !> DFTB Hamiltonian specific settings
    type(dftb_input), allocatable :: dftb
    ! ... more settings for the Hamiltonian input
  end type hamiltonian_input

  !> Input for analysis of Hamiltonian
  type :: analysis_input
    !> Evaluate derivatives of energy expression
    logical :: calculate_forces
    ! ... more settings for the analysis input
  end type analysis_input

  !> Input for complete simulation
  type :: simulation_input
    !> Hamiltonian used for simulation, always needed
    type(hamiltonian_input) :: hamiltonian
    !> Analysis to run after successful Hamiltonian evaluation
    type(analysis_input), allocatable :: analysis
    ! ... more settings for the simulation input
  end type simulation_input

Note

The representation in Fortran derived types looks lengthy compared to the actual TOML input. Consider that the 40 lines of Fortran code contain 50% comments describing the data types briefly for (future) developers. Of course, the user documentation of the input format will be much more extensive, containing descriptions for every table and every entry, including input ranges and unit conventions. The final input file provided by the user can be brief and expressive.

Staring with the root of the table which is read in the simulation_input there are two ways to obtain access to a subtable, first we get the hamiltonian subtable, which we defined as mandatory, using the get_value interface. In case it is present a reference will be returned in the child pointer. If no table is available in the input TOML Fortran will insert it into the root table and return the reference to the newly created table. The child pointer can still be unassigned in case invalid input is provided, which will result in raising an error in the implementation shown below.

The alternative is to explicitly mark the subtable as optional, like for the analysis table, if no table is available or the entry is invalid the child pointer will not be assigned. To differentiate those cases we can request the status information, check whether the operation was successful, and cleanly handle the error case.

src/input.f90#
  !> Read root document
  subroutine read_simulation(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Simulation input to be read
    type(simulation_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    type(toml_table), pointer :: child
    integer :: stat

    call get_value(table, "hamiltonian", child)
    if (.not.associated(child)) then
      call fatal_error(error, "No hamiltonian section found in input file")
      return
    end if
    call read_hamiltonian(error, input%hamiltonian, child)
    if (allocated(error)) return

    call get_value(table, "analysis", child, requested=.false., stat=stat)
    if (stat /= toml_stat%success) then
      call fatal_error(error, "No analysis section found in input file")
      return
    end if
    if (associated(child)) then
      allocate(input%analysis)
      call read_analysis(error, input%analysis, child)
      if (allocated(error)) return
    end if

    ! ... read further values
  end subroutine read_simulation

The same happens for reading the hamiltonian_input and dftb_input entry.

src/input.f90#
  !> Read Hamiltonian from node
  subroutine read_hamiltonian(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Hamiltonian input to be read
    type(hamiltonian_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    type(toml_table), pointer :: child

    call get_value(table, "dftb", child, requested=.false.)
    if (associated(child)) then
      allocate(input%dftb)
      call read_dftb(error, input%dftb, child)
      if (allocated(error)) return
    end if

    ! ... read further values
  end subroutine read_hamiltonian

  !> Read DFTB Hamiltonian from node
  subroutine read_dftb(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> DFTB Hamiltonian input to be read
    type(dftb_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    type(toml_table), pointer :: child

    call get_value(table, "scc", child, requested=.false.)
    if (associated(child)) then
      allocate(input%scc)
      call read_scc(error, input%scc, child)
      if (allocated(error)) return
    end if

    call get_value(table, "skf", child)
    if (.not.associated(child)) then
      call fatal_error(error, "No skf section found in dftb table")
      return
    end if
    call read_skf(error, input%skf, child)
    if (allocated(error)) return

    ! ... read further values
  end subroutine read_dftb

Finally, we can implement reading the terminal subtables into the scc_input, skf_input, and analysis_input, where we retrieve the actual values using the get_value interface. Note that we can conveniently define default values using the get_value interface. For proper error handling, we can retrieve the optional stat argument as well.

src/input.f90#
  !> Read SCC from node
  subroutine read_scc(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> SCC input to be read
    type(scc_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    call get_value(table, "tolerance", input%tolerance, 1.0e-6)
    ! ... read further values
  end subroutine read_scc

  !> Read Slater-Koster files from node
  subroutine read_skf(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Slater-Koster input to be read
    type(skf_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    call get_value(table, "format-string", input%format_string, "{}-{}.skf")
    ! ... read further values
  end subroutine read_skf

  !> Read analysis from node
  subroutine read_analysis(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Analysis input to be read
    type(analysis_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    call get_value(table, "calculate-forces", input%calculate_forces, .false.)
    ! ... read further values
  end subroutine read_analysis

For the small incomplete input as shown here, the fine-grained substructure seems overengineered and could be fully defined in the reading routine for the document root as well. However, for larger program inputs such a structure can help to ensure that input readers are properly modular and reusable.

Tip

The allocation status of a component of the derived type can be used instead of a separate boolean flag to indicate whether a feature should be activated. This avoids requiring conditional code inside a reader routine for conditionally handling entries depending on a boolean flag, instead they can be collected in a subtable.

Full source code

The full module implementing the simulation_input reading

src/input.f90#
!> Input model for a computational chemistry simulation program
module demo_input
  use demo_error, only : error_type
  use tomlf, only : toml_table, toml_stat, get_value
  implicit none
  private

  public :: simulation_input

  !> Input for the Slater-Koster integral tables
  type :: skf_input
    !> Format string to find Slater-Koster files
    character(len=:), allocatable :: format_string
    ! ... more settings for the Slater-Koster input
  end type skf_input

  !> Input for the self-consistent charge iterations
  type :: scc_input
    !> Convergence tolerance for energy minimization
    real :: tolerance
    ! ... more settings for the SCC input
  end type scc_input

  !> Input for DFTB Hamiltonian
  type :: dftb_input
    !> Self-consistent field specific settings
    type(scc_input), allocatable :: scc
    !> Slater-Koster table specific settings
    type(skf_input) :: skf
    ! ... more settings for the DFTB input
  end type dftb_input

  !> Input for the Hamiltonian used in the simulation
  type :: hamiltonian_input
    !> DFTB Hamiltonian specific settings
    type(dftb_input), allocatable :: dftb
    ! ... more settings for the Hamiltonian input
  end type hamiltonian_input

  !> Input for analysis of Hamiltonian
  type :: analysis_input
    !> Evaluate derivatives of energy expression
    logical :: calculate_forces
    ! ... more settings for the analysis input
  end type analysis_input

  !> Input for complete simulation
  type :: simulation_input
    !> Hamiltonian used for simulation, always needed
    type(hamiltonian_input) :: hamiltonian
    !> Analysis to run after successful Hamiltonian evaluation
    type(analysis_input), allocatable :: analysis
    ! ... more settings for the simulation input
  end type simulation_input

contains

  !> Read root document
  subroutine read_simulation(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Simulation input to be read
    type(simulation_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    type(toml_table), pointer :: child
    integer :: stat

    call get_value(table, "hamiltonian", child)
    if (.not.associated(child)) then
      call fatal_error(error, "No hamiltonian section found in input file")
      return
    end if
    call read_hamiltonian(error, input%hamiltonian, child)
    if (allocated(error)) return

    call get_value(table, "analysis", child, requested=.false., stat=stat)
    if (stat /= toml_stat%success) then
      call fatal_error(error, "No analysis section found in input file")
      return
    end if
    if (associated(child)) then
      allocate(input%analysis)
      call read_analysis(error, input%analysis, child)
      if (allocated(error)) return
    end if

    ! ... read further values
  end subroutine read_simulation

  !> Read Hamiltonian from node
  subroutine read_hamiltonian(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Hamiltonian input to be read
    type(hamiltonian_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    type(toml_table), pointer :: child

    call get_value(table, "dftb", child, requested=.false.)
    if (associated(child)) then
      allocate(input%dftb)
      call read_dftb(error, input%dftb, child)
      if (allocated(error)) return
    end if

    ! ... read further values
  end subroutine read_hamiltonian

  !> Read DFTB Hamiltonian from node
  subroutine read_dftb(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> DFTB Hamiltonian input to be read
    type(dftb_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    type(toml_table), pointer :: child

    call get_value(table, "scc", child, requested=.false.)
    if (associated(child)) then
      allocate(input%scc)
      call read_scc(error, input%scc, child)
      if (allocated(error)) return
    end if

    call get_value(table, "skf", child)
    if (.not.associated(child)) then
      call fatal_error(error, "No skf section found in dftb table")
      return
    end if
    call read_skf(error, input%skf, child)
    if (allocated(error)) return

    ! ... read further values
  end subroutine read_dftb

  !> Read SCC from node
  subroutine read_scc(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> SCC input to be read
    type(scc_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    call get_value(table, "tolerance", input%tolerance, 1.0e-6)
    ! ... read further values
  end subroutine read_scc

  !> Read Slater-Koster files from node
  subroutine read_skf(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Slater-Koster input to be read
    type(skf_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    call get_value(table, "format-string", input%format_string, "{}-{}.skf")
    ! ... read further values
  end subroutine read_skf

  !> Read analysis from node
  subroutine read_analysis(error, input, table)
    !> Error handler
    type(error_type), allocatable :: error
    !> Analysis input to be read
    type(analysis_input), intent(out) :: input
    !> Data structure
    type(toml_table), intent(inout) :: table

    call get_value(table, "calculate-forces", input%calculate_forces, .false.)
    ! ... read further values
  end subroutine read_analysis

end module demo_input

The auxiliary module providing the error handler

src/error.f90#
!> Central registry for error codes
module demo_error
  implicit none
  private

  public :: error_type, fatal_error

  !> Possible error codes
  type :: enum_stat
    !> Successful run
    integer :: success = 0
    !> Internal error:
    integer :: fatal = 1
  end type enum_stat

  !> Actual enumerator for return states
  type(enum_stat), parameter :: demo_stat = enum_stat()

  !> Error message
  type :: error_type
    !> Error code
    integer :: stat
    !> Payload of the error
    character(len=:), allocatable :: message
  end type error_type

contains

  !> A fatal error is encountered
  subroutine fatal_error(error, message, stat)
    !> Instance of the error
    type(error_type), allocatable, intent(out) :: error
    !> A detailed message describing the error and (optionally) offering advice
    character(len=*), intent(in), optional :: message
    !> Overwrite of the error code
    integer, intent(in), optional :: stat

    allocate(error)

    if (present(stat)) then
      error%stat = stat
    else
      error%stat = demo_stat%fatal
    end if

    if (present(message)) then
      error%message = message
    else
      error%message = "Fatal error"
    end if
  end subroutine fatal_error

end module demo_error

Direct access via key paths#

If only a deeply nested value of a data structure is needed it can be retrieved by using a key path. The build interface will internally walk the key path, resolve the child tables and create them as necessary.

Warning

Repeatly accessing values via a key path from the document root, rather than retrieving the reference the desired child table, will introduce an overhead each time the key path is resolved.

For the previous example we can use the key path access to retrieve the most deeply nested value as shown below.

block
  use tomlf, only : get_value, toml_path, toml_key
  character(:), allocatable :: format_string

  call get_value(table, toml_path("hamiltonian", "dftb", "skf", "format"), format_string)
end block

Similar like other build interfaces it can be used to create the subtables as well as the string value by providing a default.

Iterating over keys#

An expressive way to organize data is by providing a table where the keys of each entry describe the object that should be initialized. For example in a package manager, the keys represent the dependency, where each dependency is declared in a subtable. Furthermore, a convenience feature might be the possibility to just provide a string, which is interpreted as a version subentry.

The final usage of this in a requirements table could look like the snippet shown below.

[requirements]
stdlib = "^0.2.1"
toml = "^1.0.0"
cli2 = "^3.1.0"
lapack.version = "^3.10.1"
lapack.variant = "mkl|openblas"
minpack = {git="https://github.com/fortran-lang/minpack@v2.0.0"}

The first three entries provide a string value, while the fourth entry provides a subtable implicitly by using dotted key-value pairs and the last entry uses an inline table.

Here we want to focus on the iteration and the default initialization, the internal structure of the requirement_type is secondary for this example. We provide the minimal definition only holding the name of the dependency for demonstration purposes.

src/requirements.f90#
  !> Declaration of a dependency
  type :: requirement_type
    !> Name to identify dependency
    character(len=:), allocatable :: name
    ! ... further declaration of entries
  end type requirement_type

For the actual implementation of reading all entries from the table, we will use a one-dimensional array of requirement_type values. Using the get_keys method of the table we can obtain a list of all keys for the current table, the method will always allocate the list variable and we can safely allocate the requirement_type using the number of keys. To obtain the subtable, the get_value interface can be used, it will return a pointer to the subtable, either created implicitly by using a dotted key-value pair or by an inline table as shown in the snippet above. Finally, we can call the actual constructor of the requirement_type using the subtable references with the child pointer.

src/requirements.f90#
  !> Create a new list of requirements from a table
  subroutine new_requirements(error, table, req)
    !> Error handling
    type(error_type), allocatable, intent(out) :: error
    !> TOML data structure
    type(toml_table), intent(inout) :: table
    !> List of all dependencies
    type(requirement_type), allocatable, intent(out) :: req(:)

    integer :: ikey
    type(toml_key), allocatable :: list(:)
    type(toml_table), pointer :: child
    type(toml_table), allocatable, target :: dummy
    character(len=:), allocatable :: version

    ! Get all entries of current table, the `list` is guaranteed to be allocated
    call table%get_keys(list)
    allocate(req(size(list)))

    do ikey = 1, size(list)
      call get_value(table, list(ikey), child)

      ! Not providing a subtable is okay if a string provides the version constraint
      if (.not. associated(child)) then
        call get_value(table, list(ikey), version)
        if (.not.allocated(version)) then
          call fatal_error(error, "Requirement '"//list(ikey)%key//&
            & "' must be version constraint or subtable")
          exit
        end if

        ! Create a dummy table we can reference when initializing
        dummy = toml_table()
        call set_value(dummy, "version", version)
        child => dummy
      end if

      ! Initialize dependency from subtable
      call new_requirement(error, child, req(ikey), list(ikey)%key)

      ! Cleanup, alternatively the dummy could be pushed back into the main table
      if (allocated(dummy)) deallocate(dummy)
      ! Leave loop in case of error
      if (allocated(error)) exit
    end do
    ! Requirements are in a half-finished state, invalidate them to avoid confusion
    if (allocated(error)) deallocate(req)
  end subroutine new_requirements

The other scenario we want to support is the presence of a string rather than a subtable. In this case, the get_value interface will fail, while it provides an optional status argument to check for successful operation, we can more conveniently and idiomatically verify the success by checking the state of the child pointer. If there is no subtable to reference, i.e. because it is a key-value pair with a string entry, the child pointer will not be associated, which can be easily checked. For this case we will again use the get_value interface, but this time to retrieve the entry into a deferred length character. Again we can idiomatically check the status of the operation using the allocation state of the variable and create the appropriate error message if needed. Eventually, we have to provide the constructor of the requirements with a table, for this purpose we create a dummy table and set the entry at the version key to the just retrieved string. The newly created dummy table can be associated with the child pointer and passed to the actual constructor.

The actual constructor for our example is very minimalistic and only recovers the name of the dependency which is passed as a separate argument.

src/requirements.f90#
  !> Initialize a dependency from a TOML data structure
  subroutine new_requirement(error, table, req, name)
    !> Error handling
    type(error_type), allocatable, intent(out) :: error
    !> TOML data structure
    type(toml_table), intent(inout) :: table
    !> New dependency object
    type(requirement_type), intent(out) :: req
    !> Name of the dependency
    character(len=*), intent(in) :: name

    req%name = name
    ! ... further reading of entries
  end subroutine new_requirement

Note

While we provide an error handler in the example, we also ensure that the allocation status of the requirement_type values communicates the status of the operation as well.

Full source code

The full module implementing the requirement_type reading

src/requirements.f90#
!> Defines a simple dependency type to express requirements of a project.
module demo_requirements
  use demo_error, only : error_type, fatal_error
  use tomlf, only : toml_table, toml_key, get_value, set_value
  implicit none
  private

  public :: requirement_type, new_requirement, new_requirements

  !> Declaration of a dependency
  type :: requirement_type
    !> Name to identify dependency
    character(len=:), allocatable :: name
    ! ... further declaration of entries
  end type requirement_type

contains

  !> Create a new list of requirements from a table
  subroutine new_requirements(error, table, req)
    !> Error handling
    type(error_type), allocatable, intent(out) :: error
    !> TOML data structure
    type(toml_table), intent(inout) :: table
    !> List of all dependencies
    type(requirement_type), allocatable, intent(out) :: req(:)

    integer :: ikey
    type(toml_key), allocatable :: list(:)
    type(toml_table), pointer :: child
    type(toml_table), allocatable, target :: dummy
    character(len=:), allocatable :: version

    ! Get all entries of current table, the `list` is guaranteed to be allocated
    call table%get_keys(list)
    allocate(req(size(list)))

    do ikey = 1, size(list)
      call get_value(table, list(ikey), child)

      ! Not providing a subtable is okay if a string provides the version constraint
      if (.not. associated(child)) then
        call get_value(table, list(ikey), version)
        if (.not.allocated(version)) then
          call fatal_error(error, "Requirement '"//list(ikey)%key//&
            & "' must be version constraint or subtable")
          exit
        end if

        ! Create a dummy table we can reference when initializing
        dummy = toml_table()
        call set_value(dummy, "version", version)
        child => dummy
      end if

      ! Initialize dependency from subtable
      call new_requirement(error, child, req(ikey), list(ikey)%key)

      ! Cleanup, alternatively the dummy could be pushed back into the main table
      if (allocated(dummy)) deallocate(dummy)
      ! Leave loop in case of error
      if (allocated(error)) exit
    end do
    ! Requirements are in a half-finished state, invalidate them to avoid confusion
    if (allocated(error)) deallocate(req)
  end subroutine new_requirements

  !> Initialize a dependency from a TOML data structure
  subroutine new_requirement(error, table, req, name)
    !> Error handling
    type(error_type), allocatable, intent(out) :: error
    !> TOML data structure
    type(toml_table), intent(inout) :: table
    !> New dependency object
    type(requirement_type), intent(out) :: req
    !> Name of the dependency
    character(len=*), intent(in) :: name

    req%name = name
    ! ... further reading of entries
  end subroutine new_requirement

end module demo_requirements

The auxiliary module providing the error handler

src/error.f90#
!> Central registry for error codes
module demo_error
  implicit none
  private

  public :: error_type, fatal_error

  !> Possible error codes
  type :: enum_stat
    !> Successful run
    integer :: success = 0
    !> Internal error:
    integer :: fatal = 1
  end type enum_stat

  !> Actual enumerator for return states
  type(enum_stat), parameter :: demo_stat = enum_stat()

  !> Error message
  type :: error_type
    !> Error code
    integer :: stat
    !> Payload of the error
    character(len=:), allocatable :: message
  end type error_type

contains

  !> A fatal error is encountered
  subroutine fatal_error(error, message, stat)
    !> Instance of the error
    type(error_type), allocatable, intent(out) :: error
    !> A detailed message describing the error and (optionally) offering advice
    character(len=*), intent(in), optional :: message
    !> Overwrite of the error code
    integer, intent(in), optional :: stat

    allocate(error)

    if (present(stat)) then
      error%stat = stat
    else
      error%stat = demo_stat%fatal
    end if

    if (present(message)) then
      error%message = message
    else
      error%message = "Fatal error"
    end if
  end subroutine fatal_error

end module demo_error

Array of tables#

A special construct in TOML is the array of tables syntax, it provides a more verbose form to declare several tables in an array, which are usually provided using inline tables as shown below.

tasks = [
   {name="optimization", driver="lbfgs"},
   {name="equilibration", driver="velocity-verlet"},
   {name="production", driver="velocity-verlet"},
]

Comparing the above example to the snippet below using an array of tables for the tasks array, the more verbose form becomes preferable in case further subtables are needed. Except for the subtables config the same data is provided.

[[tasks]]
name = "optimization"
driver = "lbfgs"
[task.config]
tolerance = 1.0e-7

[[tasks]]
name = "equilibration"
driver = "velocity-verlet"
[task.config]
time-step = 1.0
temperature = 300.0
max-steps = 500

[[tasks]]
name = "production"
driver = "velocity-verlet"
[task.config]
time-step = 1.0
temperature = 300.0
max-steps = 10000

To represent this data we can use a single task_config derived type with a polymorphic driver_config member identifying the actual task. For this example, we will have two implementations of such tasks such as LBFGS and Velocity Verlet, which are defined in the following snippets.

src/task.f90#
  !> Abstract base class for all simulation driver configurations
  type, abstract :: driver_config
  end type driver_config

  !> Configuration for the LBFGS geometry optimization driver
  type, extends(driver_config) :: lbfgs_config
    !> Tolerance for considering optimization to be converged
    real :: tolerance
  end type lbfgs_config

  !> Configuration for the Velocity-Verlet molecular dynamics driver
  type, extends(driver_config) :: velocity_verlet_config
    !> Time step for the propagation in fs
    real :: time_step
    !> Temperature in K
    real :: temperature
    !> Number of steps to take in the propagation
    integer :: max_steps
  end type velocity_verlet_config

  !> Configuration of a single simulation task
  type :: task_config
    !> Label to identify the task
    character(len=:), allocatable :: label
    !> Driver configuration
    class(driver_config), allocatable :: config
  end type task_config

To read the array of tables we start from the root document and fetch the tasks entry as an array using the get_value interface. The length of the full arrays is known and we can use it to allocate the list of task_config values before reading the individual entries. The individual tables inside the array can be addressed using the get_value interface by passing the (one-based) index.

src/task.f90#
  !> Read task configurations from document root
  subroutine read_tasks(table, task)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configurations for simulation tasks
    type(task_config), allocatable, intent(out) :: task(:)

    integer :: itask
    type(toml_array), pointer :: array
    type(toml_table), pointer :: child

    call get_value(table, "tasks", array)
    allocate(task(len(array)))

    do itask = 1, size(task)
      call get_value(array, itask, child)
      call read_task(child, task(itask))
    end do
  end subroutine read_tasks

Note

In the setup above, if the tasks entry is not present it will be implicitly created as an empty array. The allocation and the loop over the entries will work, however the consuming code should check whether no tasks are meaningful or should produce an error.

To read the individual tasks we define a separate procedure to make it easily reusable and hide the fact that we are working with a subtable. To make the task name optional we make it default to the driver name, for allocatable or pointer variables the exit status of get_value can be easily checked by the allocation or association status of the respective variable, alternatively an integer variable can be passed to the optional stat argument. Finally, the configuration reader is called depending on the value of driver for ease of usage we use a block construct to allocate the specific type and then transfer it using move_alloc into the task_config.

src/task.f90#
  !> Read a single task configuration
  subroutine read_task(table, task)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configuration for simulation task
    type(task_config), intent(out) :: task

    character(len=:), allocatable :: driver
    type(toml_table), pointer :: child

    call get_value(table, "driver", driver)
    if (.not.allocated(driver)) then
      error stop "Driver keyword not present in task configuration"
    end if
    call get_value(table, "name", task%label, driver)

    select case(driver)
    case default
      error stop "Unknown driver type in task configuration"
    case("lbfgs")
      block
        type(lbfgs_config), allocatable :: tmp
        allocate(tmp)
        call get_value(table, "config", child)
        call read_lbfgs(child, tmp)
        call move_alloc(tmp, task%config)
      end block
    case("velocity-verlet")
      block
        type(velocity_verlet_config), allocatable :: tmp
        allocate(tmp)
        call get_value(table, "config", child)
        call read_velocity_verlet(child, tmp)
        call move_alloc(tmp, task%config)
      end block
    end select
  end subroutine read_task

For reading the actual driver configuration we use the get_value interface to obtain the settings. We use the same defaulting mechanism as for the name entry here.

src/task.f90#
  !> Read configuration for LBFGS geometry optimization
  subroutine read_lbfgs(table, config)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configuration for LBFGS optimizer
    type(lbfgs_config), intent(out) :: config

    call get_value(table, "tolerance", config%tolerance, 1.0e-6)
  end subroutine read_lbfgs

  !> Read configuration for Velocity-Verlet molecular dynamics
  subroutine read_velocity_verlet(table, config)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configuration for Velocity-Verlet propagator
    type(velocity_verlet_config), intent(out) :: config

    call get_value(table, "time-step", config%time_step, 0.5)
    call get_value(table, "temperature", config%temperature, 298.15)
    call get_value(table, "max-steps", config%max_steps, 100)
  end subroutine read_velocity_verlet

Note that this example does not propagate back errors but directly calls error stop, for a more robust error reporting this can be changed by a small error handle or a context type.

Full source code

The full module implementing the task_config reading

src/task.f90#
!> Example for a workflow pipeline to construct a molecular dynamics simulation.
module demo_task
  use tomlf, only : toml_table, toml_array, get_value, len
  implicit none
  private

  public :: read_tasks, task_config, driver_config, lbfgs_config, velocity_verlet_config

  !> Abstract base class for all simulation driver configurations
  type, abstract :: driver_config
  end type driver_config

  !> Configuration for the LBFGS geometry optimization driver
  type, extends(driver_config) :: lbfgs_config
    !> Tolerance for considering optimization to be converged
    real :: tolerance
  end type lbfgs_config

  !> Configuration for the Velocity-Verlet molecular dynamics driver
  type, extends(driver_config) :: velocity_verlet_config
    !> Time step for the propagation in fs
    real :: time_step
    !> Temperature in K
    real :: temperature
    !> Number of steps to take in the propagation
    integer :: max_steps
  end type velocity_verlet_config

  !> Configuration of a single simulation task
  type :: task_config
    !> Label to identify the task
    character(len=:), allocatable :: label
    !> Driver configuration
    class(driver_config), allocatable :: config
  end type task_config

contains

  !> Read task configurations from document root
  subroutine read_tasks(table, task)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configurations for simulation tasks
    type(task_config), allocatable, intent(out) :: task(:)

    integer :: itask
    type(toml_array), pointer :: array
    type(toml_table), pointer :: child

    call get_value(table, "tasks", array)
    allocate(task(len(array)))

    do itask = 1, size(task)
      call get_value(array, itask, child)
      call read_task(child, task(itask))
    end do
  end subroutine read_tasks

  !> Read a single task configuration
  subroutine read_task(table, task)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configuration for simulation task
    type(task_config), intent(out) :: task

    character(len=:), allocatable :: driver
    type(toml_table), pointer :: child

    call get_value(table, "driver", driver)
    if (.not.allocated(driver)) then
      error stop "Driver keyword not present in task configuration"
    end if
    call get_value(table, "name", task%label, driver)

    select case(driver)
    case default
      error stop "Unknown driver type in task configuration"
    case("lbfgs")
      block
        type(lbfgs_config), allocatable :: tmp
        allocate(tmp)
        call get_value(table, "config", child)
        call read_lbfgs(child, tmp)
        call move_alloc(tmp, task%config)
      end block
    case("velocity-verlet")
      block
        type(velocity_verlet_config), allocatable :: tmp
        allocate(tmp)
        call get_value(table, "config", child)
        call read_velocity_verlet(child, tmp)
        call move_alloc(tmp, task%config)
      end block
    end select
  end subroutine read_task

  !> Read configuration for LBFGS geometry optimization
  subroutine read_lbfgs(table, config)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configuration for LBFGS optimizer
    type(lbfgs_config), intent(out) :: config

    call get_value(table, "tolerance", config%tolerance, 1.0e-6)
  end subroutine read_lbfgs

  !> Read configuration for Velocity-Verlet molecular dynamics
  subroutine read_velocity_verlet(table, config)
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Configuration for Velocity-Verlet propagator
    type(velocity_verlet_config), intent(out) :: config

    call get_value(table, "time-step", config%time_step, 0.5)
    call get_value(table, "temperature", config%temperature, 298.15)
    call get_value(table, "max-steps", config%max_steps, 100)
  end subroutine read_velocity_verlet

end module demo_task