@@ -16,6 +16,7 @@ module fpm_manifest_metapackages
16
16
private
17
17
18
18
public :: metapackage_config_t, new_meta_config, is_meta_package
19
+ public :: metapackage_request_t, new_meta_request
19
20
20
21
21
22
! > Configuration data for a single metapackage request
@@ -95,7 +96,7 @@ subroutine request_parse(self, version_request, error)
95
96
end subroutine request_parse
96
97
97
98
! > 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 )
99
100
100
101
type (metapackage_request_t), intent (out ) :: self
101
102
@@ -105,12 +106,16 @@ subroutine new_request(self, key, table, error)
105
106
! > Instance of the TOML data structure
106
107
type (toml_table), intent (inout ) :: table
107
108
109
+ ! > List of keys allowed to be metapackages
110
+ logical , intent (in ), optional :: meta_allowed(:)
111
+
108
112
! > Error handling
109
113
type (error_t), allocatable , intent (out ) :: error
110
114
111
115
112
116
integer :: stat,i
113
117
character (len= :), allocatable :: value
118
+ logical , allocatable :: allow_meta(:)
114
119
type (toml_key), allocatable :: keys(:)
115
120
116
121
call request_destroy(self)
@@ -127,7 +132,23 @@ subroutine new_request(self, key, table, error)
127
132
128
133
call table% get_keys(keys)
129
134
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
+
130
147
do i= 1 ,size (keys)
148
+
149
+ ! Skip standard dependencies
150
+ if (.not. meta_allowed(i)) cycle
151
+
131
152
if (keys(i)% key== key) then
132
153
call get_value(table, key, value)
133
154
if (.not. allocated (value)) then
@@ -143,34 +164,37 @@ subroutine new_request(self, key, table, error)
143
164
! Key is not present, metapackage not requested
144
165
return
145
166
146
- end subroutine new_request
167
+ end subroutine new_meta_request
147
168
148
169
! > 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 )
150
171
151
172
! > Instance of the build configuration
152
173
type (metapackage_config_t), intent (out ) :: self
153
174
154
175
! > Instance of the TOML data structure
155
176
type (toml_table), intent (inout ) :: table
156
177
178
+ ! > List of keys allowed to be metapackages
179
+ logical , intent (in ) :: meta_allowed(:)
180
+
157
181
! > Error handling
158
182
type (error_t), allocatable , intent (out ) :: error
159
183
160
184
integer :: stat
161
185
162
186
! > The toml table is not checked here because it already passed
163
187
! > 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)
165
189
if (allocated (error)) return
166
190
167
- call new_request (self% stdlib, " stdlib" , table, error)
191
+ call new_meta_request (self% stdlib, " stdlib" , table, meta_allowed , error)
168
192
if (allocated (error)) return
169
193
170
- call new_request (self% minpack, " minpack" , table, error)
194
+ call new_meta_request (self% minpack, " minpack" , table, meta_allowed , error)
171
195
if (allocated (error)) return
172
196
173
- call new_request (self% mpi, " mpi" , table, error)
197
+ call new_meta_request (self% mpi, " mpi" , table, meta_allowed , error)
174
198
if (allocated (error)) return
175
199
176
200
end subroutine new_meta_config
0 commit comments