Skip to content

Commit 67ed215

Browse files
committed
intel: correct ID by OS
1 parent 78aca7a commit 67ed215

File tree

2 files changed

+311
-13
lines changed

2 files changed

+311
-13
lines changed

src/fpm/manifest/platform.f90

Lines changed: 134 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -11,9 +11,11 @@ module fpm_manifest_platform
1111
use fpm_error, only : error_t, fatal_error
1212
use tomlf, only : toml_table
1313
use fpm_toml, only : serializable_t, set_string, get_value
14-
use fpm_environment,only : OS_ALL, OS_NAME, match_os_type, OS_UNKNOWN, validate_os_name
14+
use fpm_environment,only : OS_ALL, OS_NAME, match_os_type, OS_UNKNOWN, validate_os_name, &
15+
OS_WINDOWS, OS_LINUX, OS_MACOS
1516
use fpm_compiler, only : compiler_enum, compiler_id_name, match_compiler_type, id_all, &
16-
id_unknown, validate_compiler_name
17+
id_unknown, validate_compiler_name, id_intel_classic_nix, id_intel_classic_mac, &
18+
id_intel_classic_windows, id_intel_llvm_nix, id_intel_llvm_windows
1719
use fpm_strings, only : lower
1820
implicit none
1921
private
@@ -48,6 +50,9 @@ module fpm_manifest_platform
4850
!> Get configuration name as it appears in the manifest
4951
procedure :: name => platform_config_name
5052

53+
!> Validation
54+
procedure :: is_valid => platform_is_valid
55+
5156
!> Properties
5257
procedure, non_overridable :: any_compiler
5358
procedure, non_overridable :: any_os
@@ -58,24 +63,95 @@ module fpm_manifest_platform
5863
! Overloaded initializer
5964
interface platform_config_t
6065
module procedure new_platform
66+
module procedure new_platform_id
6167
end interface
6268

6369
character(len=*), parameter, private :: class_name = 'platform_config_t'
6470

6571
contains
6672

67-
68-
69-
!> Initialize a new platform config
73+
!> Initialize a new platform config from compiler name
74+
!> Automatically selects correct Intel compiler version based on OS
7075
type(platform_config_t) function new_platform(compiler, os_type)
7176
character(*), intent(in) :: compiler
7277
integer, intent(in) :: os_type
7378

7479
new_platform%compiler = match_compiler_type(compiler)
7580
new_platform%os_type = os_type
7681

82+
! Correct Intel compiler ID based on OS (fallback to unix version for OS_ALL)
83+
new_platform%compiler = correct_compiler_for_os(new_platform%compiler, os_type)
84+
7785
end function new_platform
7886

87+
!> Initialize a new platform config from compiler enum ID
88+
!> Automatically selects correct Intel compiler version based on OS
89+
type(platform_config_t) function new_platform_id(compiler_id, os_type)
90+
integer(compiler_enum), intent(in) :: compiler_id
91+
integer, intent(in) :: os_type
92+
93+
new_platform_id%compiler = compiler_id
94+
new_platform_id%os_type = os_type
95+
96+
! Correct Intel compiler ID based on OS (fallback to unix version for OS_ALL)
97+
new_platform_id%compiler = correct_compiler_for_os(new_platform_id%compiler, os_type)
98+
99+
end function new_platform_id
100+
101+
!> Correct Intel compiler ID to match the target OS
102+
!> Returns the appropriate OS-specific Intel compiler variant
103+
function correct_compiler_for_os(compiler_id, os_type) result(corrected_id)
104+
integer(compiler_enum), intent(in) :: compiler_id
105+
integer, intent(in) :: os_type
106+
integer(compiler_enum) :: corrected_id
107+
108+
corrected_id = compiler_id ! Default: no change
109+
110+
! Intel classic compilers: map to OS-specific version
111+
select case (compiler_id)
112+
case (id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows)
113+
select case (os_type)
114+
case (OS_WINDOWS)
115+
corrected_id = id_intel_classic_windows
116+
case (OS_MACOS)
117+
corrected_id = id_intel_classic_mac
118+
case default
119+
corrected_id = id_intel_classic_nix ! Fallback to unix version
120+
end select
121+
122+
case (id_intel_llvm_nix, id_intel_llvm_windows)
123+
select case (os_type)
124+
case (OS_WINDOWS)
125+
corrected_id = id_intel_llvm_windows
126+
case default
127+
corrected_id = id_intel_llvm_nix ! Fallback to unix version
128+
end select
129+
end select
130+
131+
end function correct_compiler_for_os
132+
133+
!> Check if two Intel compiler IDs are equivalent (same family, different OS versions)
134+
logical function intel_compilers_equivalent(compiler1, compiler2) result(equivalent)
135+
integer(compiler_enum), intent(in) :: compiler1, compiler2
136+
137+
equivalent = .false.
138+
139+
! Intel classic compilers are equivalent across OS variants
140+
if (any(compiler1 == [id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows]) .and. &
141+
any(compiler2 == [id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows])) then
142+
equivalent = .true.
143+
return
144+
end if
145+
146+
! Intel LLVM compilers are equivalent across OS variants
147+
if (any(compiler1 == [id_intel_llvm_nix, id_intel_llvm_windows]) .and. &
148+
any(compiler2 == [id_intel_llvm_nix, id_intel_llvm_windows])) then
149+
equivalent = .true.
150+
return
151+
end if
152+
153+
end function intel_compilers_equivalent
154+
79155
!> Compare two platform_config_t (semantic equality)
80156
logical function platform_is_same(this, that)
81157
class(platform_config_t), intent(in) :: this
@@ -159,28 +235,75 @@ end subroutine info
159235
!> - compiler matches if SELF%compiler == id_all OR == target%compiler
160236
!> - os matches if SELF%os_type == OS_ALL OR == target%os_type
161237
!> - id_unknown / OS_UNKNOWN in SELF are treated as "no match" (conservative)
238+
!> - Intel compilers must match OS (ifort unix/windows versions use different flags)
162239
logical function platform_is_suitable(self, target) result(ok)
163240
class(platform_config_t), intent(in) :: self
164241
type(platform_config_t), intent(in) :: target
165242

166243
logical :: compiler_ok, os_ok
167244

168-
! Unknowns are conservative (don�t match)
169-
if (any([self%compiler,target%compiler] == id_unknown)) then
170-
ok = .false.
171-
return
172-
end if
173-
if (any([self%os_type,target%os_type] == OS_UNKNOWN)) then
245+
! Check that both platforms are valid
246+
if (.not. self%is_valid() .or. .not. target%is_valid()) then
174247
ok = .false.
175248
return
176249
end if
177250

178251
compiler_ok = any(self%compiler == [id_all,target%compiler])
179252
os_ok = any(self%os_type == [OS_ALL,target%os_type])
180253

254+
! Basic matching
181255
ok = compiler_ok .and. os_ok
256+
257+
if (.not. ok) return
258+
259+
! Additional validation: Intel compilers must have compatible OS
260+
! ifort on Unix/Mac should not match ifort on Windows and vice versa
261+
if (self%compiler /= id_all .and. self%os_type /= OS_ALL) then
262+
ok = compiler_os_compatible(self%compiler, self%os_type) .and. &
263+
compiler_os_compatible(target%compiler, target%os_type)
264+
end if
265+
182266
end function platform_is_suitable
183267

268+
!> Check if a platform configuration is valid (no unknowns, compatible compiler+OS)
269+
logical function platform_is_valid(self) result(valid)
270+
class(platform_config_t), intent(in) :: self
271+
272+
! Check compiler+OS compatibility
273+
valid = compiler_os_compatible(self%compiler, self%os_type)
274+
275+
end function platform_is_valid
276+
277+
!> Check if a compiler ID is compatible with an OS type
278+
elemental logical function compiler_os_compatible(compiler_id, os_type) result(compatible)
279+
integer(compiler_enum), intent(in) :: compiler_id
280+
integer, intent(in) :: os_type
281+
282+
! Check for unknowns
283+
if (compiler_id == id_unknown .or. os_type == OS_UNKNOWN) then
284+
compatible = .false.
285+
return
286+
end if
287+
288+
! Intel classic compilers: OS-specific variants
289+
select case (compiler_id)
290+
case (id_intel_classic_windows)
291+
compatible = any(os_type == [OS_ALL,OS_WINDOWS])
292+
case (id_intel_classic_nix)
293+
compatible = any(os_type == [OS_ALL,OS_LINUX])
294+
case (id_intel_classic_mac)
295+
compatible = any(os_type == [OS_ALL,OS_MACOS])
296+
case (id_intel_llvm_windows)
297+
compatible = any(os_type == [OS_ALL,OS_WINDOWS])
298+
case (id_intel_llvm_nix)
299+
compatible = any(os_type == [OS_ALL,OS_LINUX,OS_MACOS])
300+
case default
301+
! Other compilers are compatible with any OS
302+
compatible = os_type/=OS_UNKNOWN .and. compiler_id/=id_unknown
303+
end select
304+
305+
end function compiler_os_compatible
306+
184307
!> Check if a key (os or compiler) can be used for platform setting
185308
elemental logical function is_platform_key(key)
186309
character(*), intent(in) :: key

0 commit comments

Comments
 (0)