Mit Tabellen zu arbeiten#

Die zentrale Datenstruktur in TOML sind Tabellen, sie enthalten eine Zuordnung von Einträgen (String) zu allen unterstützten Datentypen in TOML. Dieses Rezept beschreibt die allgemeinen Szenarien für das Abfragen von Daten aus Tabellen mit der TOML Fortran-Bibliothek.

Auf geschachtelte Tabellen zuzugreifen#

Geschachtelte Tabellen ermöglichen es, Konfigurationsdaten besser zu gruppieren. Da das TOML-Format immer den vollständigen Pfad in jeder Tabellenkopfangabe erfordert, ist es einfach für den Benutzer zu erkennen, wo die aktuellen Einstellungen zu finden sind. Aber schwieriger wird es wenn tief geschachtelte Tabellen mit langen Tabellenpfaden oder Pfadkomponenten verwendet werden. Eine gute Balance zwischen kurzen und aussagekräftigen Tabellennamen und Untereinträge ist erforderlich.

Ein Beispiel für einen elektronischen Strukturcode, der unterschiedliche Hamiltonians implementiert, ist unten aufgeführt.

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

[analysis]
calculate-forces = true

Die tiefste geschachtelte Untertabelle in diesem Beispiel ist der hamiltonian.dftb.skf Pfad.

Dieser Aufbau in der Konfigurationsdatei wird in der tatsächlichen Implementierung korrespondierend wiedergeben, wobei jede Tabelle entsprechend einen abgeleiteten Typ beschreibt, der der Eingabe entspricht. Für das Beispiel oben sind insgesamt sechs abgeleitete Typen für die einzelnen Tabellen definiert.

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

Bemerkung

Die Darstellung in abgeleiteten Typen ist in Fortran länger als die TOML-Eingabe. Dabei sollte beachten werden, dass die 40 Zeilen von Fortran Code 50% Kommentare enthalten, die die Datentypen für (zukünftige) Entwickler beschreiben. Zudem ist die Benutzerdokumentation des Eingabeformats ähnlich ausführlich, mit Beschreibungen für alle Tabellen und Einträge, inklusive Eingabebereichs und Einheiten. Die Eingabedatei kann dann kurz und aussagekräftig sein.

Mit dem Wurzelknoten der Tabelle, der in den Datentypen simulation_input gelesen wird, gibt es zwei Wege, eine Untertabelle abzufragen, zunächst wird die hamiltonian Untertabelle abgefragt, die als benötigt definiert ist und mit der get_value-Schnittstelle abgefragt wird. In Fällen, wenn diese Tabelle vorhanden ist, wird eine Referenz mit dem child Zeiger zurückgegeben. Falls keine Tabelle vorhanden ist, wird sie in den Wurzelknoten eingefügt und eine Referenz zurückgegeben. Der child Zeiger kann in Fällen von unzulässigen Eingaben nicht zugewiesen werden, was mit einer Fehlermeldung in der Implementierung abgefangen wird.

Alternativ kann die Untertabelle als optional markiert werden, wie für die analysis Tabelle, wenn keine Tabelle vorhanden ist oder der Eintrag ungültig ist, bleibt der child Zeiger unzugewiesen. Um diese Fälle zu unterscheiden, kann der Statusinformationen abgefragt werden, um zu prüfen, ob die Operation erfolgreich war, und im Fall eines Eingabefehlers eine Fehlermeldung ausgegeben wird.

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

Das gleiche gilt für die hamiltonian_input und dftb_input Einträge.

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

Zuletzt können die terminalen Untertabellen in scc_input, skf_input, und analysis_input gelesen werden, wo die Werte mit get_value abgefragt werden. Zusätzlich kann ein Standardwert mit get_value definiert werden. Für einen korrekten Fehlerbehandlung kann auch der optionalen stat-Parameter abgefragt werden.

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

Für die kleine unvollständige Eingabe wie hier sieht die fein unterteile Struktur zu vielen Unterstrukturen übermäßig kompliziert aus und könnte auch in der Lese-Routine für der Dokument-Wurzel definiert werden. Allerdings kann für größere Programm-Eingaben eine solche Struktur hilfreich sein, um sicherzustellen, dass die Lese-Routinen modular und wiederverwendbar sind.

Tipp

Der Allokationsstatus der Teilkomponenten in den Datentypen kann statt eines separated logischen Option verwendet werden, um eine aktive Funktionalität zu signalisieren. Dies ermöglicht es auf zusätzliche Logik zu verzichten um abhängige Einträge zu lesen, diese sind stattdessen in einer Untertabelle gesammelt.

Vollständiger Quellcode

Die vollständige Modul-Implementierung des simulation_input

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

Hilfsmodul um Fehlerbehandlung zu ermöglichen

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

Direkter Zugriff über Schlüsselpfad#

Wenn nur ein tiefgeschachtelter Wert einer Datenstruktur benötigt wird, kann dieser über einen Schlüsselpfad abgefragt werden. Im Build-Interface wird intern der Schlüsselpfad aufgebaut, Untertabellen aufgelöst, und wenn nötig erstellt.

Warnung

Wiederholter Zugriff auf Werte über einen Schlüsselpfad von der Dokument-wurzel, anstelle von der Referenz auf die gewünschte Untertabelle, braucht zusätzliche Ressourcen, da der Schlüsselpfad jedes Mal erneut aufgelöst wird.

Für das vorherigen Beispiel kann der Schlüsselpfad zum Abfragen des am tiefsten geschachtelten Wertes wie unten angegeben benutzt werden.

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

Ähnlich wie andere Build-Interfaces kann auch ein Standardwert angegeben werden, um die Untertabelle zu erstellen.

Iterieren über Einträge#

Eine klare Art Daten zu organisieren ist durch die Verwendung einer Tabelle in der die Einträge die Initialisierung der Objekte beschreiben. Zum Beispiel in einem Paketmanager beschreiben die Einträge die Abhängigkeiten, in der jede davon in einer Untertabelle deklariert wird. Zusätzlich kann der einfachheitshalber ein String angeben werden, der als Versions-Einschränkung für die Untertabelle interpretiert wird.

Die Implementierung in einer requirements Tabelle könnte wie folgt aussehen:

[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"}

In den ersten drei Einträgen wird ein String Wert verwendet, während der vierte Eintrag eine implizite Untertabelle über ein Punktgetrenntes Werte-Paar nutzt und der letzte Eintrag eine Inline-Tabelle ist.

Wir wollen uns hier auf die Iteration und die Standardinitialisierung konzentrieren. Die internen Struktur des requirement_type Datentype ist nebensächlich für dieses Beispiel. Daher geben wir für dieses Beispiel nur die minimale Definition an, die ausschließlich den Namen der Abhängigkeiten enthält.

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

Für die Implementierung der Leseoperationen wird ein eindimensionales Feld von requirement_type Datentypen verwendet. Durch die get_keys Methode der Tabelle können alle Schlüssel der aktuellen Tabelle ermittelt werden. Die Methode wird immer eine allozierte list Variable zurückgeben und kann damit das requirement_type Feld auf die Anzahl der Schlüssel allozieren. Die get_value Methode kann verwendet werden, um auf die Untertabelle zuzugreifen. Sie wird einen Zeiger auf die Untertabelle zurückgeben, die entweder durch ein Punktgetrenntes Wert-Paar oder eine Inline-Tabelle erstellt wurde. Anschließend kann der Konstruktor des requirement_type Datentyps auf die Untertabelle-Referenzen mit dem child Zeiger aufgerufen werden.

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

Der zweite Scenario, das wir unterstützen, ist die Nutzung eines Strings anstatt einer Untertabelle. In diesem Fall wird die get_value Methode fehlschlagen, während ein optionaler Status-Parameter zurückgeben werden kann, um den Erfolg zu prüfen, können wir einfacher und idomatisch den Erfolg am Zuweisungs-Status des child Zeigers prüfen. Wenn es keine Untertabelle zu referenzieren gibt, weil es ein Wert-Paar mit einem String-Eintrag ist, wird der child Zeiger nicht zugewiesen. Dies kann einfach geprüft werden. Für diesen Fall werden wir die get_value Methode noch einmal verwenden, um den Eintrag in einen dynamischen String zu speichern. Auch hier können wir den Erfolg am Zuweisungs-Status prüfen und wenn ein Fehler aufgetreten ist, wird eine Fehlermeldung erzeugt. Anschließend können wir den Konstruktor des requirement_type Datentyps mit einer Dummy Tabelle aufrufen auf die wir mit dem child Zeiger referenziert haben.

Der eigentliche Konstruktor für dieses Beispiel ist sehr minimalistisch und spezifiziert nur den Namen der Abhängigkeit, welcher als separates Argument übergeben wird.

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

Bemerkung

Wir bieten einen Fehlerbehandlungs-Prozess in diesem Beispiel, zusätzlich stellen wir sicher, dass der Zuweisungs-Status des requirement_type Feldes die Status-Informationen der Operation ebenfalls kommuniziert.

Vollständiger Quellcode

Das vollständige Modul zum Einlesen des requirement_type

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

Hilfsmodul um Fehlerbehandlung zu ermöglichen

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

Feld von Tabellen#

Ein spezielles Konstrukt in TOML ist ein Feld von Tabellen, das eine ausführlichere Form zum Deklarieren von mehreren Tabellen in einem Feld anbietet. Normalerweise wird dies durch Inline-Tabellen angegeben wie unten gezeigt.

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

Vergleichen wir das obige Beispiel mit dem unten gezeigten Beispiel für das tasks Feld, dann ist die ausführlichere Form bevorzugt, wenn wir weitere Untertabelle benötigen. In beiden Beispielen werden bis auf die config Untertabelle die gleichen Daten angegeben.

[[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

Um diese Daten zu repräsentieren können wir einen eigenen task_config Datentyp verwenden, welcher einen polymorphen driver_config Eintrag enthält, der die tatsächliche Aufgabe identifiziert. Für dieses Beispiel werden zwei Implementierungen wie LBFGS und Velocity Verlet definiert, welche in den folgenden Codeblöcken angegeben sind.

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

Um das Feld von Tabellen zu einlesen starten wir vom Wurzeldokument und holen das tasks Eintrag als Feld mit der get_value Routine.Die Länge des gesamten Feldes ist bekannt und wir können diese Information benutzen, um eine Liste von task_config Einträgen zu allokieren. Die Tabellen in dem Feld können mit der get_value Routine anhand der (1-basierten) Indexposition abgefragt werden.

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

Bemerkung

Im obigen Setup wird das tasks Eintrag implizit erzeugt, wenn dieser nicht vorhanden ist. Die Allokation und der Schleifendurchlauf funktionieren ohne Probleme, allerdings müssen die folgenden Routinen prüfen, ob eine Simulation ohne Aufgaben Sinn hat oder einen Fehler erzeugen.

Für die einzelnen Aufgaben definieren wir eine separate Routine, um das Auslesen von Untertabellen zu vereinfachen und die Logik zu verstecken, dass wir mit einer Untertabelle arbeiten. Für den name Eintrag ist der Defaultwert der Name des Treibers. Für allocatable oder pointer Variablen kann der Exit-Status der get_value Routine direkt überprüft werden. Alternativ kann ein Integerwert als optionales stat Argument übergeben werden. Anschließend wird eine weitere Lese-Routine abhängig von dem driver Eintrag aufgerufen. Dabei nutzen wir einen Block, um die spezifischen Typen zu allokieren und diese mit move_alloc in die task_config Instanz zu transferieren.

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

Für die eigentliche Treiber-Konfiguration nutzen wir die get_value Routine, um die Einstellungen zu lesen. Wir nutzen dieselbe Defaultwert Mechanismus wie für den name Eintrag hier.

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

Dieses Beispiel gibt keine Fehler zurück, sondern ruft direkt error stop auf, um eine robustere Fehlerbehandlung zu ermöglichen, kann dies durch einen kleineren Fehlerbehandlungs-Typ oder einen Kontexttyp implementiert werden.

Vollständiger Quellcode

Die vollständige Modul-Implementierung um task_config zu lesen

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