Skip to content

Commit

Permalink
Allow overriding metapackages with standard dependency syntax (#928)
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Jun 10, 2023
2 parents bd1a54d + 9a46ce4 commit 6d33e74
Show file tree
Hide file tree
Showing 3 changed files with 148 additions and 35 deletions.
76 changes: 49 additions & 27 deletions src/fpm/manifest/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,8 @@ module fpm_manifest_dependency
use fpm_toml, only: toml_table, toml_key, toml_stat, get_value, check_keys
use fpm_filesystem, only: windows_path, join_path
use fpm_environment, only: get_os_type, OS_WINDOWS
use fpm_manifest_metapackages, only: metapackage_config_t, is_meta_package, new_meta_config
use fpm_manifest_metapackages, only: metapackage_config_t, is_meta_package, new_meta_config, &
metapackage_request_t, new_meta_request
use fpm_versioning, only: version_t, new_version
implicit none
private
Expand Down Expand Up @@ -223,46 +224,67 @@ subroutine new_dependencies(deps, table, root, meta, error)

type(toml_table), pointer :: node
type(toml_key), allocatable :: list(:)
logical, allocatable :: non_meta(:)
type(dependency_config_t), allocatable :: all_deps(:)
type(metapackage_request_t) :: meta_request
logical, allocatable :: is_meta(:)
logical :: metapackages_allowed
integer :: idep, stat, ndep

call table%get_keys(list)
! An empty table is okay
if (size(list) < 1) return

!> Count non-metapackage dependencies, and parse metapackage config
if (present(meta)) then
ndep = 0
do idep = 1, size(list)
if (is_meta_package(list(idep)%key)) cycle
ndep = ndep+1
end do
!> Flag dependencies that should be treated as metapackages
metapackages_allowed = present(meta)
allocate(is_meta(size(list)),source=.false.)
allocate(all_deps(size(list)))

!> Return metapackages config from this node
call new_meta_config(meta, table, error)
if (allocated(error)) return
else
ndep = size(list)
end if
!> Parse all meta- and non-metapackage dependencies
do idep = 1, size(list)

! Check if this is a standard dependency node
call get_value(table, list(idep)%key, node, stat=stat)
is_standard_dependency: if (stat /= toml_stat%success) then

! See if it can be a valid metapackage name
call new_meta_request(meta_request, list(idep)%key, table, error=error)

!> Neither a standard dep nor a metapackage
if (allocated(error)) then
call syntax_error(error, "Dependency "//list(idep)%key//" is not a valid metapackage or a table entry")
return
endif

!> Valid meta dependency
is_meta(idep) = .true.

else

! Parse as a standard dependency
is_meta(idep) = .false.

! Generate non-metapackage dependencies
call new_dependency(all_deps(idep), node, root, error)
if (allocated(error)) return

end if is_standard_dependency

end do

! Non-meta dependencies
ndep = count(.not.is_meta)

! Finalize standard dependencies
allocate(deps(ndep))
ndep = 0
do idep = 1, size(list)

if (present(meta) .and. is_meta_package(list(idep)%key)) cycle

if (is_meta(idep)) cycle
ndep = ndep+1

call get_value(table, list(idep)%key, node, stat=stat)
if (stat /= toml_stat%success) then
call syntax_error(error, "Dependency "//list(idep)%key//" must be a table entry")
exit
end if
call new_dependency(deps(ndep), node, root, error)
if (allocated(error)) exit
deps(ndep) = all_deps(idep)
end do

! Finalize meta dependencies
if (metapackages_allowed) call new_meta_config(meta,table,is_meta,error)

end subroutine new_dependencies

!> Write information on instance
Expand Down
38 changes: 31 additions & 7 deletions src/fpm/manifest/meta.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module fpm_manifest_metapackages
private

public :: metapackage_config_t, new_meta_config, is_meta_package
public :: metapackage_request_t, new_meta_request


!> Configuration data for a single metapackage request
Expand Down Expand Up @@ -95,7 +96,7 @@ subroutine request_parse(self, version_request, error)
end subroutine request_parse

!> Construct a new metapackage request from the dependencies table
subroutine new_request(self, key, table, error)
subroutine new_meta_request(self, key, table, meta_allowed, error)

type(metapackage_request_t), intent(out) :: self

Expand All @@ -105,12 +106,16 @@ subroutine new_request(self, key, table, error)
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table

!> List of keys allowed to be metapackages
logical, intent(in), optional :: meta_allowed(:)

!> Error handling
type(error_t), allocatable, intent(out) :: error


integer :: stat,i
character(len=:), allocatable :: value
logical, allocatable :: allow_meta(:)
type(toml_key), allocatable :: keys(:)

call request_destroy(self)
Expand All @@ -127,7 +132,23 @@ subroutine new_request(self, key, table, error)

call table%get_keys(keys)

!> Set list of entries that are allowed to be metapackages
if (present(meta_allowed)) then
if (size(meta_allowed)/=size(keys)) then
call fatal_error(error,"Internal error: list of metapackage-enable entries does not match table size")
return
end if
allow_meta = meta_allowed
else
allocate(allow_meta(size(keys)),source=.true.)
endif


do i=1,size(keys)

! Skip standard dependencies
if (.not.allow_meta(i)) cycle

if (keys(i)%key==key) then
call get_value(table, key, value)
if (.not. allocated(value)) then
Expand All @@ -143,34 +164,37 @@ subroutine new_request(self, key, table, error)
! Key is not present, metapackage not requested
return

end subroutine new_request
end subroutine new_meta_request

!> Construct a new build configuration from a TOML data structure
subroutine new_meta_config(self, table, error)
subroutine new_meta_config(self, table, meta_allowed, error)

!> Instance of the build configuration
type(metapackage_config_t), intent(out) :: self

!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table

!> List of keys allowed to be metapackages
logical, intent(in) :: meta_allowed(:)

!> Error handling
type(error_t), allocatable, intent(out) :: error

integer :: stat

!> The toml table is not checked here because it already passed
!> the "new_dependencies" check
call new_request(self%openmp, "openmp", table, error)
call new_meta_request(self%openmp, "openmp", table, meta_allowed, error)
if (allocated(error)) return

call new_request(self%stdlib, "stdlib", table, error)
call new_meta_request(self%stdlib, "stdlib", table, meta_allowed, error)
if (allocated(error)) return

call new_request(self%minpack, "minpack", table, error)
call new_meta_request(self%minpack, "minpack", table, meta_allowed, error)
if (allocated(error)) return

call new_request(self%mpi, "mpi", table, error)
call new_meta_request(self%mpi, "mpi", table, meta_allowed, error)
if (allocated(error)) return

end subroutine new_meta_config
Expand Down
69 changes: 68 additions & 1 deletion test/fpm_test/test_package_dependencies.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ module test_package_dependencies
use fpm_os, only: get_current_directory
use fpm_dependency
use fpm_manifest_dependency
use fpm_manifest_metapackages, only: metapackage_config_t
use fpm_manifest, only: package_config_t, get_package_data
use fpm_toml
use fpm_settings, only: fpm_global_settings, get_registry_settings, get_global_settings
use fpm_downloader, only: downloader_t
Expand Down Expand Up @@ -45,10 +47,11 @@ subroutine collect_package_dependencies(tests)
& new_unittest("status-after-load", test_status), &
& new_unittest("add-dependencies", test_add_dependencies), &
& new_unittest("update-dependencies", test_update_dependencies), &
& new_unittest("metapackage-override", test_metapackage_override), &
& new_unittest("do-not-update-dependencies", test_non_updated_dependencies), &
& new_unittest("registry-dir-not-found", registry_dir_not_found, should_fail=.true.), &
& new_unittest("no-versions-in-registry", no_versions_in_registry, should_fail=.true.), &
& new_unittest("local-registry-specified-version-not-found", local_registry_specified_version_not_found, should_fail=.true.), &
& new_unittest("local-registry-specified-version-not-found", local_registry_specified_version_not_found, should_fail=.true.), &
& new_unittest("local-registry-specified-no-manifest", local_registry_specified_no_manifest, should_fail=.true.), &
& new_unittest("local-registry-specified-has-manifest", local_registry_specified_has_manifest), &
& new_unittest("local-registry-specified-not-a-dir", local_registry_specified_not_a_dir, should_fail=.true.), &
Expand Down Expand Up @@ -421,6 +424,70 @@ subroutine test_update_dependencies(error)

end subroutine test_update_dependencies


!> Test that a metapackage is overridden if a regular dependency is provided
subroutine test_metapackage_override(error)

!> Error handling
type(error_t), allocatable, intent(out) :: error

type(toml_table) :: manifest
type(toml_table), pointer :: ptr
type(dependency_config_t), allocatable :: deps(:)
type(metapackage_config_t) :: meta
logical :: found
integer :: i

! Create a dummy manifest, with a standard git dependency for stdlib
manifest = toml_table()
call add_table(manifest, "stdlib", ptr)
call set_value(ptr, "git", "https://github.com/fortran-lang/stdlib")
call set_value(ptr, "branch", "stdlib-fpm")

! Load dependencies from manifest
call new_dependencies(deps, manifest, meta=meta, error=error)
if (allocated(error)) return

! Check that stdlib is in the regular dependency list
found = .false.
do i=1,size(deps)
if (deps(i)%name=="stdlib") found = .true.
end do

if (.not.found) then
call test_failed(error,"standard git-based dependency for stdlib not recognized")
return
end if
call manifest%destroy()


! Create a dummy manifest, with a version-based metapackage dependency for stdlib
manifest = toml_table()
call set_value(manifest, "stdlib", "*")

! Load dependencies from manifest
call new_dependencies(deps, manifest, meta=meta, error=error)
if (allocated(error)) return

! Check that stdlib is in the metapackage config and not the standard dependencies
found = .false.
do i=1,size(deps)
if (deps(i)%name=="stdlib") found = .true.
end do

if (found) then
call test_failed(error,"metapackage dependency for stdlib should not be in the tree")
return
end if
call manifest%destroy()

if (.not.meta%stdlib%on) then
call test_failed(error,"metapackage dependency for stdlib should be in the metapackage config")
return
end if

end subroutine test_metapackage_override

!> Directories for namespace and package name not found in path registry.
subroutine registry_dir_not_found(error)
type(error_t), allocatable, intent(out) :: error
Expand Down

0 comments on commit 6d33e74

Please sign in to comment.