@@ -59,9 +59,10 @@ module fpm_dependency
59
59
use fpm_environment, only : get_os_type, OS_WINDOWS
60
60
use fpm_error, only : error_t, fatal_error
61
61
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 (==)
63
63
use fpm_manifest, only : package_config_t, dependency_config_t, &
64
64
get_package_data
65
+ use fpm_manifest_dependency, only: manifest_has_changed
65
66
use fpm_strings, only : string_t, operator (.in .)
66
67
use fpm_toml, only : toml_table, toml_key, toml_error, toml_serializer, &
67
68
toml_parse, get_value, set_value, add_table
@@ -217,8 +218,6 @@ subroutine new_dependency_node(self, dependency, version, proj_dir, update)
217
218
self% update = update
218
219
end if
219
220
220
- print * , ' new node from self=' ,self% name,' dep=' ,dependency% name, ' update=' ,update
221
-
222
221
end subroutine new_dependency_node
223
222
224
223
! > Add project dependencies, each depth level after each other.
@@ -368,12 +367,33 @@ subroutine add_dependency(self, dependency, error)
368
367
type (error_t), allocatable , intent (out ) :: error
369
368
370
369
integer :: id
370
+ logical :: needs_update
371
+ type (dependency_node_t) :: new_dep
371
372
372
373
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
374
392
self% ndep = self% ndep + 1
375
393
call new_dependency_node(self% dep(self% ndep), dependency)
376
- end if
394
+
395
+ end if exists
396
+
377
397
378
398
end subroutine add_dependency
379
399
@@ -457,8 +477,6 @@ subroutine resolve_dependency(self, dependency, root, error)
457
477
character (len= :), allocatable :: manifest, proj_dir, revision
458
478
logical :: fetch
459
479
460
- print * , ' resolving dependency ' ,dependency% name,' : done=' ,dependency% done,' update=' ,dependency% update
461
-
462
480
if (dependency% done) return
463
481
464
482
fetch = .false.
@@ -562,34 +580,17 @@ subroutine register(self, package, root, fetch, revision, error)
562
580
type (error_t), allocatable , intent (out ) :: error
563
581
564
582
logical :: update
565
- character (:), allocatable :: sver,pver
566
583
567
584
update = .false.
568
585
if (self% name /= package% name) then
569
586
call fatal_error(error, " Dependency name '" // package% name// &
570
587
& " ' found, but expected '" // self% name// " ' instead" )
571
588
end if
572
589
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
-
585
590
self% version = package% version
586
-
587
- print * , ' self%proj_dir=' ,self% proj_dir,' package dir = ' ,root
588
-
589
591
self% proj_dir = root
590
592
591
593
if (allocated (self% git).and. present (revision)) then
592
- print * , ' self revision = ' ,self% revision,' revision = ' ,revision,' fetch = ' ,fetch
593
594
self% revision = revision
594
595
if (.not. fetch) then
595
596
! git object is HEAD always allows an update
@@ -604,8 +605,6 @@ subroutine register(self, package, root, fetch, revision, error)
604
605
self% update = update
605
606
self% done = .true.
606
607
607
- print * , ' dep = ' ,self% name,' update=' ,update
608
-
609
608
end subroutine register
610
609
611
610
! > Read dependency tree from file
@@ -835,4 +834,32 @@ pure subroutine resize_dependency_node(var, n)
835
834
836
835
end subroutine resize_dependency_node
837
836
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
+
838
865
end module fpm_dependency
0 commit comments