Skip to content

Commit 251383a

Browse files
authored
Merge pull request #843 from perazz/fix_cached_dependency_update
Automated dependency tree update
2 parents b364bd8 + 28c4f16 commit 251383a

File tree

6 files changed

+268
-18
lines changed

6 files changed

+268
-18
lines changed

src/fpm.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -61,6 +61,10 @@ subroutine build_model(model, settings, package, error)
6161
call model%deps%add(package, error)
6262
if (allocated(error)) return
6363

64+
! Update dependencies where needed
65+
call model%deps%update(error)
66+
if (allocated(error)) return
67+
6468
! build/ directory should now exist
6569
if (.not.exists("build/.gitignore")) then
6670
call filewrite(join_path("build", ".gitignore"),["*"])

src/fpm/cmd/update.f90

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -43,10 +43,8 @@ subroutine cmd_update(settings)
4343
if (settings%fetch_only) return
4444

4545
if (size(settings%name) == 0) then
46-
do ii = 1, deps%ndep
47-
call deps%update(deps%dep(ii)%name, error)
48-
call handle_error(error)
49-
end do
46+
call deps%update(error)
47+
call handle_error(error)
5048
else
5149
do ii = 1, size(settings%name)
5250
call deps%update(trim(settings%name(ii)), error)

src/fpm/dependency.f90

Lines changed: 142 additions & 10 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
@@ -95,6 +96,8 @@ module fpm_dependency
9596
contains
9697
!> Update dependency from project manifest
9798
procedure :: register
99+
!> Print information on this instance
100+
procedure :: info
98101
end type dependency_node_t
99102

100103

@@ -118,7 +121,7 @@ module fpm_dependency
118121
contains
119122
!> Overload procedure to add new dependencies to the tree
120123
generic :: add => add_project, add_project_dependencies, add_dependencies, &
121-
add_dependency
124+
add_dependency, add_dependency_node
122125
!> Main entry point to add a project
123126
procedure, private :: add_project
124127
!> Add a project and its dependencies to the dependency tree
@@ -127,6 +130,8 @@ module fpm_dependency
127130
procedure, private :: add_dependencies
128131
!> Add a single dependency to the dependency tree
129132
procedure, private :: add_dependency
133+
!> Add a single dependency node to the dependency tree
134+
procedure, private :: add_dependency_node
130135
!> Resolve dependencies
131136
generic :: resolve => resolve_dependencies, resolve_dependency
132137
!> Resolve dependencies
@@ -158,9 +163,11 @@ module fpm_dependency
158163
!> Write dependency tree to TOML data structure
159164
procedure, private :: dump_to_toml
160165
!> Update dependency tree
161-
generic :: update => update_dependency
166+
generic :: update => update_dependency,update_tree
162167
!> Update a list of dependencies
163168
procedure, private :: update_dependency
169+
!> Update all dependencies in the tree
170+
procedure, private :: update_tree
164171
end type dependency_tree_t
165172

166173
!> Common output format for writing to the command line
@@ -191,7 +198,7 @@ subroutine new_dependency_tree(self, verbosity, cache)
191198
end subroutine new_dependency_tree
192199

193200
!> Create a new dependency node from a configuration
194-
pure subroutine new_dependency_node(self, dependency, version, proj_dir, update)
201+
subroutine new_dependency_node(self, dependency, version, proj_dir, update)
195202
!> Instance of the dependency node
196203
type(dependency_node_t), intent(out) :: self
197204
!> Dependency configuration data
@@ -219,6 +226,49 @@ pure subroutine new_dependency_node(self, dependency, version, proj_dir, update)
219226

220227
end subroutine new_dependency_node
221228

229+
!> Write information on instance
230+
subroutine info(self, unit, verbosity)
231+
232+
!> Instance of the dependency configuration
233+
class(dependency_node_t), intent(in) :: self
234+
235+
!> Unit for IO
236+
integer, intent(in) :: unit
237+
238+
!> Verbosity of the printout
239+
integer, intent(in), optional :: verbosity
240+
241+
integer :: pr
242+
character(:), allocatable :: ver
243+
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
244+
245+
if (present(verbosity)) then
246+
pr = verbosity
247+
else
248+
pr = 1
249+
end if
250+
251+
!> Call base object info
252+
call self%dependency_config_t%info(unit,pr)
253+
254+
if (allocated(self%version)) then
255+
call self%version%to_string(ver)
256+
write(unit, fmt) "- version", ver
257+
end if
258+
259+
if (allocated(self%proj_dir)) then
260+
write(unit, fmt) "- dir", self%proj_dir
261+
end if
262+
263+
if (allocated(self%revision)) then
264+
write(unit, fmt) "- revision", self%revision
265+
end if
266+
267+
write(unit, fmt) "- done", merge('YES','NO ',self%done)
268+
write(unit, fmt) "- update", merge('YES','NO ',self%update)
269+
270+
end subroutine info
271+
222272
!> Add project dependencies, each depth level after each other.
223273
!>
224274
!> We implement this algorithm in an interative rather than a recursive fashion
@@ -356,22 +406,58 @@ subroutine add_dependencies(self, dependency, error)
356406

357407
end subroutine add_dependencies
358408

359-
!> Add a single dependency to the dependency tree
360-
pure subroutine add_dependency(self, dependency, error)
409+
!> Add a single dependency node to the dependency tree
410+
!> Dependency nodes contain additional information (version, git, revision)
411+
subroutine add_dependency_node(self, dependency, error)
361412
!> Instance of the dependency tree
362413
class(dependency_tree_t), intent(inout) :: self
363414
!> Dependency configuration to add
364-
type(dependency_config_t), intent(in) :: dependency
415+
type(dependency_node_t), intent(in) :: dependency
365416
!> Error handling
366417
type(error_t), allocatable, intent(out) :: error
367418

368419
integer :: id
420+
logical :: needs_update
369421

370422
id = self%find(dependency)
371-
if (id == 0) then
423+
424+
exists: if (id > 0) then
425+
426+
!> A dependency with this same name is already in the dependency tree.
427+
428+
!> check if it needs to be updated
429+
needs_update = dependency_has_changed(self%dep(id), dependency)
430+
431+
!> Ensure an update is requested whenever the dependency has changed
432+
if (needs_update) then
433+
write(self%unit, out_fmt) "Dependency change detected:", dependency%name
434+
self%dep(id) = dependency
435+
self%dep(id)%update = .true.
436+
endif
437+
438+
else exists
439+
440+
!> New dependency: add from scratch
372441
self%ndep = self%ndep + 1
373-
call new_dependency_node(self%dep(self%ndep), dependency)
374-
end if
442+
self%dep(self%ndep) = dependency
443+
444+
end if exists
445+
446+
end subroutine add_dependency_node
447+
448+
!> Add a single dependency to the dependency tree
449+
subroutine add_dependency(self, dependency, error)
450+
!> Instance of the dependency tree
451+
class(dependency_tree_t), intent(inout) :: self
452+
!> Dependency configuration to add
453+
type(dependency_config_t), intent(in) :: dependency
454+
!> Error handling
455+
type(error_t), allocatable, intent(out) :: error
456+
457+
type(dependency_node_t) :: node
458+
459+
call new_dependency_node(node, dependency)
460+
call add_dependency_node(self, node, error)
375461

376462
end subroutine add_dependency
377463

@@ -400,6 +486,7 @@ subroutine update_dependency(self, name, error)
400486
if (self%verbosity > 1) then
401487
write(self%unit, out_fmt) "Update:", dep%name
402488
end if
489+
write(self%unit, out_fmt) "Update:", dep%name
403490
proj_dir = join_path(self%dep_dir, dep%name)
404491
call dep%git%checkout(proj_dir, error)
405492
if (allocated(error)) return
@@ -419,6 +506,23 @@ subroutine update_dependency(self, name, error)
419506

420507
end subroutine update_dependency
421508

509+
!> Update whole dependency tree
510+
subroutine update_tree(self, error)
511+
!> Instance of the dependency tree
512+
class(dependency_tree_t), intent(inout) :: self
513+
!> Error handling
514+
type(error_t), allocatable, intent(out) :: error
515+
516+
integer :: i
517+
518+
! Update dependencies where needed
519+
do i = 1, self%ndep
520+
call self%update(self%dep(i)%name,error)
521+
if (allocated(error)) return
522+
end do
523+
524+
end subroutine update_tree
525+
422526
!> Resolve all dependencies in the tree
423527
subroutine resolve_dependencies(self, root, error)
424528
!> Instance of the dependency tree
@@ -811,4 +915,32 @@ pure subroutine resize_dependency_node(var, n)
811915

812916
end subroutine resize_dependency_node
813917

918+
!> Check if a dependency node has changed
919+
logical function dependency_has_changed(this,that) result(has_changed)
920+
!> Two instances of the same dependency to be compared
921+
type(dependency_node_t), intent(in) :: this,that
922+
923+
has_changed = .true.
924+
925+
!> All the following entities must be equal for the dependency to not have changed
926+
if (manifest_has_changed(this, that)) return
927+
928+
!> For now, only perform the following checks if both are available. A dependency in cache.toml
929+
!> will always have this metadata; a dependency from fpm.toml which has not been fetched yet
930+
!> may not have it
931+
if (allocated(this%version) .and. allocated(that%version)) then
932+
if (this%version/=that%version) return
933+
endif
934+
if (allocated(this%revision) .and. allocated(that%revision)) then
935+
if (this%revision/=that%revision) return
936+
endif
937+
if (allocated(this%proj_dir) .and. allocated(that%proj_dir)) then
938+
if (this%proj_dir/=that%proj_dir) return
939+
endif
940+
941+
!> All checks passed: the two dependencies have no differences
942+
has_changed = .false.
943+
944+
end function dependency_has_changed
945+
814946
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)