Skip to content

Commit ee812cf

Browse files
committed
extract target platform from package and dependencies
1 parent c19ff1a commit ee812cf

File tree

3 files changed

+119
-13
lines changed

3 files changed

+119
-13
lines changed

src/fpm.f90

Lines changed: 27 additions & 11 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,21 +38,25 @@ 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
5153
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))
@@ -68,19 +73,26 @@ subroutine build_model(model, settings, package, error)
6873
"Defaults for this compiler might be incorrect"
6974
end if
7075

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))
7482
model%include_tests = settings%build_tests
75-
if (allocated(package%build)) then
76-
model%enforce_module_names = package%build%module_naming
77-
model%module_prefix = package%build%module_prefix
78-
endif
79-
83+
84+
! Extract the current package configuration request
85+
package = package_config%export_config(target_platform)
86+
8087
! Resolve meta-dependencies into the package and the model
8188
call resolve_metapackages(model,package,settings,error)
8289
if (allocated(error)) return
8390

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+
8496
! Create dependencies
8597
call new_dependency_tree(model%deps, cache=join_path(settings%build_dir, "cache.toml"), &
8698
& path_to_config=settings%path_to_config, build_dir=settings%build_dir)
@@ -111,8 +123,12 @@ subroutine build_model(model, settings, package, error)
111123
manifest => package
112124
else
113125

114-
call get_package_data(dependency, file_name, error, apply_defaults=.true.)
115-
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)
116132

117133
manifest => dependency
118134
end if

src/fpm/manifest/package.f90

Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,8 @@ module fpm_manifest_package
4646
use fpm_manifest_preprocess, only : preprocess_config_t, new_preprocessors
4747
use fpm_manifest_feature, only: feature_config_t, init_feature_components
4848
use fpm_manifest_feature_collection, only: feature_collection_t, get_default_features, new_collections
49+
use fpm_manifest_platform, only: platform_config_t
50+
use fpm_strings, only: string_t
4951
use fpm_filesystem, only : exists, getline, join_path
5052
use fpm_error, only : error_t, fatal_error, syntax_error, bad_name_error
5153
use tomlf, only : toml_table, toml_array, toml_key, toml_stat
@@ -94,6 +96,9 @@ module fpm_manifest_package
9496
procedure :: dump_to_toml
9597
procedure :: load_from_toml
9698

99+
!> Export package configuration with features applied
100+
procedure :: export_config
101+
97102
end type package_config_t
98103

99104
character(len=*), parameter, private :: class_name = 'package_config_t'
@@ -535,5 +540,47 @@ subroutine load_from_toml(self, table, error)
535540

536541
end subroutine load_from_toml
537542

543+
!> Export package configuration for a given (OS+compiler) platform
544+
type(package_config_t) function export_config(self, platform, features) result(cfg)
545+
546+
!> Instance of the package configuration
547+
class(package_config_t), intent(in) :: self
548+
549+
!> Target platform
550+
type(platform_config_t), intent(in) :: platform
551+
552+
!> Optional list of features to apply (currently idle)
553+
type(string_t), optional, intent(in) :: features(:)
554+
555+
! Copy the entire package configuration
556+
cfg = self
557+
558+
! Ensure allocatable fields are always allocated with default values if not already set
559+
if (.not. allocated(cfg%build)) then
560+
allocate(cfg%build)
561+
cfg%build%auto_executables = .true.
562+
cfg%build%auto_examples = .true.
563+
cfg%build%auto_tests = .true.
564+
cfg%build%module_naming = .false.
565+
end if
566+
567+
if (.not. allocated(cfg%install)) then
568+
allocate(cfg%install)
569+
cfg%install%library = .false.
570+
cfg%install%test = .false.
571+
end if
572+
573+
if (.not. allocated(cfg%fortran)) then
574+
allocate(cfg%fortran)
575+
cfg%fortran%implicit_typing = .false.
576+
cfg%fortran%implicit_external = .false.
577+
cfg%fortran%source_form = 'free'
578+
end if
579+
580+
! TODO: Feature processing will be implemented here
581+
! For now, features parameter is ignored as requested
582+
583+
end function export_config
584+
538585

539586
end module fpm_manifest_package

src/fpm_model.f90

Lines changed: 45 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,9 +44,12 @@ module fpm_model
4444
use fpm_toml, only: serializable_t, set_value, set_list, get_value, &
4545
& get_list, add_table, toml_key, add_array, set_string
4646
use fpm_error, only: error_t, fatal_error
47-
use fpm_environment, only: OS_WINDOWS,OS_MACOS
47+
use fpm_environment, only: OS_WINDOWS,OS_MACOS, get_os_type, OS_UNKNOWN, OS_LINUX, OS_CYGWIN, &
48+
OS_SOLARIS, OS_FREEBSD, OS_OPENBSD, OS_ALL, validate_os_name, OS_NAME, &
49+
match_os_type
4850
use fpm_manifest_preprocess, only: preprocess_config_t
4951
use fpm_manifest_fortran, only: fortran_config_t
52+
use fpm_manifest_platform, only: platform_config_t
5053
implicit none
5154

5255
private
@@ -221,10 +224,16 @@ module fpm_model
221224
!> Prefix for all module names
222225
type(string_t) :: module_prefix
223226

227+
!> Target operating system
228+
integer :: target_os = OS_UNKNOWN
229+
224230
contains
225231

226232
!> Get target link flags
227233
procedure :: get_package_libraries_link
234+
235+
!> Get target platform configuration
236+
procedure :: target_platform
228237

229238
!> Serialization interface
230239
procedure :: serializable_is_same => model_is_same
@@ -864,6 +873,7 @@ logical function model_is_same(this,that)
864873
if (.not.(this%include_tests.eqv.other%include_tests)) return
865874
if (.not.(this%enforce_module_names.eqv.other%enforce_module_names)) return
866875
if (.not.(this%module_prefix==other%module_prefix)) return
876+
if (.not.(this%target_os==other%target_os)) return
867877

868878
class default
869879
! Not the same type
@@ -929,6 +939,10 @@ subroutine model_dump_to_toml(self, table, error)
929939
if (allocated(error)) return
930940
call set_string(table, "module-prefix", self%module_prefix, error, 'fpm_model_t')
931941
if (allocated(error)) return
942+
943+
! Serialize target OS as string
944+
call set_string(table, "target-os", OS_NAME(self%target_os), error, 'fpm_model_t')
945+
if (allocated(error)) return
932946

933947
call add_table(table, "deps", ptr, error, 'fpm_model_t')
934948
if (allocated(error)) return
@@ -985,7 +999,9 @@ subroutine model_load_from_toml(self, table, error)
985999
type(toml_key), allocatable :: keys(:),pkg_keys(:)
9861000
integer :: ierr, ii, jj
9871001
type(toml_table), pointer :: ptr,ptr_pkg
988-
1002+
character(:), allocatable :: os_string
1003+
logical :: is_valid
1004+
9891005
call table%get_keys(keys)
9901006

9911007
call get_value(table, "package-name", self%package_name)
@@ -1072,8 +1088,35 @@ subroutine model_load_from_toml(self, table, error)
10721088
if (allocated(error)) return
10731089
call get_value(table, "module-prefix", self%module_prefix%s)
10741090

1091+
! Load target OS from string and validate
1092+
call get_value(table, "target-os", os_string)
1093+
if (allocated(os_string)) then
1094+
! Validate and convert OS string to integer
1095+
call validate_os_name(os_string, is_valid)
1096+
if (.not. is_valid) then
1097+
call fatal_error(error, "Invalid target OS: " // os_string)
1098+
return
1099+
end if
1100+
1101+
self%target_os = match_os_type(os_string)
1102+
1103+
else
1104+
! Default to current OS if not specified
1105+
self%target_os = get_os_type()
1106+
end if
1107+
10751108
end subroutine model_load_from_toml
10761109

1110+
!> Get target platform configuration for the current model
1111+
function target_platform(self) result(target)
1112+
class(fpm_model_t), intent(in) :: self
1113+
type(platform_config_t) :: target
1114+
1115+
! Initialize platform with compiler and target OS
1116+
target = platform_config_t(self%compiler%id, self%target_os)
1117+
1118+
end function target_platform
1119+
10771120
function get_package_libraries_link(model, package_name, prefix, exclude_self, dep_IDs, error) result(r)
10781121
class(fpm_model_t), intent(in) :: model
10791122
character(*), intent(in) :: package_name

0 commit comments

Comments
 (0)