@@ -19,6 +19,7 @@ module fpm
19
19
use fpm_targets, only: targets_from_sources, build_target_t, build_target_ptr, &
20
20
FPM_TARGET_EXECUTABLE, get_library_dirs, filter_executable_targets
21
21
use fpm_manifest, only : get_package_data, package_config_t
22
+ use fpm_manifest_platform, only: platform_config_t
22
23
use fpm_meta, only : resolve_metapackages
23
24
use fpm_error, only : error_t, fatal_error, fpm_stop
24
25
use fpm_toml, only: name_is_json
@@ -37,26 +38,30 @@ module fpm
37
38
contains
38
39
39
40
! > Constructs a valid fpm model from command line settings and the toml manifest.
40
- subroutine build_model (model , settings , package , error )
41
+ subroutine build_model (model , settings , package_config , error )
41
42
type (fpm_model_t), intent (out ) :: model
42
43
class(fpm_build_settings), intent (inout ) :: settings
43
- type (package_config_t), intent (inout ), target :: package
44
+ type (package_config_t), intent (inout ), target :: package_config
44
45
type (error_t), allocatable , intent (out ) :: error
45
46
46
47
integer :: i, j
47
- type (package_config_t), target :: dependency
48
+ type (package_config_t), target :: package, dependency_config, dependency
48
49
type (package_config_t), pointer :: manifest
50
+ type (platform_config_t) :: target_platform
49
51
character (len= :), allocatable :: file_name, lib_dir
50
52
logical :: has_cpp
51
- logical :: duplicates_found
53
+ logical :: duplicates_found, auto_exe, auto_example, auto_test
52
54
type (string_t) :: include_dir
53
55
54
- model% package_name = package% name
56
+ model% package_name = package_config% name
57
+
58
+ ! Set target OS to current OS (may be extended for cross-compilation in the future)
59
+ model% target_os = get_os_type()
55
60
56
61
allocate (model% include_dirs(0 ))
57
62
allocate (model% link_libraries(0 ))
58
63
allocate (model% external_modules(0 ))
59
-
64
+
60
65
call new_compiler(model% compiler, settings% compiler, settings% c_compiler, &
61
66
& settings% cxx_compiler, echo= settings% verbose, verbose= settings% verbose)
62
67
call new_archiver(model% archiver, settings% archiver, &
@@ -67,18 +72,27 @@ subroutine build_model(model, settings, package, error)
67
72
" <WARN>" , " Unknown compiler" , model% compiler% fc, " requested!" , &
68
73
" Defaults for this compiler might be incorrect"
69
74
end if
70
-
75
+
76
+ ! Extract the target platform for this build
77
+ target_platform = model% target_platform()
78
+
71
79
call new_compiler_flags(model,settings)
72
80
model% build_dir = settings% build_dir
73
81
model% build_prefix = join_path(settings% build_dir, basename(model% compiler% fc))
74
- model% include_tests = settings% build_tests
75
- model% enforce_module_names = package% build% module_naming
76
- model% module_prefix = package% build% module_prefix
77
-
82
+ model% include_tests = settings% build_tests
83
+
84
+ ! Extract the current package configuration request
85
+ package = package_config% export_config(target_platform)
86
+
78
87
! Resolve meta-dependencies into the package and the model
79
88
call resolve_metapackages(model,package,settings,error)
80
89
if (allocated (error)) return
81
90
91
+ if (allocated (package% build)) then
92
+ model% enforce_module_names = package% build% module_naming
93
+ model% module_prefix = package% build% module_prefix
94
+ endif
95
+
82
96
! Create dependencies
83
97
call new_dependency_tree(model% deps, cache= join_path(settings% build_dir, " cache.toml" ), &
84
98
& path_to_config= settings% path_to_config, build_dir= settings% build_dir)
@@ -109,19 +123,20 @@ subroutine build_model(model, settings, package, error)
109
123
manifest = > package
110
124
else
111
125
112
- call get_package_data(dependency, file_name, error, apply_defaults= .true. )
113
- if (allocated (error)) exit
126
+ ! Extract this dependency config
127
+ call get_package_data(dependency_config, file_name, error, apply_defaults= .true. )
128
+ if (allocated (error)) exit
129
+
130
+ ! Adapt it to the current profile/platform
131
+ dependency = dependency_config% export_config(target_platform)
114
132
115
133
manifest = > dependency
116
134
end if
117
135
118
- model% packages(i)% name = manifest% name
119
- associate(features = > model% packages(i)% features)
120
- features% implicit_typing = manifest% fortran% implicit_typing
121
- features% implicit_external = manifest% fortran% implicit_external
122
- features% source_form = manifest% fortran% source_form
123
- end associate
124
- model% packages(i)% version = manifest% version
136
+
137
+ model% packages(i)% name = manifest% name
138
+ model% packages(i)% features = manifest% fortran
139
+ model% packages(i)% version = manifest% version
125
140
126
141
! > Add this dependency's manifest macros
127
142
if (allocated (manifest% preprocess)) then
@@ -163,18 +178,22 @@ subroutine build_model(model, settings, package, error)
163
178
end if
164
179
165
180
end if
181
+
182
+ if (allocated (manifest% build)) then
166
183
167
- if (allocated (manifest% build% link)) then
168
- model% link_libraries = [model% link_libraries, manifest% build% link]
169
- end if
184
+ if (allocated (manifest% build% link)) then
185
+ model% link_libraries = [model% link_libraries, manifest% build% link]
186
+ end if
170
187
171
- if (allocated (manifest% build% external_modules)) then
172
- model% external_modules = [model% external_modules, manifest% build% external_modules]
173
- end if
188
+ if (allocated (manifest% build% external_modules)) then
189
+ model% external_modules = [model% external_modules, manifest% build% external_modules]
190
+ end if
174
191
175
- ! Copy naming conventions from this dependency's manifest
176
- model% packages(i)% enforce_module_names = manifest% build% module_naming
177
- model% packages(i)% module_prefix = manifest% build% module_prefix
192
+ ! Copy naming conventions from this dependency's manifest
193
+ model% packages(i)% enforce_module_names = manifest% build% module_naming
194
+ model% packages(i)% module_prefix = manifest% build% module_prefix
195
+
196
+ endif
178
197
179
198
end associate
180
199
end do
@@ -184,7 +203,18 @@ subroutine build_model(model, settings, package, error)
184
203
if (has_cpp) call set_cpp_preprocessor_flags(model% compiler% id, model% fortran_compile_flags)
185
204
186
205
! Add sources from executable directories
187
- if (is_dir(' app' ) .and. package% build% auto_executables) then
206
+
207
+ if (allocated (package% build)) then
208
+ auto_exe = package% build% auto_executables
209
+ auto_example = package% build% auto_examples
210
+ auto_test = package% build% auto_tests
211
+ else
212
+ auto_exe = .true.
213
+ auto_example = .true.
214
+ auto_test = .true.
215
+ endif
216
+
217
+ if (is_dir(' app' ) .and. auto_exe) then
188
218
call add_sources_from_dir(model% packages(1 )% sources,' app' , FPM_SCOPE_APP, &
189
219
with_executables= .true. , with_f_ext= model% packages(1 )% preprocess% suffixes,&
190
220
error= error,preprocess= model% packages(1 )% preprocess)
@@ -194,7 +224,7 @@ subroutine build_model(model, settings, package, error)
194
224
end if
195
225
196
226
end if
197
- if (is_dir(' example' ) .and. package % build % auto_examples ) then
227
+ if (is_dir(' example' ) .and. auto_example ) then
198
228
call add_sources_from_dir(model% packages(1 )% sources,' example' , FPM_SCOPE_EXAMPLE, &
199
229
with_executables= .true. , &
200
230
with_f_ext= model% packages(1 )% preprocess% suffixes,error= error,&
@@ -205,7 +235,7 @@ subroutine build_model(model, settings, package, error)
205
235
end if
206
236
207
237
end if
208
- if (is_dir(' test' ) .and. package % build % auto_tests ) then
238
+ if (is_dir(' test' ) .and. auto_test ) then
209
239
call add_sources_from_dir(model% packages(1 )% sources,' test' , FPM_SCOPE_TEST, &
210
240
with_executables= .true. , &
211
241
with_f_ext= model% packages(1 )% preprocess% suffixes,error= error,&
@@ -218,7 +248,7 @@ subroutine build_model(model, settings, package, error)
218
248
end if
219
249
if (allocated (package% executable)) then
220
250
call add_executable_sources(model% packages(1 )% sources, package% executable, FPM_SCOPE_APP, &
221
- auto_discover= package % build % auto_executables , &
251
+ auto_discover= auto_exe , &
222
252
with_f_ext= model% packages(1 )% preprocess% suffixes, &
223
253
error= error,preprocess= model% packages(1 )% preprocess)
224
254
@@ -229,7 +259,7 @@ subroutine build_model(model, settings, package, error)
229
259
end if
230
260
if (allocated (package% example)) then
231
261
call add_executable_sources(model% packages(1 )% sources, package% example, FPM_SCOPE_EXAMPLE, &
232
- auto_discover= package % build % auto_examples , &
262
+ auto_discover= auto_example , &
233
263
with_f_ext= model% packages(1 )% preprocess% suffixes, &
234
264
error= error,preprocess= model% packages(1 )% preprocess)
235
265
@@ -240,7 +270,7 @@ subroutine build_model(model, settings, package, error)
240
270
end if
241
271
if (allocated (package% test)) then
242
272
call add_executable_sources(model% packages(1 )% sources, package% test, FPM_SCOPE_TEST, &
243
- auto_discover= package % build % auto_tests , &
273
+ auto_discover= auto_test , &
244
274
with_f_ext= model% packages(1 )% preprocess% suffixes, &
245
275
error= error,preprocess= model% packages(1 )% preprocess)
246
276
0 commit comments