Skip to content

Commit 28c3fd9

Browse files
committed
compare preprocessing configs in the cached manifest
1 parent 5550f5e commit 28c3fd9

File tree

2 files changed

+52
-3
lines changed

2 files changed

+52
-3
lines changed

src/fpm/dependency.f90

Lines changed: 3 additions & 1 deletion
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
@@ -1227,13 +1228,14 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
12271228
return
12281229
end if
12291230
do ip=1,size(cached%preprocess)
1230-
if (cached%preprocess(ip) /= manifest%preprocess(ip)) then
1231+
if (.not.(cached%preprocess(ip) == manifest%preprocess(ip))) then
12311232
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS config has changed"
12321233
return
12331234
end if
12341235
end do
12351236
else
12361237
if (verbosity > 1) write (iunit, out_fmt) "PREPROCESS has changed presence "
1238+
return
12371239
end if
12381240

12391241
!> All checks passed: the two dependencies have no differences

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

0 commit comments

Comments
 (0)