Skip to content

Commit b83d26c

Browse files
committed
toml serialization interfaces returning fpm error types
1 parent bb76d6a commit b83d26c

File tree

1 file changed

+53
-0
lines changed

1 file changed

+53
-0
lines changed

src/fpm/toml.f90

Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,8 @@ module fpm_toml
7878
module procedure get_logical
7979
module procedure get_integer
8080
module procedure get_integer_64
81+
module procedure get_char
82+
module procedure get_string
8183
end interface get_value
8284

8385

@@ -704,6 +706,57 @@ subroutine get_integer(table, key, var, error, whereAt)
704706

705707
end subroutine get_integer
706708

709+
!> Function wrapper to get a default string variable from a toml table, returning an fpm error
710+
subroutine get_string(table, key, var, error, whereAt)
711+
712+
!> Instance of the TOML data structure
713+
type(toml_table), intent(inout) :: table
714+
715+
!> The key
716+
character(len=*), intent(in) :: key
717+
718+
!> The variable
719+
type(string_t), intent(inout) :: var
720+
721+
!> Error handling
722+
type(error_t), allocatable, intent(out) :: error
723+
724+
!> Optional description
725+
character(len=*), intent(in), optional :: whereAt
726+
727+
call get_char(table, key, var%s, error, whereAt)
728+
729+
end subroutine get_string
730+
731+
!> Function wrapper to get a default character variable from a toml table, returning an fpm error
732+
subroutine get_char(table, key, var, error, whereAt)
733+
734+
!> Instance of the TOML data structure
735+
type(toml_table), intent(inout) :: table
736+
737+
!> The key
738+
character(len=*), intent(in) :: key
739+
740+
!> The variable
741+
character(len=:), allocatable, intent(inout) :: var
742+
743+
!> Error handling
744+
type(error_t), allocatable, intent(out) :: error
745+
746+
!> Optional description
747+
character(len=*), intent(in), optional :: whereAt
748+
749+
integer :: ierr
750+
751+
call get_value(table, key, var, stat=ierr)
752+
if (ierr/=toml_stat%success) then
753+
call fatal_error(error,'cannot get string key <'//key//'> from TOML table')
754+
if (present(whereAt)) error%message = whereAt//': '//error%message
755+
return
756+
end if
757+
758+
end subroutine get_char
759+
707760
!> Function wrapper to get a integer(int64) variable from a toml table, returning an fpm error
708761
subroutine get_integer_64(table, key, var, error, whereAt)
709762

0 commit comments

Comments
 (0)