Skip to content

Commit

Permalink
Dependency-level macro setting (#952)
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz authored Jul 10, 2023
2 parents cfd77ce + 3df03c2 commit 39fdc09
Show file tree
Hide file tree
Showing 11 changed files with 175 additions and 17 deletions.
4 changes: 4 additions & 0 deletions ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,10 @@ pushd preprocess_cpp_deps
"$fpm" build
popd

pushd preprocess_per_dependency
"$fpm" run
popd

pushd preprocess_hello
"$fpm" build
popd
Expand Down
8 changes: 8 additions & 0 deletions example_packages/preprocess_per_dependency/app/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
program hello_fpm
use utils, only: say_hello
integer :: ierr

call say_hello(ierr)
stop ierr ! ierr==0 if DEPENDENCY_MACRO is defined

end program hello_fpm
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
name = "utils"

[preprocess]
[preprocess.cpp]
macros = ["X=1"]
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module utils

implicit none

contains

subroutine say_hello(ierr)
integer, intent(out) :: ierr

ierr = -1
#ifdef DEPENDENCY_MACRO
ierr = 0
#endif

print *, "Dependency macro ", merge(" IS","NOT",ierr==0)," defined"

end subroutine say_hello

end module utils
4 changes: 4 additions & 0 deletions example_packages/preprocess_per_dependency/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
name = "preprocess_cpp_deps"

[dependencies]
utils = { path = "crate/utils" , preprocess.cpp.macros=["DEPENDENCY_MACRO"] }
20 changes: 19 additions & 1 deletion src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -109,12 +109,30 @@ subroutine build_model(model, settings, package, error)
end associate
model%packages(i)%version = package%version%s()

!> Add this dependency's manifest macros
allocate(model%packages(i)%macros(0))

if (allocated(dependency%preprocess)) then
do j = 1, size(dependency%preprocess)
if (dependency%preprocess(j)%name == "cpp") then
if (.not. has_cpp) has_cpp = .true.
if (allocated(dependency%preprocess(j)%macros)) then
model%packages(i)%macros = dependency%preprocess(j)%macros
model%packages(i)%macros = [model%packages(i)%macros, dependency%preprocess(j)%macros]
end if
else
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
' is not supported; will ignore it'
end if
end do
end if

!> Add this dependency's package-level macros
if (allocated(dep%preprocess)) then
do j = 1, size(dep%preprocess)
if (dep%preprocess(j)%name == "cpp") then
if (.not. has_cpp) has_cpp = .true.
if (allocated(dep%preprocess(j)%macros)) then
model%packages(i)%macros = [model%packages(i)%macros, dep%preprocess(j)%macros]
end if
else
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
Expand Down
20 changes: 20 additions & 0 deletions src/fpm/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,7 @@ module fpm_dependency
use fpm_git, only: git_target_revision, git_target_default, git_revision, operator(==)
use fpm_manifest, only: package_config_t, dependency_config_t, get_package_data
use fpm_manifest_dependency, only: manifest_has_changed
use fpm_manifest_preprocess, only: operator(==)
use fpm_strings, only: string_t, operator(.in.)
use fpm_toml, only: toml_table, toml_key, toml_error, toml_serialize, &
get_value, set_value, add_table, toml_load, toml_stat
Expand Down Expand Up @@ -1187,6 +1188,8 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
!> Log verbosity
integer, intent(in) :: verbosity, iunit

integer :: ip

has_changed = .true.

!> All the following entities must be equal for the dependency to not have changed
Expand Down Expand Up @@ -1219,6 +1222,23 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
else
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed presence "
end if
if (allocated(cached%preprocess) .eqv. allocated(manifest%preprocess)) then
if (allocated(cached%preprocess)) then
if (size(cached%preprocess) /= size(manifest%preprocess)) then
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS has changed size"
return
end if
do ip=1,size(cached%preprocess)
if (.not.(cached%preprocess(ip) == manifest%preprocess(ip))) then
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS config has changed"
return
end if
end do
endif
else
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS has changed presence "
return
end if

!> All checks passed: the two dependencies have no differences
has_changed = .false.
Expand Down
45 changes: 36 additions & 9 deletions src/fpm/manifest/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,8 @@ module fpm_manifest_dependency
use fpm_manifest_metapackages, only: metapackage_config_t, is_meta_package, new_meta_config, &
metapackage_request_t, new_meta_request
use fpm_versioning, only: version_t, new_version
use fpm_strings, only: string_t
use fpm_manifest_preprocess
implicit none
private

Expand All @@ -55,6 +57,9 @@ module fpm_manifest_dependency
!> The latest version is used if not specified.
type(version_t), allocatable :: requested_version

!> Requested macros for the dependency
type(preprocess_config_t), allocatable :: preprocess(:)

!> Git descriptor
type(git_target_t), allocatable :: git

Expand Down Expand Up @@ -87,12 +92,28 @@ subroutine new_dependency(self, table, root, error)

character(len=:), allocatable :: uri, value, requested_version

type(toml_table), pointer :: child

call check(table, error)
if (allocated(error)) return

call table%get_key(self%name)
call get_value(table, "namespace", self%namespace)

call get_value(table, "v", requested_version)
if (allocated(requested_version)) then
if (.not. allocated(self%requested_version)) allocate (self%requested_version)
call new_version(self%requested_version, requested_version, error)
if (allocated(error)) return
end if

!> Get optional preprocessor directives
call get_value(table, "preprocess", child, requested=.false.)
if (associated(child)) then
call new_preprocessors(self%preprocess, child, error)
if (allocated(error)) return
endif

call get_value(table, "path", uri)
if (allocated(uri)) then
if (get_os_type() == OS_WINDOWS) uri = windows_path(uri)
Expand Down Expand Up @@ -128,14 +149,6 @@ subroutine new_dependency(self, table, root, error)
return
end if

call get_value(table, "v", requested_version)

if (allocated(requested_version)) then
if (.not. allocated(self%requested_version)) allocate (self%requested_version)
call new_version(self%requested_version, requested_version, error)
if (allocated(error)) return
end if

end subroutine new_dependency

!> Check local schema for allowed entries
Expand All @@ -149,6 +162,7 @@ subroutine check(table, error)

character(len=:), allocatable :: name
type(toml_key), allocatable :: list(:)
type(toml_table), pointer :: child

!> List of valid keys for the dependency table.
character(*), dimension(*), parameter :: valid_keys = [character(24) :: &
Expand All @@ -158,7 +172,8 @@ subroutine check(table, error)
"git", &
"tag", &
"branch", &
"rev" &
"rev", &
"preprocess" &
& ]

call table%get_key(name)
Expand Down Expand Up @@ -202,6 +217,18 @@ subroutine check(table, error)
return
end if

! Check preprocess key
if (table%has_key('preprocess')) then

call get_value(table, 'preprocess', child)

if (.not.associated(child)) then
call syntax_error(error, "Dependency '"//name//"' has invalid 'preprocess' entry")
return
end if

end if

end subroutine check

!> Construct new dependency array from a TOML data structure
Expand Down
51 changes: 49 additions & 2 deletions src/fpm/manifest/preprocess.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ module fpm_manifest_preprocess
implicit none
private

public :: preprocess_config_t, new_preprocess_config, new_preprocessors
public :: preprocess_config_t, new_preprocess_config, new_preprocessors, operator(==)

!> Configuration meta data for a preprocessor
type :: preprocess_config_t
Expand All @@ -41,6 +41,10 @@ module fpm_manifest_preprocess

end type preprocess_config_t

interface operator(==)
module procedure preprocess_is_same
end interface

contains

!> Construct a new preprocess configuration from TOML data structure
Expand Down Expand Up @@ -154,7 +158,7 @@ subroutine info(self, unit, verbosity)
pr = 1
end if

if (pr < 1) return
if (pr < 1) return

write(unit, fmt) "Preprocessor"
if (allocated(self%name)) then
Expand All @@ -181,4 +185,47 @@ subroutine info(self, unit, verbosity)

end subroutine info

logical function preprocess_is_same(this,that)
class(preprocess_config_t), intent(in) :: this
class(preprocess_config_t), intent(in) :: that

integer :: istr

preprocess_is_same = .false.

select type (other=>that)
type is (preprocess_config_t)
if (allocated(this%name).neqv.allocated(other%name)) return
if (allocated(this%name)) then
if (.not.(this%name==other%name)) return
endif
if (.not.(allocated(this%suffixes).eqv.allocated(other%suffixes))) return
if (allocated(this%suffixes)) then
do istr=1,size(this%suffixes)
if (.not.(this%suffixes(istr)%s==other%suffixes(istr)%s)) return
end do
end if
if (.not.(allocated(this%directories).eqv.allocated(other%directories))) return
if (allocated(this%directories)) then
do istr=1,size(this%directories)
if (.not.(this%directories(istr)%s==other%directories(istr)%s)) return
end do
end if
if (.not.(allocated(this%macros).eqv.allocated(other%macros))) return
if (allocated(this%macros)) then
do istr=1,size(this%macros)
if (.not.(this%macros(istr)%s==other%macros(istr)%s)) return
end do
end if

class default
! Not the same type
return
end select

!> All checks passed!
preprocess_is_same = .true.

end function preprocess_is_same

end module fpm_manifest_preprocess
15 changes: 11 additions & 4 deletions src/fpm/toml.f90
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,7 @@ subroutine check_keys(table, valid_keys, error)
type(error_t), allocatable, intent(out) :: error

type(toml_key), allocatable :: keys(:)
type(toml_table), pointer :: child
character(:), allocatable :: name, value, valid_keys_string
integer :: ikey, ivalid

Expand All @@ -143,12 +144,18 @@ subroutine check_keys(table, valid_keys, error)
end if

! Check if value can be mapped or else (wrong type) show error message with the error location.
! Right now, it can only be mapped to a string, but this can be extended in the future.
! Right now, it can only be mapped to a string or to a child node, but this can be extended in the future.
call get_value(table, keys(ikey)%key, value)
if (.not. allocated(value)) then
allocate (error)
error%message = "'"//name//"' has an invalid '"//keys(ikey)%key//"' entry."
return

! If value is not a string, check if it is a child node
call get_value(table, keys(ikey)%key, child)

if (.not.associated(child)) then
allocate (error)
error%message = "'"//name//"' has an invalid '"//keys(ikey)%key//"' entry."
return
endif
end if
end do

Expand Down
1 change: 0 additions & 1 deletion test/fpm_test/test_package_dependencies.f90
Original file line number Diff line number Diff line change
Expand Up @@ -334,7 +334,6 @@ subroutine test_non_updated_dependencies(error)
return
end if


! Test that dependency 3 is flagged as "not update"
if (manifest_deps%dep(3)%update) then
call test_failed(error, "Updated dependency (git rev) detected, should not be")
Expand Down

0 comments on commit 39fdc09

Please sign in to comment.