Skip to content

Commit 3ab251e

Browse files
committed
more checks to deploy to CI
1 parent 85af013 commit 3ab251e

File tree

3 files changed

+50
-12
lines changed

3 files changed

+50
-12
lines changed

src/fpm/dependency.f90

Lines changed: 25 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -310,7 +310,7 @@ subroutine add_project(self, package, error)
310310

311311
! After resolving all dependencies, check if we have cached ones to avoid updates
312312
if (allocated(self%cache)) then
313-
call new_dependency_tree(cached, cache=self%cache)
313+
call new_dependency_tree(cached, verbosity=2,cache=self%cache)
314314
call cached%load(self%cache, error)
315315
if (allocated(error)) return
316316

@@ -441,7 +441,7 @@ subroutine add_dependency_node(self, dependency, error)
441441
! the same dependency from a lower branch of the dependency tree, the existing one from
442442
! the manifest has priority
443443
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
445445
if (self%verbosity>0) write (self%unit, out_fmt) "Dependency change detected:", dependency%name
446446
self%dep(id)%update = .true.
447447
else
@@ -1182,26 +1182,44 @@ pure subroutine resize_dependency_node(var, n)
11821182
end subroutine resize_dependency_node
11831183

11841184
!> Check if a dependency node has changed
1185-
logical function dependency_has_changed(cached, manifest) result(has_changed)
1185+
logical function dependency_has_changed(cached, manifest, verbosity, iunit) result(has_changed)
11861186
!> Two instances of the same dependency to be compared
11871187
type(dependency_node_t), intent(in) :: cached, manifest
11881188

1189+
!> Log verbosity
1190+
integer, intent(in) :: verbosity, iunit
1191+
11891192
has_changed = .true.
11901193

11911194
!> All the following entities must be equal for the dependency to not have changed
1192-
if (manifest_has_changed(cached=cached, manifest=manifest)) return
1195+
if (manifest_has_changed(cached=cached, manifest=manifest, verbosity=verbosity, iunit=iunit)) return
11931196

11941197
!> For now, only perform the following checks if both are available. A dependency in cache.toml
11951198
!> will always have this metadata; a dependency from fpm.toml which has not been fetched yet
11961199
!> may not have it
11971200
if (allocated(cached%version) .and. allocated(manifest%version)) then
1198-
if (cached%version /= manifest%version) return
1201+
if (cached%version /= manifest%version) then
1202+
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed: "//cached%version%s()//" vs. "//manifest%version%s()
1203+
return
1204+
endif
1205+
else
1206+
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed presence "
11991207
end if
12001208
if (allocated(cached%revision) .and. allocated(manifest%revision)) then
1201-
if (cached%revision /= manifest%revision) return
1209+
if (cached%revision /= manifest%revision) then
1210+
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
1211+
return
1212+
endif
1213+
else
1214+
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed presence "
12021215
end if
12031216
if (allocated(cached%proj_dir) .and. allocated(manifest%proj_dir)) then
1204-
if (cached%proj_dir /= manifest%proj_dir) return
1217+
if (cached%proj_dir /= manifest%proj_dir) then
1218+
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed: "//cached%proj_dir//" vs. "//manifest%proj_dir
1219+
return
1220+
endif
1221+
else
1222+
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed presence "
12051223
end if
12061224

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

src/fpm/git.f90

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,9 @@ module fpm_git
6060
module procedure git_target_eq
6161
end interface
6262

63+
!> Common output format for writing to the command line
64+
character(len=*), parameter :: out_fmt = '("#", *(1x, g0))'
65+
6366
contains
6467

6568

@@ -147,19 +150,27 @@ logical function git_target_eq(this,that) result(is_equal)
147150
end function git_target_eq
148151

149152
!> Check that a cached dependency matches a manifest request
150-
logical function git_matches_manifest(cached,manifest)
153+
logical function git_matches_manifest(cached,manifest,verbosity,iunit)
151154

152155
!> Two input git targets
153156
type(git_target_t), intent(in) :: cached,manifest
154157

158+
integer, intent(in) :: verbosity,iunit
159+
155160
git_matches_manifest = cached%url == manifest%url
156-
if (.not.git_matches_manifest) return
161+
if (.not.git_matches_manifest) then
162+
if (verbosity>1) write(iunit,out_fmt) "GIT URL has changed: ",cached%url," vs. ", manifest%url
163+
return
164+
endif
157165

158166
!> The manifest dependency only contains partial information (what's requested),
159167
!> while the cached dependency always stores a commit hash because it's built
160168
!> after the repo is available (saved as git_descriptor%revision==revision).
161169
!> So, comparing against the descriptor is not reliable
162170
git_matches_manifest = cached%object == manifest%object
171+
if (.not.git_matches_manifest) then
172+
if (verbosity>1) write(iunit,out_fmt) "GIT OBJECT has changed: ",cached%object," vs. ", manifest%object
173+
end if
163174

164175
end function git_matches_manifest
165176

src/fpm/manifest/dependency.f90

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,9 @@ module fpm_manifest_dependency
6363

6464
end type dependency_config_t
6565

66+
!> Common output format for writing to the command line
67+
character(len=*), parameter :: out_fmt = '("#", *(1x, g0))'
68+
6669
contains
6770

6871
!> Construct a new dependency configuration from a TOML data structure
@@ -274,17 +277,23 @@ subroutine info(self, unit, verbosity)
274277
end subroutine info
275278

276279
!> Check if two dependency configurations are different
277-
logical function manifest_has_changed(cached, manifest) result(has_changed)
280+
logical function manifest_has_changed(cached, manifest, verbosity, iunit) result(has_changed)
278281

279282
!> Two instances of the dependency configuration
280283
class(dependency_config_t), intent(in) :: cached, manifest
281284

285+
!> Log verbosity
286+
integer, intent(in) :: verbosity, iunit
287+
282288
has_changed = .true.
283289

284290
!> Perform all checks
285-
if (allocated(cached%git).neqv.allocated(manifest%git)) return
291+
if (allocated(cached%git).neqv.allocated(manifest%git)) then
292+
if (verbosity>1) write(iunit,out_fmt) "GIT presence has changed. "
293+
return
294+
endif
286295
if (allocated(cached%git)) then
287-
if (.not.git_matches_manifest(cached%git,manifest%git)) return
296+
if (.not.git_matches_manifest(cached%git,manifest%git,verbosity,iunit)) return
288297
end if
289298

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

0 commit comments

Comments
 (0)