Skip to content

Commit

Permalink
Sync fpm_model with main branch
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Feb 10, 2024
1 parent c212d92 commit 53a4486
Showing 1 changed file with 17 additions and 6 deletions.
23 changes: 17 additions & 6 deletions src/fpm_model.f90
Original file line number Diff line number Diff line change
Expand Up @@ -675,7 +675,7 @@ logical function package_is_same(this,that)
end do
end if

if (.not.(this%macros==other%macros)) return
if (.not.(this%preprocess==other%preprocess)) return
if (.not.(this%version==other%version)) return

!> Module naming
Expand Down Expand Up @@ -723,7 +723,10 @@ subroutine package_dump_to_toml(self, table, error)
call set_string(table, "module-prefix", self%module_prefix, error, 'package_t')
if (allocated(error)) return

call set_list(table, "macros", self%macros, error)
!> Create a preprocessor table
call add_table(table, "preprocess", ptr, error, 'package_t')
if (allocated(error)) return
call self%preprocess%dump_to_toml(ptr, error)
if (allocated(error)) return

!> Create a fortran table
Expand Down Expand Up @@ -768,7 +771,7 @@ subroutine package_load_from_toml(self, table, error)

integer :: ierr,ii,jj
type(toml_key), allocatable :: keys(:),src_keys(:)
type(toml_table), pointer :: ptr_sources,ptr,ptr_fortran
type(toml_table), pointer :: ptr_sources,ptr,ptr_fortran,ptr_preprocess
type(error_t), allocatable :: new_error

call get_value(table, "name", self%name)
Expand All @@ -780,9 +783,6 @@ subroutine package_load_from_toml(self, table, error)
! Return unallocated value if not present
call get_value(table, "module-prefix", self%module_prefix%s)

call get_list(table, "macros", self%macros, error)
if (allocated(error)) return

! Sources
call table%get_keys(keys)

Expand All @@ -799,6 +799,17 @@ subroutine package_load_from_toml(self, table, error)
call self%features%load_from_toml(ptr_fortran,error)
if (allocated(error)) return

case ("preprocess")

call get_value(table, keys(ii), ptr_preprocess)
if (.not.associated(ptr_preprocess)) then
call fatal_error(error,'package_t: error retrieving preprocess table from TOML table')
return
end if

call self%preprocess%load_from_toml(ptr_preprocess,error)
if (allocated(error)) return

case ("sources")

call get_value(table, keys(ii), ptr_sources)
Expand Down

0 comments on commit 53a4486

Please sign in to comment.