@@ -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
@@ -95,6 +96,8 @@ module fpm_dependency
95
96
contains
96
97
! > Update dependency from project manifest
97
98
procedure :: register
99
+ ! > Print information on this instance
100
+ procedure :: info
98
101
end type dependency_node_t
99
102
100
103
@@ -118,7 +121,7 @@ module fpm_dependency
118
121
contains
119
122
! > Overload procedure to add new dependencies to the tree
120
123
generic :: add = > add_project, add_project_dependencies, add_dependencies, &
121
- add_dependency
124
+ add_dependency, add_dependency_node
122
125
! > Main entry point to add a project
123
126
procedure , private :: add_project
124
127
! > Add a project and its dependencies to the dependency tree
@@ -127,6 +130,8 @@ module fpm_dependency
127
130
procedure , private :: add_dependencies
128
131
! > Add a single dependency to the dependency tree
129
132
procedure , private :: add_dependency
133
+ ! > Add a single dependency node to the dependency tree
134
+ procedure , private :: add_dependency_node
130
135
! > Resolve dependencies
131
136
generic :: resolve = > resolve_dependencies, resolve_dependency
132
137
! > Resolve dependencies
@@ -158,9 +163,11 @@ module fpm_dependency
158
163
! > Write dependency tree to TOML data structure
159
164
procedure , private :: dump_to_toml
160
165
! > Update dependency tree
161
- generic :: update = > update_dependency
166
+ generic :: update = > update_dependency,update_tree
162
167
! > Update a list of dependencies
163
168
procedure , private :: update_dependency
169
+ ! > Update all dependencies in the tree
170
+ procedure , private :: update_tree
164
171
end type dependency_tree_t
165
172
166
173
! > Common output format for writing to the command line
@@ -191,7 +198,7 @@ subroutine new_dependency_tree(self, verbosity, cache)
191
198
end subroutine new_dependency_tree
192
199
193
200
! > 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 )
195
202
! > Instance of the dependency node
196
203
type (dependency_node_t), intent (out ) :: self
197
204
! > Dependency configuration data
@@ -219,6 +226,49 @@ pure subroutine new_dependency_node(self, dependency, version, proj_dir, update)
219
226
220
227
end subroutine new_dependency_node
221
228
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
+
222
272
! > Add project dependencies, each depth level after each other.
223
273
! >
224
274
! > We implement this algorithm in an interative rather than a recursive fashion
@@ -356,22 +406,58 @@ subroutine add_dependencies(self, dependency, error)
356
406
357
407
end subroutine add_dependencies
358
408
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 )
361
412
! > Instance of the dependency tree
362
413
class(dependency_tree_t), intent (inout ) :: self
363
414
! > Dependency configuration to add
364
- type (dependency_config_t ), intent (in ) :: dependency
415
+ type (dependency_node_t ), intent (in ) :: dependency
365
416
! > Error handling
366
417
type (error_t), allocatable , intent (out ) :: error
367
418
368
419
integer :: id
420
+ logical :: needs_update
369
421
370
422
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
372
441
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)
375
461
376
462
end subroutine add_dependency
377
463
@@ -400,6 +486,7 @@ subroutine update_dependency(self, name, error)
400
486
if (self% verbosity > 1 ) then
401
487
write (self% unit, out_fmt) " Update:" , dep% name
402
488
end if
489
+ write (self% unit, out_fmt) " Update:" , dep% name
403
490
proj_dir = join_path(self% dep_dir, dep% name)
404
491
call dep% git% checkout(proj_dir, error)
405
492
if (allocated (error)) return
@@ -419,6 +506,23 @@ subroutine update_dependency(self, name, error)
419
506
420
507
end subroutine update_dependency
421
508
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
+
422
526
! > Resolve all dependencies in the tree
423
527
subroutine resolve_dependencies (self , root , error )
424
528
! > Instance of the dependency tree
@@ -811,4 +915,32 @@ pure subroutine resize_dependency_node(var, n)
811
915
812
916
end subroutine resize_dependency_node
813
917
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
+
814
946
end module fpm_dependency
0 commit comments