Skip to content

Commit 55d94b0

Browse files
authored
Update TOML Fortran to latest version (#862)
1 parent cdedd2d commit 55d94b0

File tree

4 files changed

+22
-31
lines changed

4 files changed

+22
-31
lines changed

fpm.toml

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -6,13 +6,10 @@ maintainer = ""
66
copyright = "2020 fpm contributors"
77

88
[dependencies]
9-
[dependencies.toml-f]
10-
git = "https://github.com/toml-f/toml-f"
11-
rev = "aee54c5a480d623af99828c76df0447a15ce90dc"
12-
13-
[dependencies.M_CLI2]
14-
git = "https://github.com/urbanjost/M_CLI2.git"
15-
rev = "7264878cdb1baff7323cc48596d829ccfe7751b8"
9+
toml-f.git = "https://github.com/toml-f/toml-f"
10+
toml-f.rev = "54686e45993f3a9a1d05d5c7419f39e7d5a4eb3f"
11+
M_CLI2.git = "https://github.com/urbanjost/M_CLI2.git"
12+
M_CLI2.rev = "7264878cdb1baff7323cc48596d829ccfe7751b8"
1613

1714
[[test]]
1815
name = "cli-test"

src/fpm/cmd/new.f90

Lines changed: 10 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -627,17 +627,17 @@ end function git_metadata
627627

628628
subroutine create_verified_basic_manifest(filename)
629629
!> create a basic but verified default manifest file
630-
use fpm_toml, only : toml_table, toml_serializer, set_value
630+
use fpm_toml, only : toml_table, toml_serialize, set_value
631631
use fpm_manifest_package, only : package_config_t, new_package
632632
use fpm_error, only : error_t
633633
implicit none
634634
character(len=*),intent(in) :: filename
635635
type(toml_table) :: table
636-
type(toml_serializer) :: ser
637636
type(package_config_t) :: package
638637
type(error_t), allocatable :: error
639638
integer :: lun
640639
character(len=8) :: date
640+
character(:), allocatable :: output
641641

642642
if(exists(filename))then
643643
write(stderr,'(*(g0,1x))')'<INFO> ',filename,&
@@ -647,7 +647,6 @@ subroutine create_verified_basic_manifest(filename)
647647
!> get date to put into metadata in manifest file "fpm.toml"
648648
call date_and_time(DATE=date)
649649
table = toml_table()
650-
ser = toml_serializer()
651650
call fileopen(filename,lun) ! fileopen stops on error
652651

653652
call set_value(table, "name", BNAME)
@@ -660,11 +659,11 @@ subroutine create_verified_basic_manifest(filename)
660659
! ...
661660
call new_package(package, table, error=error)
662661
if (allocated(error)) call fpm_stop( 3,'')
662+
output = toml_serialize(table)
663663
if(settings%verbose)then
664-
call table%accept(ser)
664+
print '(a)', output
665665
endif
666-
ser%unit=lun
667-
call table%accept(ser)
666+
write(lun, '(a)') output
668667
call fileclose(lun) ! fileopen stops on error
669668

670669
end subroutine create_verified_basic_manifest
@@ -673,27 +672,25 @@ end subroutine create_verified_basic_manifest
673672
subroutine validate_toml_data(input)
674673
!> verify a string array is a valid fpm.toml file
675674
!
676-
use tomlf, only : toml_parse
677-
use fpm_toml, only : toml_table, toml_serializer
675+
use tomlf, only : toml_load
676+
use fpm_toml, only : toml_table, toml_serialize
678677
implicit none
679678
character(kind=tfc,len=:),intent(in),allocatable :: input(:)
680679
character(len=1), parameter :: nl = new_line('a')
681680
type(toml_table), allocatable :: table
682681
character(kind=tfc, len=:), allocatable :: joined_string
683-
type(toml_serializer) :: ser
684682

685683
! you have to add a newline character by using the intrinsic
686684
! function `new_line("a")` to get the lines processed correctly.
687685
joined_string = join(input,right=nl)
688686

689687
if (allocated(table)) deallocate(table)
690-
call toml_parse(table, joined_string)
688+
call toml_load(table, joined_string)
691689
if (allocated(table)) then
692690
if(settings%verbose)then
693691
! If the TOML file is successfully parsed the table will be allocated and
694-
! can be written to the standard output by passing the `toml_serializer`
695-
! as visitor to the table.
696-
call table%accept(ser)
692+
! can be written by `toml_serialize` to the standard output
693+
print '(a)', toml_serialize(table)
697694
endif
698695
call table%destroy
699696
endif

src/fpm/dependency.f90

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -64,8 +64,8 @@ module fpm_dependency
6464
get_package_data
6565
use fpm_manifest_dependency, only: manifest_has_changed
6666
use fpm_strings, only : string_t, operator(.in.)
67-
use fpm_toml, only : toml_table, toml_key, toml_error, toml_serializer, &
68-
toml_parse, get_value, set_value, add_table
67+
use fpm_toml, only : toml_table, toml_key, toml_error, toml_serialize, &
68+
toml_load, get_value, set_value, add_table
6969
use fpm_versioning, only : version_t, new_version, char
7070
implicit none
7171
private
@@ -720,7 +720,7 @@ subroutine load_from_unit(self, unit, error)
720720
type(toml_error), allocatable :: parse_error
721721
type(toml_table), allocatable :: table
722722

723-
call toml_parse(table, unit, parse_error)
723+
call toml_load(table, unit, error=parse_error)
724724

725725
if (allocated(parse_error)) then
726726
allocate(error)
@@ -830,14 +830,11 @@ subroutine dump_to_unit(self, unit, error)
830830
type(error_t), allocatable, intent(out) :: error
831831

832832
type(toml_table) :: table
833-
type(toml_serializer) :: ser
834833

835834
table = toml_table()
836-
ser = toml_serializer(unit)
837-
838835
call self%dump(table, error)
839836

840-
call table%accept(ser)
837+
write(unit, '(a)') toml_serialize(table)
841838

842839
end subroutine dump_to_unit
843840

src/fpm/toml.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -16,15 +16,15 @@ module fpm_toml
1616
use fpm_error, only : error_t, fatal_error, file_not_found_error
1717
use fpm_strings, only : string_t
1818
use tomlf, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
19-
& set_value, toml_parse, toml_error, new_table, add_table, add_array, &
20-
& toml_serializer, len
19+
& set_value, toml_load, toml_error, new_table, add_table, add_array, &
20+
& toml_serialize, len
2121
implicit none
2222
private
2323

2424
public :: read_package_file
2525
public :: toml_table, toml_array, toml_key, toml_stat, get_value, set_value, get_list
2626
public :: new_table, add_table, add_array, len
27-
public :: toml_error, toml_serializer, toml_parse
27+
public :: toml_error, toml_serialize, toml_load
2828

2929

3030
contains
@@ -54,7 +54,7 @@ subroutine read_package_file(table, manifest, error)
5454
end if
5555

5656
open(file=manifest, newunit=unit)
57-
call toml_parse(table, unit, parse_error)
57+
call toml_load(table, unit, error=parse_error)
5858
close(unit)
5959

6060
if (allocated(parse_error)) then

0 commit comments

Comments
 (0)