@@ -44,9 +44,12 @@ module fpm_model
44
44
use fpm_toml, only: serializable_t, set_value, set_list, get_value, &
45
45
& get_list, add_table, toml_key, add_array, set_string
46
46
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
48
50
use fpm_manifest_preprocess, only: preprocess_config_t
49
51
use fpm_manifest_fortran, only: fortran_config_t
52
+ use fpm_manifest_platform, only: platform_config_t
50
53
implicit none
51
54
52
55
private
@@ -221,10 +224,16 @@ module fpm_model
221
224
! > Prefix for all module names
222
225
type (string_t) :: module_prefix
223
226
227
+ ! > Target operating system
228
+ integer :: target_os = OS_UNKNOWN
229
+
224
230
contains
225
231
226
232
! > Get target link flags
227
233
procedure :: get_package_libraries_link
234
+
235
+ ! > Get target platform configuration
236
+ procedure :: target_platform
228
237
229
238
! > Serialization interface
230
239
procedure :: serializable_is_same = > model_is_same
@@ -864,6 +873,7 @@ logical function model_is_same(this,that)
864
873
if (.not. (this% include_tests.eqv. other% include_tests)) return
865
874
if (.not. (this% enforce_module_names.eqv. other% enforce_module_names)) return
866
875
if (.not. (this% module_prefix== other% module_prefix)) return
876
+ if (.not. (this% target_os== other% target_os)) return
867
877
868
878
class default
869
879
! Not the same type
@@ -929,6 +939,10 @@ subroutine model_dump_to_toml(self, table, error)
929
939
if (allocated (error)) return
930
940
call set_string(table, " module-prefix" , self% module_prefix, error, ' fpm_model_t' )
931
941
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
932
946
933
947
call add_table(table, " deps" , ptr, error, ' fpm_model_t' )
934
948
if (allocated (error)) return
@@ -985,7 +999,9 @@ subroutine model_load_from_toml(self, table, error)
985
999
type (toml_key), allocatable :: keys(:),pkg_keys(:)
986
1000
integer :: ierr, ii, jj
987
1001
type (toml_table), pointer :: ptr,ptr_pkg
988
-
1002
+ character (:), allocatable :: os_string
1003
+ logical :: is_valid
1004
+
989
1005
call table% get_keys(keys)
990
1006
991
1007
call get_value(table, " package-name" , self% package_name)
@@ -1072,8 +1088,35 @@ subroutine model_load_from_toml(self, table, error)
1072
1088
if (allocated (error)) return
1073
1089
call get_value(table, " module-prefix" , self% module_prefix% s)
1074
1090
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
+
1075
1108
end subroutine model_load_from_toml
1076
1109
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
+
1077
1120
function get_package_libraries_link (model , package_name , prefix , exclude_self , dep_IDs , error ) result(r)
1078
1121
class(fpm_model_t), intent (in ) :: model
1079
1122
character (* ), intent (in ) :: package_name
0 commit comments