Skip to content

Commit 6d33e74

Browse files
authored
Allow overriding metapackages with standard dependency syntax (#928)
2 parents bd1a54d + 9a46ce4 commit 6d33e74

File tree

3 files changed

+148
-35
lines changed

3 files changed

+148
-35
lines changed

src/fpm/manifest/dependency.f90

Lines changed: 49 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,8 @@ module fpm_manifest_dependency
2929
use fpm_toml, only: toml_table, toml_key, toml_stat, get_value, check_keys
3030
use fpm_filesystem, only: windows_path, join_path
3131
use fpm_environment, only: get_os_type, OS_WINDOWS
32-
use fpm_manifest_metapackages, only: metapackage_config_t, is_meta_package, new_meta_config
32+
use fpm_manifest_metapackages, only: metapackage_config_t, is_meta_package, new_meta_config, &
33+
metapackage_request_t, new_meta_request
3334
use fpm_versioning, only: version_t, new_version
3435
implicit none
3536
private
@@ -223,46 +224,67 @@ subroutine new_dependencies(deps, table, root, meta, error)
223224

224225
type(toml_table), pointer :: node
225226
type(toml_key), allocatable :: list(:)
226-
logical, allocatable :: non_meta(:)
227+
type(dependency_config_t), allocatable :: all_deps(:)
228+
type(metapackage_request_t) :: meta_request
229+
logical, allocatable :: is_meta(:)
230+
logical :: metapackages_allowed
227231
integer :: idep, stat, ndep
228232

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

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

241-
!> Return metapackages config from this node
242-
call new_meta_config(meta, table, error)
243-
if (allocated(error)) return
244-
else
245-
ndep = size(list)
246-
end if
242+
!> Parse all meta- and non-metapackage dependencies
243+
do idep = 1, size(list)
244+
245+
! Check if this is a standard dependency node
246+
call get_value(table, list(idep)%key, node, stat=stat)
247+
is_standard_dependency: if (stat /= toml_stat%success) then
248+
249+
! See if it can be a valid metapackage name
250+
call new_meta_request(meta_request, list(idep)%key, table, error=error)
251+
252+
!> Neither a standard dep nor a metapackage
253+
if (allocated(error)) then
254+
call syntax_error(error, "Dependency "//list(idep)%key//" is not a valid metapackage or a table entry")
255+
return
256+
endif
257+
258+
!> Valid meta dependency
259+
is_meta(idep) = .true.
260+
261+
else
262+
263+
! Parse as a standard dependency
264+
is_meta(idep) = .false.
247265

248-
! Generate non-metapackage dependencies
266+
call new_dependency(all_deps(idep), node, root, error)
267+
if (allocated(error)) return
268+
269+
end if is_standard_dependency
270+
271+
end do
272+
273+
! Non-meta dependencies
274+
ndep = count(.not.is_meta)
275+
276+
! Finalize standard dependencies
249277
allocate(deps(ndep))
250278
ndep = 0
251279
do idep = 1, size(list)
252-
253-
if (present(meta) .and. is_meta_package(list(idep)%key)) cycle
254-
280+
if (is_meta(idep)) cycle
255281
ndep = ndep+1
256-
257-
call get_value(table, list(idep)%key, node, stat=stat)
258-
if (stat /= toml_stat%success) then
259-
call syntax_error(error, "Dependency "//list(idep)%key//" must be a table entry")
260-
exit
261-
end if
262-
call new_dependency(deps(ndep), node, root, error)
263-
if (allocated(error)) exit
282+
deps(ndep) = all_deps(idep)
264283
end do
265284

285+
! Finalize meta dependencies
286+
if (metapackages_allowed) call new_meta_config(meta,table,is_meta,error)
287+
266288
end subroutine new_dependencies
267289

268290
!> Write information on instance

src/fpm/manifest/meta.f90

Lines changed: 31 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ module fpm_manifest_metapackages
1616
private
1717

1818
public :: metapackage_config_t, new_meta_config, is_meta_package
19+
public :: metapackage_request_t, new_meta_request
1920

2021

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

9798
!> Construct a new metapackage request from the dependencies table
98-
subroutine new_request(self, key, table, error)
99+
subroutine new_meta_request(self, key, table, meta_allowed, error)
99100

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

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

109+
!> List of keys allowed to be metapackages
110+
logical, intent(in), optional :: meta_allowed(:)
111+
108112
!> Error handling
109113
type(error_t), allocatable, intent(out) :: error
110114

111115

112116
integer :: stat,i
113117
character(len=:), allocatable :: value
118+
logical, allocatable :: allow_meta(:)
114119
type(toml_key), allocatable :: keys(:)
115120

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

128133
call table%get_keys(keys)
129134

135+
!> Set list of entries that are allowed to be metapackages
136+
if (present(meta_allowed)) then
137+
if (size(meta_allowed)/=size(keys)) then
138+
call fatal_error(error,"Internal error: list of metapackage-enable entries does not match table size")
139+
return
140+
end if
141+
allow_meta = meta_allowed
142+
else
143+
allocate(allow_meta(size(keys)),source=.true.)
144+
endif
145+
146+
130147
do i=1,size(keys)
148+
149+
! Skip standard dependencies
150+
if (.not.allow_meta(i)) cycle
151+
131152
if (keys(i)%key==key) then
132153
call get_value(table, key, value)
133154
if (.not. allocated(value)) then
@@ -143,34 +164,37 @@ subroutine new_request(self, key, table, error)
143164
! Key is not present, metapackage not requested
144165
return
145166

146-
end subroutine new_request
167+
end subroutine new_meta_request
147168

148169
!> Construct a new build configuration from a TOML data structure
149-
subroutine new_meta_config(self, table, error)
170+
subroutine new_meta_config(self, table, meta_allowed, error)
150171

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

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

178+
!> List of keys allowed to be metapackages
179+
logical, intent(in) :: meta_allowed(:)
180+
157181
!> Error handling
158182
type(error_t), allocatable, intent(out) :: error
159183

160184
integer :: stat
161185

162186
!> The toml table is not checked here because it already passed
163187
!> the "new_dependencies" check
164-
call new_request(self%openmp, "openmp", table, error)
188+
call new_meta_request(self%openmp, "openmp", table, meta_allowed, error)
165189
if (allocated(error)) return
166190

167-
call new_request(self%stdlib, "stdlib", table, error)
191+
call new_meta_request(self%stdlib, "stdlib", table, meta_allowed, error)
168192
if (allocated(error)) return
169193

170-
call new_request(self%minpack, "minpack", table, error)
194+
call new_meta_request(self%minpack, "minpack", table, meta_allowed, error)
171195
if (allocated(error)) return
172196

173-
call new_request(self%mpi, "mpi", table, error)
197+
call new_meta_request(self%mpi, "mpi", table, meta_allowed, error)
174198
if (allocated(error)) return
175199

176200
end subroutine new_meta_config

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)