@@ -310,7 +310,7 @@ subroutine add_project(self, package, error)
310
310
311
311
! After resolving all dependencies, check if we have cached ones to avoid updates
312
312
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)
314
314
call cached% load(self% cache, error)
315
315
if (allocated (error)) return
316
316
@@ -441,7 +441,7 @@ subroutine add_dependency_node(self, dependency, error)
441
441
! the same dependency from a lower branch of the dependency tree, the existing one from
442
442
! the manifest has priority
443
443
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
445
445
if (self% verbosity> 0 ) write (self% unit, out_fmt) " Dependency change detected:" , dependency% name
446
446
self% dep(id)% update = .true.
447
447
else
@@ -454,6 +454,7 @@ subroutine add_dependency_node(self, dependency, error)
454
454
! New dependency: add from scratch
455
455
self% ndep = self% ndep + 1
456
456
self% dep(self% ndep) = dependency
457
+ self% dep(self% ndep)% update = .false.
457
458
end if
458
459
459
460
end subroutine add_dependency_node
@@ -576,6 +577,7 @@ subroutine resolve_dependency(self, dependency, global_settings, root, error)
576
577
577
578
if (dependency% done) return
578
579
580
+ fetch = .false.
579
581
if (allocated (dependency% proj_dir)) then
580
582
proj_dir = dependency% proj_dir
581
583
else if (allocated (dependency% path)) then
@@ -947,16 +949,12 @@ subroutine register(self, package, root, fetch, revision, error)
947
949
if (allocated (self% git) .and. present (revision)) then
948
950
self% revision = revision
949
951
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)
956
954
end if
957
955
end if
958
956
959
- self% update = update
957
+ if (update) self% update = update
960
958
self% done = .true.
961
959
962
960
end subroutine register
@@ -1182,26 +1180,44 @@ pure subroutine resize_dependency_node(var, n)
1182
1180
end subroutine resize_dependency_node
1183
1181
1184
1182
! > 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)
1186
1184
! > Two instances of the same dependency to be compared
1187
1185
type (dependency_node_t), intent (in ) :: cached, manifest
1188
1186
1187
+ ! > Log verbosity
1188
+ integer , intent (in ) :: verbosity, iunit
1189
+
1189
1190
has_changed = .true.
1190
1191
1191
1192
! > 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
1193
1194
1194
1195
! > For now, only perform the following checks if both are available. A dependency in cache.toml
1195
1196
! > will always have this metadata; a dependency from fpm.toml which has not been fetched yet
1196
1197
! > may not have it
1197
1198
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 "
1199
1205
end if
1200
1206
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 "
1202
1213
end if
1203
1214
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 "
1205
1221
end if
1206
1222
1207
1223
! > All checks passed: the two dependencies have no differences
0 commit comments