Skip to content

Commit 39fdc09

Browse files
authored
Dependency-level macro setting (#952)
2 parents cfd77ce + 3df03c2 commit 39fdc09

File tree

11 files changed

+175
-17
lines changed

11 files changed

+175
-17
lines changed

ci/run_tests.sh

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -150,6 +150,10 @@ pushd preprocess_cpp_deps
150150
"$fpm" build
151151
popd
152152

153+
pushd preprocess_per_dependency
154+
"$fpm" run
155+
popd
156+
153157
pushd preprocess_hello
154158
"$fpm" build
155159
popd
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
program hello_fpm
2+
use utils, only: say_hello
3+
integer :: ierr
4+
5+
call say_hello(ierr)
6+
stop ierr ! ierr==0 if DEPENDENCY_MACRO is defined
7+
8+
end program hello_fpm
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
name = "utils"
2+
3+
[preprocess]
4+
[preprocess.cpp]
5+
macros = ["X=1"]
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
module utils
2+
3+
implicit none
4+
5+
contains
6+
7+
subroutine say_hello(ierr)
8+
integer, intent(out) :: ierr
9+
10+
ierr = -1
11+
#ifdef DEPENDENCY_MACRO
12+
ierr = 0
13+
#endif
14+
15+
print *, "Dependency macro ", merge(" IS","NOT",ierr==0)," defined"
16+
17+
end subroutine say_hello
18+
19+
end module utils
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
name = "preprocess_cpp_deps"
2+
3+
[dependencies]
4+
utils = { path = "crate/utils" , preprocess.cpp.macros=["DEPENDENCY_MACRO"] }

src/fpm.f90

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -109,12 +109,30 @@ subroutine build_model(model, settings, package, error)
109109
end associate
110110
model%packages(i)%version = package%version%s()
111111

112+
!> Add this dependency's manifest macros
113+
allocate(model%packages(i)%macros(0))
114+
112115
if (allocated(dependency%preprocess)) then
113116
do j = 1, size(dependency%preprocess)
114117
if (dependency%preprocess(j)%name == "cpp") then
115118
if (.not. has_cpp) has_cpp = .true.
116119
if (allocated(dependency%preprocess(j)%macros)) then
117-
model%packages(i)%macros = dependency%preprocess(j)%macros
120+
model%packages(i)%macros = [model%packages(i)%macros, dependency%preprocess(j)%macros]
121+
end if
122+
else
123+
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
124+
' is not supported; will ignore it'
125+
end if
126+
end do
127+
end if
128+
129+
!> Add this dependency's package-level macros
130+
if (allocated(dep%preprocess)) then
131+
do j = 1, size(dep%preprocess)
132+
if (dep%preprocess(j)%name == "cpp") then
133+
if (.not. has_cpp) has_cpp = .true.
134+
if (allocated(dep%preprocess(j)%macros)) then
135+
model%packages(i)%macros = [model%packages(i)%macros, dep%preprocess(j)%macros]
118136
end if
119137
else
120138
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &

src/fpm/dependency.f90

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,7 @@ module fpm_dependency
6363
use fpm_git, only: git_target_revision, git_target_default, git_revision, operator(==)
6464
use fpm_manifest, only: package_config_t, dependency_config_t, get_package_data
6565
use fpm_manifest_dependency, only: manifest_has_changed
66+
use fpm_manifest_preprocess, only: operator(==)
6667
use fpm_strings, only: string_t, operator(.in.)
6768
use fpm_toml, only: toml_table, toml_key, toml_error, toml_serialize, &
6869
get_value, set_value, add_table, toml_load, toml_stat
@@ -1187,6 +1188,8 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
11871188
!> Log verbosity
11881189
integer, intent(in) :: verbosity, iunit
11891190

1191+
integer :: ip
1192+
11901193
has_changed = .true.
11911194

11921195
!> All the following entities must be equal for the dependency to not have changed
@@ -1219,6 +1222,23 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
12191222
else
12201223
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed presence "
12211224
end if
1225+
if (allocated(cached%preprocess) .eqv. allocated(manifest%preprocess)) then
1226+
if (allocated(cached%preprocess)) then
1227+
if (size(cached%preprocess) /= size(manifest%preprocess)) then
1228+
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS has changed size"
1229+
return
1230+
end if
1231+
do ip=1,size(cached%preprocess)
1232+
if (.not.(cached%preprocess(ip) == manifest%preprocess(ip))) then
1233+
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS config has changed"
1234+
return
1235+
end if
1236+
end do
1237+
endif
1238+
else
1239+
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS has changed presence "
1240+
return
1241+
end if
12221242

12231243
!> All checks passed: the two dependencies have no differences
12241244
has_changed = .false.

src/fpm/manifest/dependency.f90

Lines changed: 36 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,8 @@ module fpm_manifest_dependency
3232
use fpm_manifest_metapackages, only: metapackage_config_t, is_meta_package, new_meta_config, &
3333
metapackage_request_t, new_meta_request
3434
use fpm_versioning, only: version_t, new_version
35+
use fpm_strings, only: string_t
36+
use fpm_manifest_preprocess
3537
implicit none
3638
private
3739

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

60+
!> Requested macros for the dependency
61+
type(preprocess_config_t), allocatable :: preprocess(:)
62+
5863
!> Git descriptor
5964
type(git_target_t), allocatable :: git
6065

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

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

95+
type(toml_table), pointer :: child
96+
9097
call check(table, error)
9198
if (allocated(error)) return
9299

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

103+
call get_value(table, "v", requested_version)
104+
if (allocated(requested_version)) then
105+
if (.not. allocated(self%requested_version)) allocate (self%requested_version)
106+
call new_version(self%requested_version, requested_version, error)
107+
if (allocated(error)) return
108+
end if
109+
110+
!> Get optional preprocessor directives
111+
call get_value(table, "preprocess", child, requested=.false.)
112+
if (associated(child)) then
113+
call new_preprocessors(self%preprocess, child, error)
114+
if (allocated(error)) return
115+
endif
116+
96117
call get_value(table, "path", uri)
97118
if (allocated(uri)) then
98119
if (get_os_type() == OS_WINDOWS) uri = windows_path(uri)
@@ -128,14 +149,6 @@ subroutine new_dependency(self, table, root, error)
128149
return
129150
end if
130151

131-
call get_value(table, "v", requested_version)
132-
133-
if (allocated(requested_version)) then
134-
if (.not. allocated(self%requested_version)) allocate (self%requested_version)
135-
call new_version(self%requested_version, requested_version, error)
136-
if (allocated(error)) return
137-
end if
138-
139152
end subroutine new_dependency
140153

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

150163
character(len=:), allocatable :: name
151164
type(toml_key), allocatable :: list(:)
165+
type(toml_table), pointer :: child
152166

153167
!> List of valid keys for the dependency table.
154168
character(*), dimension(*), parameter :: valid_keys = [character(24) :: &
@@ -158,7 +172,8 @@ subroutine check(table, error)
158172
"git", &
159173
"tag", &
160174
"branch", &
161-
"rev" &
175+
"rev", &
176+
"preprocess" &
162177
& ]
163178

164179
call table%get_key(name)
@@ -202,6 +217,18 @@ subroutine check(table, error)
202217
return
203218
end if
204219

220+
! Check preprocess key
221+
if (table%has_key('preprocess')) then
222+
223+
call get_value(table, 'preprocess', child)
224+
225+
if (.not.associated(child)) then
226+
call syntax_error(error, "Dependency '"//name//"' has invalid 'preprocess' entry")
227+
return
228+
end if
229+
230+
end if
231+
205232
end subroutine check
206233

207234
!> Construct new dependency array from a TOML data structure

src/fpm/manifest/preprocess.f90

Lines changed: 49 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ module fpm_manifest_preprocess
1717
implicit none
1818
private
1919

20-
public :: preprocess_config_t, new_preprocess_config, new_preprocessors
20+
public :: preprocess_config_t, new_preprocess_config, new_preprocessors, operator(==)
2121

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

4242
end type preprocess_config_t
4343

44+
interface operator(==)
45+
module procedure preprocess_is_same
46+
end interface
47+
4448
contains
4549

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

157-
if (pr < 1) return
161+
if (pr < 1) return
158162

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

182186
end subroutine info
183187

188+
logical function preprocess_is_same(this,that)
189+
class(preprocess_config_t), intent(in) :: this
190+
class(preprocess_config_t), intent(in) :: that
191+
192+
integer :: istr
193+
194+
preprocess_is_same = .false.
195+
196+
select type (other=>that)
197+
type is (preprocess_config_t)
198+
if (allocated(this%name).neqv.allocated(other%name)) return
199+
if (allocated(this%name)) then
200+
if (.not.(this%name==other%name)) return
201+
endif
202+
if (.not.(allocated(this%suffixes).eqv.allocated(other%suffixes))) return
203+
if (allocated(this%suffixes)) then
204+
do istr=1,size(this%suffixes)
205+
if (.not.(this%suffixes(istr)%s==other%suffixes(istr)%s)) return
206+
end do
207+
end if
208+
if (.not.(allocated(this%directories).eqv.allocated(other%directories))) return
209+
if (allocated(this%directories)) then
210+
do istr=1,size(this%directories)
211+
if (.not.(this%directories(istr)%s==other%directories(istr)%s)) return
212+
end do
213+
end if
214+
if (.not.(allocated(this%macros).eqv.allocated(other%macros))) return
215+
if (allocated(this%macros)) then
216+
do istr=1,size(this%macros)
217+
if (.not.(this%macros(istr)%s==other%macros(istr)%s)) return
218+
end do
219+
end if
220+
221+
class default
222+
! Not the same type
223+
return
224+
end select
225+
226+
!> All checks passed!
227+
preprocess_is_same = .true.
228+
229+
end function preprocess_is_same
230+
184231
end module fpm_manifest_preprocess

src/fpm/toml.f90

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -123,6 +123,7 @@ subroutine check_keys(table, valid_keys, error)
123123
type(error_t), allocatable, intent(out) :: error
124124

125125
type(toml_key), allocatable :: keys(:)
126+
type(toml_table), pointer :: child
126127
character(:), allocatable :: name, value, valid_keys_string
127128
integer :: ikey, ivalid
128129

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

145146
! Check if value can be mapped or else (wrong type) show error message with the error location.
146-
! Right now, it can only be mapped to a string, but this can be extended in the future.
147+
! Right now, it can only be mapped to a string or to a child node, but this can be extended in the future.
147148
call get_value(table, keys(ikey)%key, value)
148149
if (.not. allocated(value)) then
149-
allocate (error)
150-
error%message = "'"//name//"' has an invalid '"//keys(ikey)%key//"' entry."
151-
return
150+
151+
! If value is not a string, check if it is a child node
152+
call get_value(table, keys(ikey)%key, child)
153+
154+
if (.not.associated(child)) then
155+
allocate (error)
156+
error%message = "'"//name//"' has an invalid '"//keys(ikey)%key//"' entry."
157+
return
158+
endif
152159
end if
153160
end do
154161

0 commit comments

Comments
 (0)