@@ -627,17 +627,17 @@ end function git_metadata
627
627
628
628
subroutine create_verified_basic_manifest (filename )
629
629
! > 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
631
631
use fpm_manifest_package, only : package_config_t, new_package
632
632
use fpm_error, only : error_t
633
633
implicit none
634
634
character (len=* ),intent (in ) :: filename
635
635
type (toml_table) :: table
636
- type (toml_serializer) :: ser
637
636
type (package_config_t) :: package
638
637
type (error_t), allocatable :: error
639
638
integer :: lun
640
639
character (len= 8 ) :: date
640
+ character (:), allocatable :: output
641
641
642
642
if (exists(filename))then
643
643
write (stderr,' (*(g0,1x))' )' <INFO> ' ,filename,&
@@ -647,7 +647,6 @@ subroutine create_verified_basic_manifest(filename)
647
647
! > get date to put into metadata in manifest file "fpm.toml"
648
648
call date_and_time (DATE= date)
649
649
table = toml_table()
650
- ser = toml_serializer()
651
650
call fileopen(filename,lun) ! fileopen stops on error
652
651
653
652
call set_value(table, " name" , BNAME)
@@ -660,11 +659,11 @@ subroutine create_verified_basic_manifest(filename)
660
659
! ...
661
660
call new_package(package, table, error= error)
662
661
if (allocated (error)) call fpm_stop( 3 ,' ' )
662
+ output = toml_serialize(table)
663
663
if (settings% verbose)then
664
- call table % accept(ser)
664
+ print ' (a) ' , output
665
665
endif
666
- ser% unit= lun
667
- call table% accept(ser)
666
+ write (lun, ' (a)' ) output
668
667
call fileclose(lun) ! fileopen stops on error
669
668
670
669
end subroutine create_verified_basic_manifest
@@ -673,27 +672,25 @@ end subroutine create_verified_basic_manifest
673
672
subroutine validate_toml_data (input )
674
673
! > verify a string array is a valid fpm.toml file
675
674
!
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
678
677
implicit none
679
678
character (kind= tfc,len= :),intent (in ),allocatable :: input(:)
680
679
character (len= 1 ), parameter :: nl = new_line(' a' )
681
680
type (toml_table), allocatable :: table
682
681
character (kind= tfc, len= :), allocatable :: joined_string
683
- type (toml_serializer) :: ser
684
682
685
683
! you have to add a newline character by using the intrinsic
686
684
! function `new_line("a")` to get the lines processed correctly.
687
685
joined_string = join(input,right= nl)
688
686
689
687
if (allocated (table)) deallocate (table)
690
- call toml_parse (table, joined_string)
688
+ call toml_load (table, joined_string)
691
689
if (allocated (table)) then
692
690
if (settings% verbose)then
693
691
! 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)
697
694
endif
698
695
call table% destroy
699
696
endif
0 commit comments