Serializable base class#

This recipe shows how to create a serializable class based on TOML Fortran. Currently, TOML Fortran does not define such a base class itself, therefore we define a loader and dumper interface for turning a file or connected unit into a data structure. The abstract base class will implement the processing of the file or unit to a TOML data structure and pass it to a deferred procedure which the implementing class uses to define its mapping from and back to the TOML data structure. This way an easily round-tripable data structure can be created and used in a variety of contexts.

Note

TOML Fortran might provide such abstract base class in the future natively.

The base class can be defined as

src/serde_class.f90#
!> Definition of configuration data with serde properties.
!> Each data record knows how to serialize and deserialize itself.
module serde_class
  use serde_error, only : error_type, fatal_error
  use tomlf, only : toml_table, toml_error, toml_load, toml_dump
  implicit none
  private

  public :: serde_record

  !> Serializable and deserializable configuration data record
  type, abstract :: serde_record
  contains
    !> Reading of configuration data
    generic :: load => load_from_file, load_from_unit, load_from_toml
    !> Read configuration data from file
    procedure, private :: load_from_file
    !> Read configuration data from formatted unit
    procedure, private :: load_from_unit
    !> Read configuration data from TOML data structure
    procedure(load_from_toml), deferred :: load_from_toml
    !> Writing of configuration data
    generic :: dump => dump_to_file, dump_to_unit, dump_to_toml
    !> Write configuration data to file
    procedure, private :: dump_to_file
    !> Write configuration data to formatted unit
    procedure, private :: dump_to_unit
    !> Write configuration data to TOML data structure
    procedure(dump_to_toml), deferred :: dump_to_toml
  end type serde_record

  abstract interface
    !> Read configuration data from TOML data structure
    subroutine load_from_toml(self, table, error)
      import :: serde_record, toml_table, error_type
      !> Instance of the configuration data
      class(serde_record), intent(inout) :: self
      !> Data structure
      type(toml_table), intent(inout) :: table
      !> Error handling
      type(error_type), allocatable, intent(out) :: error
    end subroutine load_from_toml
    !> Write configuration data to TOML datastructure
    subroutine dump_to_toml(self, table, error)
      import :: serde_record, toml_table, error_type
      !> Instance of the configuration data
      class(serde_record), intent(in) :: self
      !> Data structure
      type(toml_table), intent(inout) :: table
      !> Error handling
      type(error_type), allocatable, intent(out) :: error
    end subroutine dump_to_toml
  end interface

contains

  !> Read configuration data from file
  subroutine load_from_file(self, file, error)
    !> Instance of the configuration data
    class(serde_record), intent(inout) :: self
    !> File name
    character(len=*), intent(in) :: file
    !> Error handling
    type(error_type), allocatable, intent(out) :: error

    type(toml_error), allocatable :: parse_error
    type(toml_table), allocatable :: table

    call toml_load(table, file, error=parse_error)

    if (allocated(parse_error)) then
      allocate(error)
      call move_alloc(parse_error%message, error%message)
      return
    end if

    call self%load(table, error)
    if (allocated(error)) return
  end subroutine load_from_file

  !> Read configuration data from file
  subroutine load_from_unit(self, unit, error)
    !> Instance of the configuration data
    class(serde_record), intent(inout) :: self
    !> File name
    integer, intent(in) :: unit
    !> Error handling
    type(error_type), allocatable, intent(out) :: error

    type(toml_error), allocatable :: parse_error
    type(toml_table), allocatable :: table

    call toml_load(table, unit, error=parse_error)

    if (allocated(parse_error)) then
      allocate(error)
      call move_alloc(parse_error%message, error%message)
      return
    end if

    call self%load(table, error)
    if (allocated(error)) return
  end subroutine load_from_unit

  !> Write configuration data to file
  subroutine dump_to_file(self, file, error)
    !> Instance of the configuration data
    class(serde_record), intent(in) :: self
    !> File name
    character(len=*), intent(in) :: file
    !> Error handling
    type(error_type), allocatable, intent(out) :: error

    integer :: unit

    open(file=file, newunit=unit)
    call self%dump(unit, error)
    close(unit)
    if (allocated(error)) return

  end subroutine dump_to_file

  !> Write configuration data to file
  subroutine dump_to_unit(self, unit, error)
    !> Instance of the configuration data
    class(serde_record), intent(in) :: self
    !> Formatted unit
    integer, intent(in) :: unit
    !> Error handling
    type(error_type), allocatable, intent(out) :: error

    type(toml_table) :: table

    table = toml_table()

    call self%dump(table, error)

    if (.not.allocated(error)) then
      call toml_dump(table, unit, error)
    end if

  end subroutine dump_to_unit

end module serde_class

We also define a convenience error handler which holds the error message and signals its error status by its allocation state.

src/serde_error.f90#
!> Central registry for error codes
module serde_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 :: serde_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 = serde_stat%fatal
    end if

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

end module serde_error

An example for a serializable class based on the above base class is given below.

src/demo.f90#
module demo_serde
  use serde_class, only : serde_record
  use serde_error, only : error_type, fatal_error
  use tomlf, only : toml_table, get_value, set_value
  implicit none
  private

  public :: example_record

  type, extends(serde_record) :: example_record
    integer :: nrun
    real :: alpha
    character(len=:), allocatable :: label
  contains
    !> Read configuration data from TOML data structure
    procedure :: load_from_toml
    !> Write configuration data to TOML data structure
    procedure :: dump_to_toml
  end type example_record

contains

  !> Read configuration data from TOML data structure
  subroutine load_from_toml(self, table, error)
    !> Instance of the configuration data
    class(example_record), intent(inout) :: self
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Error handling
    type(error_type), allocatable, intent(out) :: error

    integer :: stat

    call get_value(table, "nrun", self%nrun, 10, stat=stat)
    if (stat /= 0) then
      call fatal_error(error, "Invalid entry for number of runs")
      return
    end if

    call get_value(table, "alpha", self%alpha, 1.0, stat=stat)
    if (stat /= 0) then
      call fatal_error(error, "Invalid entry for alpha parameter")
      return
    end if

    call get_value(table, "label", self%label, stat=stat)
    if (stat /= 0) then
      call fatal_error(error, "Invalid entry for data label")
      return
    end if
  end subroutine load_from_toml


  !> Write configuration data to TOML datastructure
  subroutine dump_to_toml(self, table, error)
    !> Instance of the configuration data
    class(example_record), intent(in) :: self
    !> Data structure
    type(toml_table), intent(inout) :: table
    !> Error handling
    type(error_type), allocatable, intent(out) :: error

    call set_value(table, "nrun", self%nrun)
    call set_value(table, "alpha", self%alpha)
    if (allocated(self%label)) then
      call set_value(table, "label", self%label)
    end if
  end subroutine dump_to_toml

end module demo_serde

The defined data class can in an application easily be loaded from a file, while the actual implementation does not have to deal with getting the TOML data structure from the file but can assume that if the configuration file was valid TOML it will be provided with a data structure to read from.