Skip to content

Commit 5550f5e

Browse files
committed
verify cached preprocessors
1 parent 44076f4 commit 5550f5e

File tree

3 files changed

+66
-17
lines changed

3 files changed

+66
-17
lines changed

src/fpm.f90

Lines changed: 20 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -109,12 +109,31 @@ 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+
print *, 'dep preprocess? ',allocated(dep%preprocess),' nam,e=',dep%name
131+
if (allocated(dep%preprocess)) then
132+
do j = 1, size(dep%preprocess)
133+
if (dep%preprocess(j)%name == "cpp") then
134+
if (.not. has_cpp) has_cpp = .true.
135+
if (allocated(dep%preprocess(j)%macros)) then
136+
model%packages(i)%macros = [model%packages(i)%macros, dep%preprocess(j)%macros]
118137
end if
119138
else
120139
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &

src/fpm/dependency.f90

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1187,6 +1187,8 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
11871187
!> Log verbosity
11881188
integer, intent(in) :: verbosity, iunit
11891189

1190+
integer :: ip
1191+
11901192
has_changed = .true.
11911193

11921194
!> All the following entities must be equal for the dependency to not have changed
@@ -1219,6 +1221,20 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
12191221
else
12201222
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed presence "
12211223
end if
1224+
if (allocated(cached%preprocess) .eqv. allocated(manifest%preprocess)) then
1225+
if (size(cached%preprocess) /= size(manifest%preprocess)) then
1226+
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS has changed size"
1227+
return
1228+
end if
1229+
do ip=1,size(cached%preprocess)
1230+
if (cached%preprocess(ip) /= manifest%preprocess(ip)) then
1231+
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS config has changed"
1232+
return
1233+
end if
1234+
end do
1235+
else
1236+
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS has changed presence "
1237+
end if
12221238

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

src/fpm/manifest/dependency.f90

Lines changed: 30 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -100,6 +100,22 @@ subroutine new_dependency(self, table, root, error)
100100
call table%get_key(self%name)
101101
call get_value(table, "namespace", self%namespace)
102102

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+
print *, 'has preprocess? ',associated(child)
113+
if (associated(child)) then
114+
call new_preprocessors(self%preprocess, child, error)
115+
print *, 'size preprocess ',size(self%preprocess),' error? =',allocated(error)
116+
if (allocated(error)) return
117+
endif
118+
103119
call get_value(table, "path", uri)
104120
if (allocated(uri)) then
105121
if (get_os_type() == OS_WINDOWS) uri = windows_path(uri)
@@ -135,21 +151,6 @@ subroutine new_dependency(self, table, root, error)
135151
return
136152
end if
137153

138-
call get_value(table, "v", requested_version)
139-
140-
if (allocated(requested_version)) then
141-
if (.not. allocated(self%requested_version)) allocate (self%requested_version)
142-
call new_version(self%requested_version, requested_version, error)
143-
if (allocated(error)) return
144-
end if
145-
146-
!> Get optional preprocessor directives
147-
call get_value(table, "preprocess", child, requested=.false.)
148-
if (associated(child)) then
149-
call new_preprocessors(self%preprocess, child, error)
150-
if (allocated(error)) return
151-
end if
152-
153154
end subroutine new_dependency
154155

155156
!> Check local schema for allowed entries
@@ -163,6 +164,7 @@ subroutine check(table, error)
163164

164165
character(len=:), allocatable :: name
165166
type(toml_key), allocatable :: list(:)
167+
type(toml_table), pointer :: child
166168

167169
!> List of valid keys for the dependency table.
168170
character(*), dimension(*), parameter :: valid_keys = [character(24) :: &
@@ -185,7 +187,6 @@ subroutine check(table, error)
185187
end if
186188

187189
call check_keys(table, valid_keys, error)
188-
print *, 'check keys ',allocated(error)
189190
if (allocated(error)) return
190191

191192
if (table%has_key("path") .and. table%has_key("git")) then
@@ -218,6 +219,18 @@ subroutine check(table, error)
218219
return
219220
end if
220221

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

223236
!> Construct new dependency array from a TOML data structure
@@ -279,6 +292,7 @@ subroutine new_dependencies(deps, table, root, meta, error)
279292
! Parse as a standard dependency
280293
is_meta(idep) = .false.
281294

295+
print *, 'new dependency ',all_deps(idep)%name
282296
call new_dependency(all_deps(idep), node, root, error)
283297
if (allocated(error)) return
284298

0 commit comments

Comments
 (0)