Skip to content

Commit e01591b

Browse files
authored
feat: add Features and Profiles support to fpm manifest (#1177)
2 parents 77bf0bb + e9b8019 commit e01591b

19 files changed

+4604
-1247
lines changed

src/fpm.f90

Lines changed: 65 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ module fpm
1919
use fpm_targets, only: targets_from_sources, build_target_t, build_target_ptr, &
2020
FPM_TARGET_EXECUTABLE, get_library_dirs, filter_executable_targets
2121
use fpm_manifest, only : get_package_data, package_config_t
22+
use fpm_manifest_platform, only: platform_config_t
2223
use fpm_meta, only : resolve_metapackages
2324
use fpm_error, only : error_t, fatal_error, fpm_stop
2425
use fpm_toml, only: name_is_json
@@ -37,26 +38,30 @@ module fpm
3738
contains
3839

3940
!> 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)
4142
type(fpm_model_t), intent(out) :: model
4243
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
4445
type(error_t), allocatable, intent(out) :: error
4546

4647
integer :: i, j
47-
type(package_config_t), target :: dependency
48+
type(package_config_t), target :: package, dependency_config, dependency
4849
type(package_config_t), pointer :: manifest
50+
type(platform_config_t) :: target_platform
4951
character(len=:), allocatable :: file_name, lib_dir
5052
logical :: has_cpp
51-
logical :: duplicates_found
53+
logical :: duplicates_found, auto_exe, auto_example, auto_test
5254
type(string_t) :: include_dir
5355

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()
5560

5661
allocate(model%include_dirs(0))
5762
allocate(model%link_libraries(0))
5863
allocate(model%external_modules(0))
59-
64+
6065
call new_compiler(model%compiler, settings%compiler, settings%c_compiler, &
6166
& settings%cxx_compiler, echo=settings%verbose, verbose=settings%verbose)
6267
call new_archiver(model%archiver, settings%archiver, &
@@ -67,18 +72,27 @@ subroutine build_model(model, settings, package, error)
6772
"<WARN>", "Unknown compiler", model%compiler%fc, "requested!", &
6873
"Defaults for this compiler might be incorrect"
6974
end if
70-
75+
76+
! Extract the target platform for this build
77+
target_platform = model%target_platform()
78+
7179
call new_compiler_flags(model,settings)
7280
model%build_dir = settings%build_dir
7381
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+
7887
! Resolve meta-dependencies into the package and the model
7988
call resolve_metapackages(model,package,settings,error)
8089
if (allocated(error)) return
8190

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+
8296
! Create dependencies
8397
call new_dependency_tree(model%deps, cache=join_path(settings%build_dir, "cache.toml"), &
8498
& path_to_config=settings%path_to_config, build_dir=settings%build_dir)
@@ -109,19 +123,20 @@ subroutine build_model(model, settings, package, error)
109123
manifest => package
110124
else
111125

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)
114132

115133
manifest => dependency
116134
end if
117135

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
125140

126141
!> Add this dependency's manifest macros
127142
if (allocated(manifest%preprocess)) then
@@ -163,18 +178,22 @@ subroutine build_model(model, settings, package, error)
163178
end if
164179

165180
end if
181+
182+
if (allocated(manifest%build)) then
166183

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
170187

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
174191

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
178197

179198
end associate
180199
end do
@@ -184,7 +203,18 @@ subroutine build_model(model, settings, package, error)
184203
if (has_cpp) call set_cpp_preprocessor_flags(model%compiler%id, model%fortran_compile_flags)
185204

186205
! 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
188218
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
189219
with_executables=.true., with_f_ext=model%packages(1)%preprocess%suffixes,&
190220
error=error,preprocess=model%packages(1)%preprocess)
@@ -194,7 +224,7 @@ subroutine build_model(model, settings, package, error)
194224
end if
195225

196226
end if
197-
if (is_dir('example') .and. package%build%auto_examples) then
227+
if (is_dir('example') .and. auto_example) then
198228
call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, &
199229
with_executables=.true., &
200230
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
@@ -205,7 +235,7 @@ subroutine build_model(model, settings, package, error)
205235
end if
206236

207237
end if
208-
if (is_dir('test') .and. package%build%auto_tests) then
238+
if (is_dir('test') .and. auto_test) then
209239
call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, &
210240
with_executables=.true., &
211241
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
@@ -218,7 +248,7 @@ subroutine build_model(model, settings, package, error)
218248
end if
219249
if (allocated(package%executable)) then
220250
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, &
222252
with_f_ext=model%packages(1)%preprocess%suffixes, &
223253
error=error,preprocess=model%packages(1)%preprocess)
224254

@@ -229,7 +259,7 @@ subroutine build_model(model, settings, package, error)
229259
end if
230260
if (allocated(package%example)) then
231261
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, &
233263
with_f_ext=model%packages(1)%preprocess%suffixes, &
234264
error=error,preprocess=model%packages(1)%preprocess)
235265

@@ -240,7 +270,7 @@ subroutine build_model(model, settings, package, error)
240270
end if
241271
if (allocated(package%test)) then
242272
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, &
244274
with_f_ext=model%packages(1)%preprocess%suffixes, &
245275
error=error,preprocess=model%packages(1)%preprocess)
246276

src/fpm/cmd/install.f90

Lines changed: 23 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,9 @@ subroutine cmd_install(settings)
2929
type(build_target_ptr), allocatable :: targets(:), libraries(:)
3030
type(installer_t) :: installer
3131
type(string_t), allocatable :: list(:)
32-
logical :: installable
32+
logical :: installable, has_install, with_library, with_tests
33+
logical :: has_library, has_executables
34+
character(len=:), allocatable :: module_dir
3335
integer :: ntargets,i
3436

3537
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
@@ -38,8 +40,22 @@ subroutine cmd_install(settings)
3840
call build_model(model, settings, package, error)
3941
call handle_error(error)
4042

43+
! Set up logical variables to avoid repetitive conditions
44+
has_install = allocated(package%install)
45+
has_library = allocated(package%library)
46+
has_executables = allocated(package%executable)
47+
if (has_install) then
48+
with_library = has_install .and. package%install%library
49+
with_tests = has_install .and. package%install%test
50+
! Set module directory (or leave unallocated because `optional`)
51+
if (allocated(package%install%module_dir)) module_dir = package%install%module_dir
52+
else
53+
with_library = .false.
54+
with_tests = .false.
55+
endif
56+
4157
! ifx bug: does not resolve allocatable -> optional
42-
if (allocated(package%library)) then
58+
if (has_library) then
4359
call targets_from_sources(targets, model, settings%prune, package%library, error)
4460
else
4561
call targets_from_sources(targets, model, settings%prune, error=error)
@@ -49,8 +65,7 @@ subroutine cmd_install(settings)
4965
call install_info(output_unit, settings%list, targets, ntargets)
5066
if (settings%list) return
5167

52-
installable = (allocated(package%library) .and. package%install%library) &
53-
.or. allocated(package%executable) .or. ntargets>0
68+
installable = (has_library .and. with_library) .or. has_executables .or. ntargets>0
5469

5570
if (.not.installable) then
5671
call fatal_error(error, "Project does not contain any installable targets")
@@ -63,10 +78,10 @@ subroutine cmd_install(settings)
6378

6479
call new_installer(installer, prefix=settings%prefix, &
6580
bindir=settings%bindir, libdir=settings%libdir, testdir=settings%testdir, &
66-
includedir=settings%includedir, moduledir=package%install%module_dir, &
81+
includedir=settings%includedir, moduledir=module_dir, &
6782
verbosity=merge(2, 1, settings%verbose))
6883

69-
if (allocated(package%library) .and. package%install%library) then
84+
if (has_library .and. with_library) then
7085
call filter_library_targets(targets, libraries)
7186

7287
if (size(libraries) > 0) then
@@ -80,12 +95,12 @@ subroutine cmd_install(settings)
8095
end if
8196
end if
8297

83-
if (allocated(package%executable) .or. ntargets>0) then
98+
if (has_executables .or. ntargets>0) then
8499
call install_executables(installer, targets, error)
85100
call handle_error(error)
86101
end if
87102

88-
if (allocated(package%test) .and. (package%install%test .or. model%include_tests)) then
103+
if (allocated(package%test) .and. (with_tests .or. model%include_tests)) then
89104

90105
call install_tests(installer, targets, error)
91106
call handle_error(error)

0 commit comments

Comments
 (0)