@@ -12,14 +12,13 @@ module fpm
12
12
13
13
use fpm_sources, only: add_executable_sources, add_sources_from_dir
14
14
use fpm_targets, only: targets_from_sources, resolve_module_dependencies
15
- use fpm_manifest, only : get_package_data, default_executable, &
16
- default_library, package_t, default_test
15
+ use fpm_manifest, only : get_package_data, package_config_t
17
16
use fpm_error, only : error_t, fatal_error
18
- use fpm_manifest_test, only : test_t
17
+ use fpm_manifest_test, only : test_config_t
19
18
use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, &
20
19
& stdout= >output_unit, &
21
20
& stderr= >error_unit
22
- use fpm_manifest_dependency, only: dependency_t
21
+ use fpm_manifest_dependency, only: dependency_config_t
23
22
implicit none
24
23
private
25
24
public :: cmd_build, cmd_install, cmd_run
@@ -34,7 +33,7 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
34
33
type (srcfile_t), allocatable , intent (inout ), target :: sources(:)
35
34
type (string_t), allocatable , intent (inout ) :: link_libraries(:)
36
35
type (string_t), allocatable , intent (inout ) :: package_list(:)
37
- type (package_t ), intent (in ) :: package
36
+ type (package_config_t ), intent (in ) :: package
38
37
character (* ), intent (in ) :: package_root
39
38
logical , intent (in ) :: dev_depends
40
39
type (error_t), allocatable , intent (out ) :: error
@@ -76,11 +75,11 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
76
75
contains
77
76
78
77
subroutine add_dependencies (dependency_list )
79
- type (dependency_t ), intent (in ) :: dependency_list(:)
78
+ type (dependency_config_t ), intent (in ) :: dependency_list(:)
80
79
81
80
integer :: i
82
81
type (string_t) :: dep_name
83
- type (package_t ) :: dependency
82
+ type (package_config_t ) :: dependency
84
83
85
84
character (:), allocatable :: dependency_path
86
85
@@ -135,8 +134,8 @@ subroutine add_dependencies(dependency_list)
135
134
136
135
dep_name% s = dependency_list(i)% name
137
136
package_list = [package_list, dep_name]
138
- if (allocated (dependency% build_config % link)) then
139
- link_libraries = [link_libraries, dependency% build_config % link]
137
+ if (allocated (dependency% build % link)) then
138
+ link_libraries = [link_libraries, dependency% build % link]
140
139
end if
141
140
142
141
end do
@@ -151,15 +150,15 @@ subroutine build_model(model, settings, package, error)
151
150
!
152
151
type (fpm_model_t), intent (out ) :: model
153
152
type (fpm_build_settings), intent (in ) :: settings
154
- type (package_t ), intent (in ) :: package
153
+ type (package_config_t ), intent (in ) :: package
155
154
type (error_t), allocatable , intent (out ) :: error
156
155
157
156
integer :: i
158
157
type (string_t), allocatable :: package_list(:)
159
158
160
159
model% package_name = package% name
161
- if (allocated (package% build_config % link)) then
162
- model% link_libraries = package% build_config % link
160
+ if (allocated (package% build % link)) then
161
+ model% link_libraries = package% build % link
163
162
else
164
163
allocate (model% link_libraries(0 ))
165
164
end if
@@ -189,7 +188,7 @@ subroutine build_model(model, settings, package, error)
189
188
model% link_flags = ' '
190
189
191
190
! Add sources from executable directories
192
- if (is_dir(' app' ) .and. package% build_config % auto_executables) then
191
+ if (is_dir(' app' ) .and. package% build % auto_executables) then
193
192
call add_sources_from_dir(model% sources,' app' , FPM_SCOPE_APP, &
194
193
with_executables= .true. , error= error)
195
194
@@ -198,7 +197,7 @@ subroutine build_model(model, settings, package, error)
198
197
end if
199
198
200
199
end if
201
- if (is_dir(' test' ) .and. package% build_config % auto_tests) then
200
+ if (is_dir(' test' ) .and. package% build % auto_tests) then
202
201
call add_sources_from_dir(model% sources,' test' , FPM_SCOPE_TEST, &
203
202
with_executables= .true. , error= error)
204
203
@@ -209,7 +208,7 @@ subroutine build_model(model, settings, package, error)
209
208
end if
210
209
if (allocated (package% executable)) then
211
210
call add_executable_sources(model% sources, package% executable, FPM_SCOPE_APP, &
212
- auto_discover= package% build_config % auto_executables, &
211
+ auto_discover= package% build % auto_executables, &
213
212
error= error)
214
213
215
214
if (allocated (error)) then
@@ -219,7 +218,7 @@ subroutine build_model(model, settings, package, error)
219
218
end if
220
219
if (allocated (package% test)) then
221
220
call add_executable_sources(model% sources, package% test, FPM_SCOPE_TEST, &
222
- auto_discover= package% build_config % auto_tests, &
221
+ auto_discover= package% build % auto_tests, &
223
222
error= error)
224
223
225
224
if (allocated (error)) then
@@ -245,53 +244,21 @@ subroutine build_model(model, settings, package, error)
245
244
246
245
end subroutine build_model
247
246
248
- ! > Apply package defaults
249
- subroutine package_defaults (package )
250
- type (package_t), intent (inout ) :: package
251
-
252
- ! Populate library in case we find the default src directory
253
- if (.not. allocated (package% library) .and. exists(" src" )) then
254
- allocate (package% library)
255
- call default_library(package% library)
256
- end if
257
-
258
- ! Populate executable in case we find the default app
259
- if (.not. allocated (package% executable) .and. &
260
- exists(join_path(' app' ," main.f90" ))) then
261
- allocate (package% executable(1 ))
262
- call default_executable(package% executable(1 ), package% name)
263
- end if
264
-
265
- ! Populate test in case we find the default test directory
266
- if (.not. allocated (package% test) .and. &
267
- exists(join_path(" test" ," main.f90" ))) then
268
- allocate (package% test(1 ))
269
- call default_test(package% test(1 ), package% name)
270
- endif
271
-
272
- if (.not. (allocated (package% library) .or. allocated (package% executable))) then
273
- print ' (a)' , " Neither library nor executable found, there is nothing to do"
274
- error stop 1
275
- end if
276
-
277
- end subroutine
278
247
279
248
subroutine cmd_build (settings )
280
249
type (fpm_build_settings), intent (in ) :: settings
281
- type (package_t ) :: package
250
+ type (package_config_t ) :: package
282
251
type (fpm_model_t) :: model
283
252
type (error_t), allocatable :: error
284
253
285
254
integer :: i
286
255
287
- call get_package_data(package, " fpm.toml" , error)
256
+ call get_package_data(package, " fpm.toml" , error, apply_defaults = .true. )
288
257
if (allocated (error)) then
289
258
print ' (a)' , error% message
290
259
error stop 1
291
260
end if
292
261
293
- call package_defaults(package)
294
-
295
262
call build_model(model, settings, package, error)
296
263
if (allocated (error)) then
297
264
print ' (a)' , error% message
@@ -322,22 +289,19 @@ subroutine cmd_run(settings,test)
322
289
integer :: i, j, col_width, nCol
323
290
logical :: found(size (settings% name))
324
291
type (error_t), allocatable :: error
325
- type (package_t ) :: package
292
+ type (package_config_t ) :: package
326
293
type (fpm_model_t) :: model
327
294
type (string_t) :: exe_cmd
328
295
type (string_t), allocatable :: executables(:)
329
296
type (build_target_t), pointer :: exe_target
330
297
type (srcfile_t), pointer :: exe_source
331
298
332
- call get_package_data(package, " fpm.toml" , error)
299
+ call get_package_data(package, " fpm.toml" , error, apply_defaults = .true. )
333
300
if (allocated (error)) then
334
301
print ' (a)' , error% message
335
302
error stop 1
336
303
end if
337
304
338
-
339
- call package_defaults(package)
340
-
341
305
call build_model(model, settings% fpm_build_settings, package, error)
342
306
if (allocated (error)) then
343
307
print ' (a)' , error% message
0 commit comments