Skip to content

Commit 6f14446

Browse files
committed
fix different intel versions for different OSes
1 parent 67ed215 commit 6f14446

File tree

1 file changed

+28
-18
lines changed

1 file changed

+28
-18
lines changed

src/fpm/manifest/platform.f90

Lines changed: 28 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,12 @@ module fpm_manifest_platform
2222

2323
public :: platform_config_t
2424
public :: is_platform_key
25-
25+
26+
!> Shortcuts for the Intel OS variants
27+
integer(compiler_enum), parameter :: &
28+
id_intel_classic(*) = [id_intel_classic_mac,id_intel_classic_nix,id_intel_classic_windows], &
29+
id_intel_llvm (*) = [id_intel_llvm_nix,id_intel_llvm_windows]
30+
2631
!> Serializable platform configuration (compiler + OS only)
2732
type, extends(serializable_t) :: platform_config_t
2833

@@ -109,7 +114,7 @@ function correct_compiler_for_os(compiler_id, os_type) result(corrected_id)
109114

110115
! Intel classic compilers: map to OS-specific version
111116
select case (compiler_id)
112-
case (id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows)
117+
case (id_intel_classic_mac,id_intel_classic_nix,id_intel_classic_windows)
113118
select case (os_type)
114119
case (OS_WINDOWS)
115120
corrected_id = id_intel_classic_windows
@@ -119,7 +124,7 @@ function correct_compiler_for_os(compiler_id, os_type) result(corrected_id)
119124
corrected_id = id_intel_classic_nix ! Fallback to unix version
120125
end select
121126

122-
case (id_intel_llvm_nix, id_intel_llvm_windows)
127+
case (id_intel_llvm_nix,id_intel_llvm_windows)
123128
select case (os_type)
124129
case (OS_WINDOWS)
125130
corrected_id = id_intel_llvm_windows
@@ -130,27 +135,32 @@ function correct_compiler_for_os(compiler_id, os_type) result(corrected_id)
130135

131136
end function correct_compiler_for_os
132137

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
138+
!> Check if a compiler ID is suitable for a target platform
139+
!> Handles special cases like Intel compiler variants
140+
logical function compiler_is_suitable(compiler_id, target) result(suitable)
141+
integer(compiler_enum), intent(in) :: compiler_id
142+
type(platform_config_t), intent(in) :: target
136143

137-
equivalent = .false.
144+
! Default case: exact match or compiler_id is id_all
145+
suitable = (compiler_id == id_all .or. compiler_id == target%compiler)
138146

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.
147+
if (suitable) return
148+
149+
! Intel classic compilers: all variants are equivalent
150+
if (any(compiler_id == id_intel_classic) .and. any(target%compiler == id_intel_classic)) then
151+
suitable = .true.
143152
return
144153
end if
145154

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.
155+
! Intel LLVM compilers: all variants are equivalent
156+
if (any(compiler_id == id_intel_llvm) .and. any(target%compiler == id_intel_llvm)) then
157+
suitable = .true.
150158
return
151159
end if
152160

153-
end function intel_compilers_equivalent
161+
! Future extensions can be added here for other compiler families
162+
163+
end function compiler_is_suitable
154164

155165
!> Compare two platform_config_t (semantic equality)
156166
logical function platform_is_same(this, that)
@@ -247,8 +257,8 @@ logical function platform_is_suitable(self, target) result(ok)
247257
ok = .false.
248258
return
249259
end if
250-
251-
compiler_ok = any(self%compiler == [id_all,target%compiler])
260+
261+
compiler_ok = compiler_is_suitable(self%compiler, target)
252262
os_ok = any(self%os_type == [OS_ALL,target%os_type])
253263

254264
! Basic matching

0 commit comments

Comments
 (0)