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