Skip to content

Commit dd3e229

Browse files
authored
Automated dependency update: restore deterministic behavior (#875)
Fix undefined behavior from 1f604b4, was triggering inconsistent module updates
2 parents 8d482f8 + d2c9425 commit dd3e229

File tree

5 files changed

+84
-20
lines changed

5 files changed

+84
-20
lines changed

ci/run_tests.sh

Lines changed: 22 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -203,7 +203,28 @@ popd
203203

204204
# test dependency priority
205205
pushd dependency_priority
206-
"$fpm" run
206+
207+
# first build should run OK
208+
EXIT_CODE=0
209+
"$fpm" run || EXIT_CODE=$?
210+
test $EXIT_CODE -eq 0
211+
212+
"$fpm" build --verbose
213+
214+
# Build again, should update nothing
215+
"$fpm" build --verbose > build.log
216+
if [[ -n "$(grep Update build.log)" ]]; then
217+
echo "Some dependencies were updated that should not be";
218+
exit 1;
219+
fi
220+
221+
# Request update --clean, should update all dependencies
222+
"$fpm" update --clean --verbose > update.log
223+
if [[ -z "$(grep Update update.log)" ]]; then
224+
echo "No updated dependencies after 'fpm update --clean'";
225+
exit 1;
226+
fi
227+
207228
popd
208229

209230
# Cleanup

src/fpm/cmd/update.f90

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,13 @@ subroutine cmd_update(settings)
4040
call deps%add(package, error)
4141
call handle_error(error)
4242

43+
! Force-update all dependencies if `--clean`
44+
if (settings%clean) then
45+
do ii = 1, deps%ndep
46+
deps%dep(ii)%update = .true.
47+
end do
48+
end if
49+
4350
if (settings%fetch_only) return
4451

4552
if (size(settings%name) == 0) then

src/fpm/dependency.f90

Lines changed: 30 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -310,7 +310,7 @@ subroutine add_project(self, package, error)
310310

311311
! After resolving all dependencies, check if we have cached ones to avoid updates
312312
if (allocated(self%cache)) then
313-
call new_dependency_tree(cached, cache=self%cache)
313+
call new_dependency_tree(cached, verbosity=self%verbosity,cache=self%cache)
314314
call cached%load(self%cache, error)
315315
if (allocated(error)) return
316316

@@ -441,7 +441,7 @@ subroutine add_dependency_node(self, dependency, error)
441441
! the same dependency from a lower branch of the dependency tree, the existing one from
442442
! the manifest has priority
443443
if (dependency%cached) then
444-
if (dependency_has_changed(dependency, self%dep(id))) then
444+
if (dependency_has_changed(dependency, self%dep(id), self%verbosity, self%unit)) then
445445
if (self%verbosity>0) write (self%unit, out_fmt) "Dependency change detected:", dependency%name
446446
self%dep(id)%update = .true.
447447
else
@@ -454,6 +454,7 @@ subroutine add_dependency_node(self, dependency, error)
454454
! New dependency: add from scratch
455455
self%ndep = self%ndep + 1
456456
self%dep(self%ndep) = dependency
457+
self%dep(self%ndep)%update = .false.
457458
end if
458459

459460
end subroutine add_dependency_node
@@ -576,6 +577,7 @@ subroutine resolve_dependency(self, dependency, global_settings, root, error)
576577

577578
if (dependency%done) return
578579

580+
fetch = .false.
579581
if (allocated(dependency%proj_dir)) then
580582
proj_dir = dependency%proj_dir
581583
else if (allocated(dependency%path)) then
@@ -947,16 +949,12 @@ subroutine register(self, package, root, fetch, revision, error)
947949
if (allocated(self%git) .and. present(revision)) then
948950
self%revision = revision
949951
if (.not. fetch) then
950-
! git object is HEAD always allows an update
951-
update = .not. allocated(self%git%object)
952-
if (.not. update) then
953-
! allow update in case the revision does not match the requested object
954-
update = revision /= self%git%object
955-
end if
952+
! Change in revision ID was checked already. Only update if ALL git information is missing
953+
update = .not. allocated(self%git%url)
956954
end if
957955
end if
958956

959-
self%update = update
957+
if (update) self%update = update
960958
self%done = .true.
961959

962960
end subroutine register
@@ -1182,26 +1180,44 @@ pure subroutine resize_dependency_node(var, n)
11821180
end subroutine resize_dependency_node
11831181

11841182
!> Check if a dependency node has changed
1185-
logical function dependency_has_changed(cached, manifest) result(has_changed)
1183+
logical function dependency_has_changed(cached, manifest, verbosity, iunit) result(has_changed)
11861184
!> Two instances of the same dependency to be compared
11871185
type(dependency_node_t), intent(in) :: cached, manifest
11881186

1187+
!> Log verbosity
1188+
integer, intent(in) :: verbosity, iunit
1189+
11891190
has_changed = .true.
11901191

11911192
!> All the following entities must be equal for the dependency to not have changed
1192-
if (manifest_has_changed(cached=cached, manifest=manifest)) return
1193+
if (manifest_has_changed(cached=cached, manifest=manifest, verbosity=verbosity, iunit=iunit)) return
11931194

11941195
!> For now, only perform the following checks if both are available. A dependency in cache.toml
11951196
!> will always have this metadata; a dependency from fpm.toml which has not been fetched yet
11961197
!> may not have it
11971198
if (allocated(cached%version) .and. allocated(manifest%version)) then
1198-
if (cached%version /= manifest%version) return
1199+
if (cached%version /= manifest%version) then
1200+
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed: "//cached%version%s()//" vs. "//manifest%version%s()
1201+
return
1202+
endif
1203+
else
1204+
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed presence "
11991205
end if
12001206
if (allocated(cached%revision) .and. allocated(manifest%revision)) then
1201-
if (cached%revision /= manifest%revision) return
1207+
if (cached%revision /= manifest%revision) then
1208+
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
1209+
return
1210+
endif
1211+
else
1212+
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed presence "
12021213
end if
12031214
if (allocated(cached%proj_dir) .and. allocated(manifest%proj_dir)) then
1204-
if (cached%proj_dir /= manifest%proj_dir) return
1215+
if (cached%proj_dir /= manifest%proj_dir) then
1216+
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed: "//cached%proj_dir//" vs. "//manifest%proj_dir
1217+
return
1218+
endif
1219+
else
1220+
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed presence "
12051221
end if
12061222

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

src/fpm/git.f90

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,9 @@ module fpm_git
6060
module procedure git_target_eq
6161
end interface
6262

63+
!> Common output format for writing to the command line
64+
character(len=*), parameter :: out_fmt = '("#", *(1x, g0))'
65+
6366
contains
6467

6568

@@ -147,19 +150,27 @@ logical function git_target_eq(this,that) result(is_equal)
147150
end function git_target_eq
148151

149152
!> Check that a cached dependency matches a manifest request
150-
logical function git_matches_manifest(cached,manifest)
153+
logical function git_matches_manifest(cached,manifest,verbosity,iunit)
151154

152155
!> Two input git targets
153156
type(git_target_t), intent(in) :: cached,manifest
154157

158+
integer, intent(in) :: verbosity,iunit
159+
155160
git_matches_manifest = cached%url == manifest%url
156-
if (.not.git_matches_manifest) return
161+
if (.not.git_matches_manifest) then
162+
if (verbosity>1) write(iunit,out_fmt) "GIT URL has changed: ",cached%url," vs. ", manifest%url
163+
return
164+
endif
157165

158166
!> The manifest dependency only contains partial information (what's requested),
159167
!> while the cached dependency always stores a commit hash because it's built
160168
!> after the repo is available (saved as git_descriptor%revision==revision).
161169
!> So, comparing against the descriptor is not reliable
162170
git_matches_manifest = cached%object == manifest%object
171+
if (.not.git_matches_manifest) then
172+
if (verbosity>1) write(iunit,out_fmt) "GIT OBJECT has changed: ",cached%object," vs. ", manifest%object
173+
end if
163174

164175
end function git_matches_manifest
165176

src/fpm/manifest/dependency.f90

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,9 @@ module fpm_manifest_dependency
6363

6464
end type dependency_config_t
6565

66+
!> Common output format for writing to the command line
67+
character(len=*), parameter :: out_fmt = '("#", *(1x, g0))'
68+
6669
contains
6770

6871
!> Construct a new dependency configuration from a TOML data structure
@@ -274,17 +277,23 @@ subroutine info(self, unit, verbosity)
274277
end subroutine info
275278

276279
!> Check if two dependency configurations are different
277-
logical function manifest_has_changed(cached, manifest) result(has_changed)
280+
logical function manifest_has_changed(cached, manifest, verbosity, iunit) result(has_changed)
278281

279282
!> Two instances of the dependency configuration
280283
class(dependency_config_t), intent(in) :: cached, manifest
281284

285+
!> Log verbosity
286+
integer, intent(in) :: verbosity, iunit
287+
282288
has_changed = .true.
283289

284290
!> Perform all checks
285-
if (allocated(cached%git).neqv.allocated(manifest%git)) return
291+
if (allocated(cached%git).neqv.allocated(manifest%git)) then
292+
if (verbosity>1) write(iunit,out_fmt) "GIT presence has changed. "
293+
return
294+
endif
286295
if (allocated(cached%git)) then
287-
if (.not.git_matches_manifest(cached%git,manifest%git)) return
296+
if (.not.git_matches_manifest(cached%git,manifest%git,verbosity,iunit)) return
288297
end if
289298

290299
!> All checks passed! The two instances are equal

0 commit comments

Comments
 (0)