Skip to content

Commit a10bddb

Browse files
committed
allow overriding metapackages with standard deps
1 parent b20b3dc commit a10bddb

File tree

2 files changed

+85
-32
lines changed

2 files changed

+85
-32
lines changed

src/fpm/manifest/dependency.f90

Lines changed: 54 additions & 25 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,74 @@ 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
247-
248-
! Generate non-metapackage dependencies
249-
allocate(deps(ndep))
250-
ndep = 0
242+
!> Parse all meta- and non-metapackage dependencies
251243
do idep = 1, size(list)
252244

253-
if (present(meta) .and. is_meta_package(list(idep)%key)) cycle
254-
255-
ndep = ndep+1
256-
257245
call get_value(table, list(idep)%key, node, stat=stat)
258246
if (stat /= toml_stat%success) then
259247
call syntax_error(error, "Dependency "//list(idep)%key//" must be a table entry")
260248
exit
261249
end if
262-
call new_dependency(deps(ndep), node, root, error)
263-
if (allocated(error)) exit
250+
251+
! Try to parse as a standard dependency
252+
call new_dependency(all_deps(idep), node, root, error)
253+
254+
is_standard_dependency: if (.not.allocated(error)) then
255+
256+
! If a valid git/local config is found, use it always
257+
is_meta(idep) = .false.
258+
259+
elseif (metapackages_allowed .and. is_meta_package(list(idep)%key)) then
260+
261+
!> Metapackage name: Check if this is a valid metapackage request
262+
call new_meta_request(meta_request, list(idep)%key, table, error=error)
263+
264+
!> Neither a standard dep nor a metapackage
265+
if (allocated(error)) return
266+
267+
!> Valid meta dependency
268+
is_meta(idep) = .true.
269+
270+
else
271+
272+
!> Not a standard dependency and not a metapackage: dump an error
273+
call syntax_error(error, "Dependency "//list(idep)%key//" cannot be parsed. Check input format")
274+
return
275+
276+
endif is_standard_dependency
277+
278+
end do
279+
280+
! Non-meta dependencies
281+
ndep = count(.not.is_meta)
282+
283+
! Finalize standard dependencies
284+
allocate(deps(ndep))
285+
ndep = 0
286+
do idep = 1, size(list)
287+
if (is_meta(idep)) cycle
288+
ndep = ndep+1
289+
deps(ndep) = all_deps(idep)
264290
end do
265291

292+
! Finalize meta dependencies
293+
if (metapackages_allowed) call new_meta_config(meta,table,is_meta,error)
294+
266295
end subroutine new_dependencies
267296

268297
!> 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.meta_allowed(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

0 commit comments

Comments
 (0)