@@ -45,6 +45,7 @@ subroutine collect_package_dependencies(tests)
45
45
& new_unittest(" status-after-load" , test_status), &
46
46
& new_unittest(" add-dependencies" , test_add_dependencies), &
47
47
& new_unittest(" update-dependencies" , test_update_dependencies), &
48
+ & new_unittest(" do-not-update-dependencies" , test_non_updated_dependencies), &
48
49
& new_unittest(" registry-dir-not-found" , registry_dir_not_found, should_fail= .true. ), &
49
50
& new_unittest(" no-versions-in-registry" , no_versions_in_registry, should_fail= .true. ), &
50
51
& new_unittest(" local-registry-specified-version-not-found" , local_registry_specified_version_not_found, should_fail= .true. ), &
@@ -254,15 +255,15 @@ subroutine test_add_dependencies(error)
254
255
255
256
end subroutine test_add_dependencies
256
257
257
- subroutine test_update_dependencies (error )
258
+ subroutine test_non_updated_dependencies (error )
258
259
259
260
! > Error handling
260
261
type (error_t), allocatable , intent (out ) :: error
261
262
262
263
type (toml_table) :: cache, manifest
263
264
type (toml_table), pointer :: ptr
264
265
type (toml_key), allocatable :: list(:)
265
- type (dependency_tree_t) :: deps, cached_deps
266
+ type (dependency_tree_t) :: cached, manifest_deps
266
267
integer :: ii
267
268
268
269
! Create a dummy cache
@@ -283,11 +284,99 @@ subroutine test_update_dependencies(error)
283
284
call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
284
285
285
286
! Load into a dependency tree
286
- call new_dependency_tree(cached_deps)
287
- call cached_deps% load(cache, error)
287
+ call new_dependency_tree(cached)
288
+ call cached% load(cache, error)
289
+ if (allocated (error)) return
290
+ ! Mark all dependencies as "cached"
291
+ do ii= 1 ,cached% ndep
292
+ cached% dep(ii)% cached = .true.
293
+ end do
288
294
call cache% destroy()
295
+
296
+ ! Create a dummy manifest, with different version
297
+ manifest = toml_table()
298
+ call add_table(manifest, " dep1" , ptr)
299
+ call set_value(ptr, " version" , " 1.1.1" )
300
+ call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
301
+ call add_table(manifest, " dep2" , ptr)
302
+ call set_value(ptr, " git" , " https://gitlab.com/fortran-lang/lin4" )
303
+ call set_value(ptr, " rev" , " c0ffee" )
304
+ call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
305
+ call add_table(manifest, " dep3" , ptr)
306
+ call set_value(ptr, " git" , " https://gitlab.com/fortran-lang/pkg3" )
307
+ call set_value(ptr, " rev" , " t4a" )
308
+ call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
309
+
310
+ ! Load dependencies from manifest
311
+ call new_dependency_tree(manifest_deps)
312
+ call manifest_deps% load(manifest, error)
313
+ call manifest% destroy()
289
314
if (allocated (error)) return
290
315
316
+ ! Add cached dependencies afterwards; will flag those that need udpate
317
+ do ii= 1 ,cached% ndep
318
+ cached% dep(ii)% cached = .true.
319
+ call manifest_deps% add(cached% dep(ii), error)
320
+ if (allocated (error)) return
321
+ end do
322
+
323
+ ! Test that dependencies 1-2 are flagged as "update"
324
+ if (.not. manifest_deps% dep(1 )% update) then
325
+ call test_failed(error, " Updated dependency (different version) not detected" )
326
+ return
327
+ end if
328
+ if (.not. manifest_deps% dep(2 )% update) then
329
+ call test_failed(error, " Updated dependency (git address) not detected" )
330
+ return
331
+ end if
332
+
333
+
334
+ ! Test that dependency 3 is flagged as "not update"
335
+ if (manifest_deps% dep(3 )% update) then
336
+ call test_failed(error, " Updated dependency (git rev) detected, should not be" )
337
+ return
338
+ end if
339
+
340
+ end subroutine test_non_updated_dependencies
341
+
342
+ subroutine test_update_dependencies (error )
343
+
344
+ ! > Error handling
345
+ type (error_t), allocatable , intent (out ) :: error
346
+
347
+ type (toml_table) :: cache, manifest
348
+ type (toml_table), pointer :: ptr
349
+ type (toml_key), allocatable :: list(:)
350
+ type (dependency_tree_t) :: cached, manifest_deps
351
+ integer :: ii
352
+
353
+ ! Create a dummy cache
354
+ cache = toml_table()
355
+ call add_table(cache, " dep1" , ptr)
356
+ call set_value(ptr, " version" , " 1.1.0" )
357
+ call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
358
+ call add_table(cache, " dep2" , ptr)
359
+ call set_value(ptr, " git" , " https://gitlab.com/fortran-lang/lin2" )
360
+ call set_value(ptr, " rev" , " c0ffee" )
361
+ call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
362
+ call add_table(cache, " dep3" , ptr)
363
+ call set_value(ptr, " git" , " https://gitlab.com/fortran-lang/pkg3" )
364
+ call set_value(ptr, " rev" , " t4a" )
365
+ call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
366
+ call add_table(cache, " dep4" , ptr)
367
+ call set_value(ptr, " version" , " 1.0.0" )
368
+ call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
369
+
370
+ ! Load into a dependency tree
371
+ call new_dependency_tree(cached)
372
+ call cached% load(cache, error)
373
+ if (allocated (error)) return
374
+ ! Mark all dependencies as "cached"
375
+ do ii= 1 ,cached% ndep
376
+ cached% dep(ii)% cached = .true.
377
+ end do
378
+ call cache% destroy()
379
+
291
380
! Create a dummy manifest, with different version
292
381
manifest = toml_table()
293
382
call add_table(manifest, " dep1" , ptr)
@@ -303,27 +392,28 @@ subroutine test_update_dependencies(error)
303
392
call set_value(ptr, " proj-dir" , " fpm-tmp1-dir" )
304
393
305
394
! Load dependencies from manifest
306
- call new_dependency_tree(deps )
307
- call deps % load(manifest, error)
395
+ call new_dependency_tree(manifest_deps )
396
+ call manifest_deps % load(manifest, error)
308
397
call manifest% destroy()
309
398
if (allocated (error)) return
310
399
311
- ! Add manifest dependencies
312
- do ii = 1 , cached_deps% ndep
313
- call deps% add(cached_deps% dep(ii), error)
314
- if (allocated (error)) return
400
+ ! Add cached dependencies afterwards; will flag those that need udpate
401
+ do ii= 1 ,cached% ndep
402
+ cached% dep(ii)% cached = .true.
403
+ call manifest_deps% add(cached% dep(ii), error)
404
+ if (allocated (error)) return
315
405
end do
316
406
317
407
! Test that all dependencies are flagged as "update"
318
- if (.not. deps % dep(1 )% update) then
408
+ if (.not. manifest_deps % dep(1 )% update) then
319
409
call test_failed(error, " Updated dependency (different version) not detected" )
320
410
return
321
411
end if
322
- if (.not. deps % dep(2 )% update) then
412
+ if (.not. manifest_deps % dep(2 )% update) then
323
413
call test_failed(error, " Updated dependency (git address) not detected" )
324
414
return
325
415
end if
326
- if (.not. deps % dep(3 )% update) then
416
+ if (.not. manifest_deps % dep(3 )% update) then
327
417
call test_failed(error, " Updated dependency (git rev) not detected" )
328
418
return
329
419
end if
0 commit comments