Skip to content

Commit 0631482

Browse files
committed
compare cache.toml and fpm.toml dependencies and force update when changed
1 parent f9b8832 commit 0631482

File tree

4 files changed

+94
-30
lines changed

4 files changed

+94
-30
lines changed

src/fpm.f90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,6 @@ subroutine build_model(model, settings, package, error)
6363
do i = 1, model%deps%ndep
6464

6565
if (model%deps%dep(i)%update) then
66-
print *, ' Updating model dependency ',model%deps%dep(i)%name,' ...'
6766
call model%deps%update(model%deps%dep(i)%name,error)
6867
if (allocated(error)) return
6968
end if

src/fpm/dependency.f90

Lines changed: 53 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -59,9 +59,10 @@ module fpm_dependency
5959
use fpm_environment, only : get_os_type, OS_WINDOWS
6060
use fpm_error, only : error_t, fatal_error
6161
use fpm_filesystem, only : exists, join_path, mkdir, canon_path, windows_path
62-
use fpm_git, only : git_target_revision, git_target_default, git_revision
62+
use fpm_git, only : git_target_revision, git_target_default, git_revision, operator(==)
6363
use fpm_manifest, only : package_config_t, dependency_config_t, &
6464
get_package_data
65+
use fpm_manifest_dependency, only: manifest_has_changed
6566
use fpm_strings, only : string_t, operator(.in.)
6667
use fpm_toml, only : toml_table, toml_key, toml_error, toml_serializer, &
6768
toml_parse, get_value, set_value, add_table
@@ -217,8 +218,6 @@ subroutine new_dependency_node(self, dependency, version, proj_dir, update)
217218
self%update = update
218219
end if
219220

220-
print *, 'new node from self=',self%name,' dep=',dependency%name, 'update=',update
221-
222221
end subroutine new_dependency_node
223222

224223
!> Add project dependencies, each depth level after each other.
@@ -368,12 +367,33 @@ subroutine add_dependency(self, dependency, error)
368367
type(error_t), allocatable, intent(out) :: error
369368

370369
integer :: id
370+
logical :: needs_update
371+
type(dependency_node_t) :: new_dep
371372

372373
id = self%find(dependency)
373-
if (id == 0) then
374+
375+
exists: if (id > 0) then
376+
377+
!> A dependency with this same name is already in the dependency tree.
378+
379+
!> check if it needs to be updated
380+
call new_dependency_node(new_dep, dependency)
381+
needs_update = dependency_has_changed(self%dep(id), new_dep)
382+
383+
!> Ensure an update is requested whenever the dependency has changed
384+
if (needs_update) then
385+
write(self%unit, out_fmt) "Update needed:", dependency%name
386+
call new_dependency_node(self%dep(id), dependency, update=.true.)
387+
endif
388+
389+
else exists
390+
391+
!> New dependency: add from scratch
374392
self%ndep = self%ndep + 1
375393
call new_dependency_node(self%dep(self%ndep), dependency)
376-
end if
394+
395+
end if exists
396+
377397

378398
end subroutine add_dependency
379399

@@ -457,8 +477,6 @@ subroutine resolve_dependency(self, dependency, root, error)
457477
character(len=:), allocatable :: manifest, proj_dir, revision
458478
logical :: fetch
459479

460-
print *, 'resolving dependency ',dependency%name,': done=',dependency%done,' update=',dependency%update
461-
462480
if (dependency%done) return
463481

464482
fetch = .false.
@@ -562,34 +580,17 @@ subroutine register(self, package, root, fetch, revision, error)
562580
type(error_t), allocatable, intent(out) :: error
563581

564582
logical :: update
565-
character(:), allocatable :: sver,pver
566583

567584
update = .false.
568585
if (self%name /= package%name) then
569586
call fatal_error(error, "Dependency name '"//package%name// &
570587
& "' found, but expected '"//self%name//"' instead")
571588
end if
572589

573-
! If this is the package node, always request an update of
574-
! the cache whenever its version changes
575-
is_package: if (self%name==package%name .and. self%path==".") then
576-
577-
if (self%version/=package%version) update = .true.
578-
579-
end if is_package
580-
581-
call self%version%to_string(sver)
582-
call package%version%to_string(pver)
583-
print *, 'self%version=',sver,' package version = ',pver
584-
585590
self%version = package%version
586-
587-
print *, 'self%proj_dir=',self%proj_dir,' package dir = ',root
588-
589591
self%proj_dir = root
590592

591593
if (allocated(self%git).and.present(revision)) then
592-
print *, 'self revision = ',self%revision,' revision = ',revision,' fetch = ',fetch
593594
self%revision = revision
594595
if (.not.fetch) then
595596
! git object is HEAD always allows an update
@@ -604,8 +605,6 @@ subroutine register(self, package, root, fetch, revision, error)
604605
self%update = update
605606
self%done = .true.
606607

607-
print *, 'dep = ',self%name,' update=',update
608-
609608
end subroutine register
610609

611610
!> Read dependency tree from file
@@ -835,4 +834,32 @@ pure subroutine resize_dependency_node(var, n)
835834

836835
end subroutine resize_dependency_node
837836

837+
!> Check if a dependency node has changed
838+
logical function dependency_has_changed(this,that) result(has_changed)
839+
!> Two instances of the same dependency to be compared
840+
type(dependency_node_t), intent(in) :: this,that
841+
842+
has_changed = .true.
843+
844+
!> All the following entities must be equal for the dependency to not have changed
845+
if (manifest_has_changed(this, that)) return
846+
847+
!> For now, only perform the following checks if both are available. A dependency in cache.toml
848+
!> will always have this metadata; a dependency from fpm.toml which has not been fetched yet
849+
!> may not have it
850+
if (allocated(this%version) .and. allocated(that%version)) then
851+
if (this%version/=that%version) return
852+
endif
853+
if (allocated(this%revision) .and. allocated(that%revision)) then
854+
if (this%revision/=that%revision) return
855+
endif
856+
if (allocated(this%proj_dir) .and. allocated(that%proj_dir)) then
857+
if (this%proj_dir/=that%proj_dir) return
858+
endif
859+
860+
!> All checks passed: the two dependencies have no differences
861+
has_changed = .false.
862+
863+
end function dependency_has_changed
864+
838865
end module fpm_dependency

src/fpm/git.f90

Lines changed: 17 additions & 0 deletions
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 :: operator(==)
1112

1213

1314
!> Possible git target
@@ -54,6 +55,10 @@ module fpm_git
5455
end type git_target_t
5556

5657

58+
interface operator(==)
59+
module procedure git_target_eq
60+
end interface
61+
5762
contains
5863

5964

@@ -128,6 +133,18 @@ function git_target_tag(url, tag) result(self)
128133

129134
end function git_target_tag
130135

136+
!> Check that two git targets are equal
137+
logical function git_target_eq(this,that) result(is_equal)
138+
139+
!> Two input git targets
140+
type(git_target_t), intent(in) :: this,that
141+
142+
is_equal = this%descriptor == that%descriptor .and. &
143+
this%url == that%url .and. &
144+
this%object == that%object
145+
146+
end function git_target_eq
147+
131148

132149
subroutine checkout(self, local_path, error)
133150

src/fpm/manifest/dependency.f90

Lines changed: 24 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -25,14 +25,14 @@
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
28+
& git_target_revision, git_target_default, operator(==)
2929
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
3030
use fpm_filesystem, only: windows_path
3131
use fpm_environment, only: get_os_type, OS_WINDOWS
3232
implicit none
3333
private
3434

35-
public :: dependency_config_t, new_dependency, new_dependencies
35+
public :: dependency_config_t, new_dependency, new_dependencies, manifest_has_changed
3636

3737

3838
!> Configuration meta data for a dependency
@@ -159,7 +159,7 @@ subroutine check(table, error)
159159
exit
160160
end if
161161
url_present = .true.
162-
162+
163163
case("path")
164164
if (url_present) then
165165
call syntax_error(error, "Dependency "//name//" cannot have both git and path entries")
@@ -266,5 +266,26 @@ subroutine info(self, unit, verbosity)
266266

267267
end subroutine info
268268

269+
!> Check if two dependency configurations are different
270+
logical function manifest_has_changed(this, that) result(has_changed)
271+
272+
!> Two instances of the dependency configuration
273+
class(dependency_config_t), intent(in) :: this, that
274+
275+
has_changed = .true.
276+
277+
!> Perform all checks
278+
if (this%name/=that%name) return
279+
if (this%path/=that%path) return
280+
if (allocated(this%git).neqv.allocated(that%git)) return
281+
if (allocated(this%git)) then
282+
if (.not.(this%git==that%git)) return
283+
end if
284+
285+
!> All checks passed! The two instances are equal
286+
has_changed = .false.
287+
288+
end function manifest_has_changed
289+
269290

270291
end module fpm_manifest_dependency

0 commit comments

Comments
 (0)