Skip to content

Commit 9a46ce4

Browse files
committed
add metapackage overriding tests
1 parent f8c7282 commit 9a46ce4

File tree

1 file changed

+68
-1
lines changed

1 file changed

+68
-1
lines changed

test/fpm_test/test_package_dependencies.f90

Lines changed: 68 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@ module test_package_dependencies
77
use fpm_os, only: get_current_directory
88
use fpm_dependency
99
use fpm_manifest_dependency
10+
use fpm_manifest_metapackages, only: metapackage_config_t
11+
use fpm_manifest, only: package_config_t, get_package_data
1012
use fpm_toml
1113
use fpm_settings, only: fpm_global_settings, get_registry_settings, get_global_settings
1214
use fpm_downloader, only: downloader_t
@@ -45,10 +47,11 @@ subroutine collect_package_dependencies(tests)
4547
& new_unittest("status-after-load", test_status), &
4648
& new_unittest("add-dependencies", test_add_dependencies), &
4749
& new_unittest("update-dependencies", test_update_dependencies), &
50+
& new_unittest("metapackage-override", test_metapackage_override), &
4851
& new_unittest("do-not-update-dependencies", test_non_updated_dependencies), &
4952
& new_unittest("registry-dir-not-found", registry_dir_not_found, should_fail=.true.), &
5053
& new_unittest("no-versions-in-registry", no_versions_in_registry, should_fail=.true.), &
51-
& new_unittest("local-registry-specified-version-not-found", local_registry_specified_version_not_found, should_fail=.true.), &
54+
& new_unittest("local-registry-specified-version-not-found", local_registry_specified_version_not_found, should_fail=.true.), &
5255
& new_unittest("local-registry-specified-no-manifest", local_registry_specified_no_manifest, should_fail=.true.), &
5356
& new_unittest("local-registry-specified-has-manifest", local_registry_specified_has_manifest), &
5457
& new_unittest("local-registry-specified-not-a-dir", local_registry_specified_not_a_dir, should_fail=.true.), &
@@ -421,6 +424,70 @@ subroutine test_update_dependencies(error)
421424

422425
end subroutine test_update_dependencies
423426

427+
428+
!> Test that a metapackage is overridden if a regular dependency is provided
429+
subroutine test_metapackage_override(error)
430+
431+
!> Error handling
432+
type(error_t), allocatable, intent(out) :: error
433+
434+
type(toml_table) :: manifest
435+
type(toml_table), pointer :: ptr
436+
type(dependency_config_t), allocatable :: deps(:)
437+
type(metapackage_config_t) :: meta
438+
logical :: found
439+
integer :: i
440+
441+
! Create a dummy manifest, with a standard git dependency for stdlib
442+
manifest = toml_table()
443+
call add_table(manifest, "stdlib", ptr)
444+
call set_value(ptr, "git", "https://github.com/fortran-lang/stdlib")
445+
call set_value(ptr, "branch", "stdlib-fpm")
446+
447+
! Load dependencies from manifest
448+
call new_dependencies(deps, manifest, meta=meta, error=error)
449+
if (allocated(error)) return
450+
451+
! Check that stdlib is in the regular dependency list
452+
found = .false.
453+
do i=1,size(deps)
454+
if (deps(i)%name=="stdlib") found = .true.
455+
end do
456+
457+
if (.not.found) then
458+
call test_failed(error,"standard git-based dependency for stdlib not recognized")
459+
return
460+
end if
461+
call manifest%destroy()
462+
463+
464+
! Create a dummy manifest, with a version-based metapackage dependency for stdlib
465+
manifest = toml_table()
466+
call set_value(manifest, "stdlib", "*")
467+
468+
! Load dependencies from manifest
469+
call new_dependencies(deps, manifest, meta=meta, error=error)
470+
if (allocated(error)) return
471+
472+
! Check that stdlib is in the metapackage config and not the standard dependencies
473+
found = .false.
474+
do i=1,size(deps)
475+
if (deps(i)%name=="stdlib") found = .true.
476+
end do
477+
478+
if (found) then
479+
call test_failed(error,"metapackage dependency for stdlib should not be in the tree")
480+
return
481+
end if
482+
call manifest%destroy()
483+
484+
if (.not.meta%stdlib%on) then
485+
call test_failed(error,"metapackage dependency for stdlib should be in the metapackage config")
486+
return
487+
end if
488+
489+
end subroutine test_metapackage_override
490+
424491
!> Directories for namespace and package name not found in path registry.
425492
subroutine registry_dir_not_found(error)
426493
type(error_t), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)