Construct a new library configuration from a TOML data structure
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(library_config_t), | intent(out) | :: | self |
Instance of the library configuration |
||
type(toml_table), | intent(inout) | :: | table |
Instance of the TOML data structure |
||
type(error_t), | intent(out), | allocatable | :: | error |
Error handling |
subroutine new_library(self, table, error)
!> Instance of the library configuration
type(library_config_t), intent(out) :: self
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
!> Error handling
type(error_t), allocatable, intent(out) :: error
call check(table, error)
if (allocated(error)) return
call get_value(table, "source-dir", self%source_dir, "src")
call get_value(table, "build-script", self%build_script)
call get_list(table, "include-dir", self%include_dir, error)
if (allocated(error)) return
! Set default value of include-dir if not found in manifest
if (.not.allocated(self%include_dir)) then
self%include_dir = [string_t("include")]
end if
end subroutine new_library