Skip to content

Commit 28e1e5f

Browse files
authored
Only update dependencies between cached build and manifest (#871)
* only update dependencies that were cached * add test to CI * update dependency tree test * simplify CI * build separate `cache` and `project` trees, then compare dependencies * update cached deps test * improve comment * test dependency that should not be updated
1 parent 2a69727 commit 28e1e5f

File tree

8 files changed

+202
-41
lines changed

8 files changed

+202
-41
lines changed

ci/run_tests.sh

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -201,6 +201,10 @@ EXIT_CODE=0
201201
test $EXIT_CODE -eq 1
202202
popd
203203

204+
# test dependency priority
205+
pushd dependency_priority
206+
"$fpm" run
207+
popd
204208

205209
# Cleanup
206210
rm -rf ./*/build
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
# dependency_tree
2+
Check dependency tree cascade. "Standard" fpm dependencies feature that the highest-priority one wins
3+
(i.e., top-level dependencies in the manifest, or the first time it's found down the dependency tree)
4+
Check this behavior is confirmed.
Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
program main
2+
use tomlf_version, only: tomlf_version_string
3+
implicit none
4+
5+
print *, 'using version =',tomlf_version_string
6+
print *, 'should be =0.3.1'
7+
8+
if (tomlf_version_string=="0.3.1") then
9+
stop 0
10+
else
11+
stop 1
12+
endif
13+
14+
end program main
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
name = "dependency_tree"
2+
version = "0.1.0"
3+
[build]
4+
auto-executables=true
5+
[dependencies]
6+
# Request toml-f v0.3.1.
7+
toml-f.git = "https://github.com/toml-f/toml-f"
8+
toml-f.tag = "v0.3.1"
9+
# jonquil 0.2.0 requires toml-f v0.4.0.
10+
# Because 0.4.0 is a derived dependency, it should not be used
11+
jonquil.git = "https://github.com/toml-f/jonquil"
12+
jonquil.tag = "v0.2.0"

src/fpm/dependency.f90

Lines changed: 40 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -93,6 +93,8 @@ module fpm_dependency
9393
logical :: done = .false.
9494
!> Dependency should be updated
9595
logical :: update = .false.
96+
!> Dependency was loaded from a cache
97+
logical :: cached = .false.
9698
contains
9799
!> Update dependency from project manifest.
98100
procedure :: register
@@ -284,12 +286,9 @@ subroutine add_project(self, package, error)
284286
type(error_t), allocatable, intent(out) :: error
285287

286288
type(dependency_config_t) :: dependency
289+
type(dependency_tree_t) :: cached
287290
character(len=*), parameter :: root = '.'
288-
289-
if (allocated(self%cache)) then
290-
call self%load(self%cache, error)
291-
if (allocated(error)) return
292-
end if
291+
integer :: id
293292

294293
if (.not. exists(self%dep_dir)) then
295294
call mkdir(self%dep_dir)
@@ -309,6 +308,20 @@ subroutine add_project(self, package, error)
309308
call self%add(package, root, .true., error)
310309
if (allocated(error)) return
311310

311+
! After resolving all dependencies, check if we have cached ones to avoid updates
312+
if (allocated(self%cache)) then
313+
call new_dependency_tree(cached, cache=self%cache)
314+
call cached%load(self%cache, error)
315+
if (allocated(error)) return
316+
317+
! Skip root node
318+
do id=2,cached%ndep
319+
cached%dep(id)%cached = .true.
320+
call self%add(cached%dep(id), error)
321+
if (allocated(error)) return
322+
end do
323+
end if
324+
312325
! Now decent into the dependency tree, level for level
313326
do while (.not. self%finished())
314327
call self%resolve(root, error)
@@ -423,11 +436,19 @@ subroutine add_dependency_node(self, dependency, error)
423436
! Check if it needs to be updated
424437
id = self%find(dependency%name)
425438

426-
! Ensure an update is requested whenever the dependency has changed
427-
if (dependency_has_changed(self%dep(id), dependency)) then
428-
write (self%unit, out_fmt) "Dependency change detected:", dependency%name
429-
self%dep(id) = dependency
430-
self%dep(id)%update = .true.
439+
! If this dependency was in the cache, and we're now requesting a different version
440+
! in the manifest, ensure it is marked for update. Otherwise, if we're just querying
441+
! the same dependency from a lower branch of the dependency tree, the existing one from
442+
! the manifest has priority
443+
if (dependency%cached) then
444+
if (dependency_has_changed(dependency, self%dep(id))) then
445+
write (self%unit, out_fmt) "Dependency change detected:", dependency%name
446+
self%dep(id)%update = .true.
447+
else
448+
! Store the cached one
449+
self%dep(id) = dependency
450+
self%dep(id)%update = .false.
451+
endif
431452
end if
432453
else
433454
! New dependency: add from scratch
@@ -1161,26 +1182,26 @@ pure subroutine resize_dependency_node(var, n)
11611182
end subroutine resize_dependency_node
11621183

11631184
!> Check if a dependency node has changed
1164-
logical function dependency_has_changed(this, that) result(has_changed)
1185+
logical function dependency_has_changed(cached, manifest) result(has_changed)
11651186
!> Two instances of the same dependency to be compared
1166-
type(dependency_node_t), intent(in) :: this, that
1187+
type(dependency_node_t), intent(in) :: cached, manifest
11671188

11681189
has_changed = .true.
11691190

11701191
!> All the following entities must be equal for the dependency to not have changed
1171-
if (manifest_has_changed(this, that)) return
1192+
if (manifest_has_changed(cached=cached, manifest=manifest)) return
11721193

11731194
!> For now, only perform the following checks if both are available. A dependency in cache.toml
11741195
!> will always have this metadata; a dependency from fpm.toml which has not been fetched yet
11751196
!> may not have it
1176-
if (allocated(this%version) .and. allocated(that%version)) then
1177-
if (this%version /= that%version) return
1197+
if (allocated(cached%version) .and. allocated(manifest%version)) then
1198+
if (cached%version /= manifest%version) return
11781199
end if
1179-
if (allocated(this%revision) .and. allocated(that%revision)) then
1180-
if (this%revision /= that%revision) return
1200+
if (allocated(cached%revision) .and. allocated(manifest%revision)) then
1201+
if (cached%revision /= manifest%revision) return
11811202
end if
1182-
if (allocated(this%proj_dir) .and. allocated(that%proj_dir)) then
1183-
if (this%proj_dir /= that%proj_dir) return
1203+
if (allocated(cached%proj_dir) .and. allocated(manifest%proj_dir)) then
1204+
if (cached%proj_dir /= manifest%proj_dir) return
11841205
end if
11851206

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

src/fpm/git.f90

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module fpm_git
88
public :: git_target_default, git_target_branch, git_target_tag, &
99
& git_target_revision
1010
public :: git_revision
11+
public :: git_matches_manifest
1112
public :: operator(==)
1213

1314

@@ -36,7 +37,7 @@ module fpm_git
3637
type :: git_target_t
3738

3839
!> Kind of the git target
39-
integer, private :: descriptor = git_descriptor%default
40+
integer :: descriptor = git_descriptor%default
4041

4142
!> Target URL of the git repository
4243
character(len=:), allocatable :: url
@@ -145,6 +146,23 @@ logical function git_target_eq(this,that) result(is_equal)
145146

146147
end function git_target_eq
147148

149+
!> Check that a cached dependency matches a manifest request
150+
logical function git_matches_manifest(cached,manifest)
151+
152+
!> Two input git targets
153+
type(git_target_t), intent(in) :: cached,manifest
154+
155+
git_matches_manifest = cached%url == manifest%url
156+
if (.not.git_matches_manifest) return
157+
158+
!> The manifest dependency only contains partial information (what's requested),
159+
!> while the cached dependency always stores a commit hash because it's built
160+
!> after the repo is available (saved as git_descriptor%revision==revision).
161+
!> So, comparing against the descriptor is not reliable
162+
git_matches_manifest = cached%object == manifest%object
163+
164+
end function git_matches_manifest
165+
148166

149167
subroutine checkout(self, local_path, error)
150168

src/fpm/manifest/dependency.f90

Lines changed: 6 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@
2525
module fpm_manifest_dependency
2626
use fpm_error, only: error_t, syntax_error
2727
use fpm_git, only: git_target_t, git_target_tag, git_target_branch, &
28-
& git_target_revision, git_target_default, operator(==)
28+
& git_target_revision, git_target_default, operator(==), git_matches_manifest
2929
use fpm_toml, only: toml_table, toml_key, toml_stat, get_value, check_keys
3030
use fpm_filesystem, only: windows_path
3131
use fpm_environment, only: get_os_type, OS_WINDOWS
@@ -274,19 +274,17 @@ subroutine info(self, unit, verbosity)
274274
end subroutine info
275275

276276
!> Check if two dependency configurations are different
277-
logical function manifest_has_changed(this, that) result(has_changed)
277+
logical function manifest_has_changed(cached, manifest) result(has_changed)
278278

279279
!> Two instances of the dependency configuration
280-
class(dependency_config_t), intent(in) :: this, that
280+
class(dependency_config_t), intent(in) :: cached, manifest
281281

282282
has_changed = .true.
283283

284284
!> Perform all checks
285-
if (this%name/=that%name) return
286-
if (this%path/=that%path) return
287-
if (allocated(this%git).neqv.allocated(that%git)) return
288-
if (allocated(this%git)) then
289-
if (.not.(this%git==that%git)) return
285+
if (allocated(cached%git).neqv.allocated(manifest%git)) return
286+
if (allocated(cached%git)) then
287+
if (.not.git_matches_manifest(cached%git,manifest%git)) return
290288
end if
291289

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

test/fpm_test/test_package_dependencies.f90

Lines changed: 103 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,7 @@ subroutine collect_package_dependencies(tests)
4545
& new_unittest("status-after-load", test_status), &
4646
& new_unittest("add-dependencies", test_add_dependencies), &
4747
& new_unittest("update-dependencies", test_update_dependencies), &
48+
& new_unittest("do-not-update-dependencies", test_non_updated_dependencies), &
4849
& new_unittest("registry-dir-not-found", registry_dir_not_found, should_fail=.true.), &
4950
& new_unittest("no-versions-in-registry", no_versions_in_registry, should_fail=.true.), &
5051
& new_unittest("local-registry-specified-version-not-found", local_registry_specified_version_not_found, should_fail=.true.), &
@@ -254,15 +255,15 @@ subroutine test_add_dependencies(error)
254255

255256
end subroutine test_add_dependencies
256257

257-
subroutine test_update_dependencies(error)
258+
subroutine test_non_updated_dependencies(error)
258259

259260
!> Error handling
260261
type(error_t), allocatable, intent(out) :: error
261262

262263
type(toml_table) :: cache, manifest
263264
type(toml_table), pointer :: ptr
264265
type(toml_key), allocatable :: list(:)
265-
type(dependency_tree_t) :: deps, cached_deps
266+
type(dependency_tree_t) :: cached, manifest_deps
266267
integer :: ii
267268

268269
! Create a dummy cache
@@ -283,11 +284,99 @@ subroutine test_update_dependencies(error)
283284
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
284285

285286
! Load into a dependency tree
286-
call new_dependency_tree(cached_deps)
287-
call cached_deps%load(cache, error)
287+
call new_dependency_tree(cached)
288+
call cached%load(cache, error)
289+
if (allocated(error)) return
290+
! Mark all dependencies as "cached"
291+
do ii=1,cached%ndep
292+
cached%dep(ii)%cached = .true.
293+
end do
288294
call cache%destroy()
295+
296+
! Create a dummy manifest, with different version
297+
manifest = toml_table()
298+
call add_table(manifest, "dep1", ptr)
299+
call set_value(ptr, "version", "1.1.1")
300+
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
301+
call add_table(manifest, "dep2", ptr)
302+
call set_value(ptr, "git", "https://gitlab.com/fortran-lang/lin4")
303+
call set_value(ptr, "rev", "c0ffee")
304+
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
305+
call add_table(manifest, "dep3", ptr)
306+
call set_value(ptr, "git", "https://gitlab.com/fortran-lang/pkg3")
307+
call set_value(ptr, "rev", "t4a")
308+
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
309+
310+
! Load dependencies from manifest
311+
call new_dependency_tree(manifest_deps)
312+
call manifest_deps%load(manifest, error)
313+
call manifest%destroy()
289314
if (allocated(error)) return
290315

316+
! Add cached dependencies afterwards; will flag those that need udpate
317+
do ii=1,cached%ndep
318+
cached%dep(ii)%cached = .true.
319+
call manifest_deps%add(cached%dep(ii), error)
320+
if (allocated(error)) return
321+
end do
322+
323+
! Test that dependencies 1-2 are flagged as "update"
324+
if (.not. manifest_deps%dep(1)%update) then
325+
call test_failed(error, "Updated dependency (different version) not detected")
326+
return
327+
end if
328+
if (.not. manifest_deps%dep(2)%update) then
329+
call test_failed(error, "Updated dependency (git address) not detected")
330+
return
331+
end if
332+
333+
334+
! Test that dependency 3 is flagged as "not update"
335+
if (manifest_deps%dep(3)%update) then
336+
call test_failed(error, "Updated dependency (git rev) detected, should not be")
337+
return
338+
end if
339+
340+
end subroutine test_non_updated_dependencies
341+
342+
subroutine test_update_dependencies(error)
343+
344+
!> Error handling
345+
type(error_t), allocatable, intent(out) :: error
346+
347+
type(toml_table) :: cache, manifest
348+
type(toml_table), pointer :: ptr
349+
type(toml_key), allocatable :: list(:)
350+
type(dependency_tree_t) :: cached, manifest_deps
351+
integer :: ii
352+
353+
! Create a dummy cache
354+
cache = toml_table()
355+
call add_table(cache, "dep1", ptr)
356+
call set_value(ptr, "version", "1.1.0")
357+
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
358+
call add_table(cache, "dep2", ptr)
359+
call set_value(ptr, "git", "https://gitlab.com/fortran-lang/lin2")
360+
call set_value(ptr, "rev", "c0ffee")
361+
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
362+
call add_table(cache, "dep3", ptr)
363+
call set_value(ptr, "git", "https://gitlab.com/fortran-lang/pkg3")
364+
call set_value(ptr, "rev", "t4a")
365+
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
366+
call add_table(cache, "dep4", ptr)
367+
call set_value(ptr, "version", "1.0.0")
368+
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
369+
370+
! Load into a dependency tree
371+
call new_dependency_tree(cached)
372+
call cached%load(cache, error)
373+
if (allocated(error)) return
374+
! Mark all dependencies as "cached"
375+
do ii=1,cached%ndep
376+
cached%dep(ii)%cached = .true.
377+
end do
378+
call cache%destroy()
379+
291380
! Create a dummy manifest, with different version
292381
manifest = toml_table()
293382
call add_table(manifest, "dep1", ptr)
@@ -303,27 +392,28 @@ subroutine test_update_dependencies(error)
303392
call set_value(ptr, "proj-dir", "fpm-tmp1-dir")
304393

305394
! Load dependencies from manifest
306-
call new_dependency_tree(deps)
307-
call deps%load(manifest, error)
395+
call new_dependency_tree(manifest_deps)
396+
call manifest_deps%load(manifest, error)
308397
call manifest%destroy()
309398
if (allocated(error)) return
310399

311-
! Add manifest dependencies
312-
do ii = 1, cached_deps%ndep
313-
call deps%add(cached_deps%dep(ii), error)
314-
if (allocated(error)) return
400+
! Add cached dependencies afterwards; will flag those that need udpate
401+
do ii=1,cached%ndep
402+
cached%dep(ii)%cached = .true.
403+
call manifest_deps%add(cached%dep(ii), error)
404+
if (allocated(error)) return
315405
end do
316406

317407
! Test that all dependencies are flagged as "update"
318-
if (.not. deps%dep(1)%update) then
408+
if (.not. manifest_deps%dep(1)%update) then
319409
call test_failed(error, "Updated dependency (different version) not detected")
320410
return
321411
end if
322-
if (.not. deps%dep(2)%update) then
412+
if (.not. manifest_deps%dep(2)%update) then
323413
call test_failed(error, "Updated dependency (git address) not detected")
324414
return
325415
end if
326-
if (.not. deps%dep(3)%update) then
416+
if (.not. manifest_deps%dep(3)%update) then
327417
call test_failed(error, "Updated dependency (git rev) not detected")
328418
return
329419
end if

0 commit comments

Comments
 (0)