Skip to content

Commit d810d87

Browse files
committed
Fix compile flag behavior of ifx
1 parent fd2b38a commit d810d87

File tree

2 files changed

+22
-11
lines changed

2 files changed

+22
-11
lines changed

src/fpm_compiler.F90

Lines changed: 15 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -206,7 +206,8 @@ module fpm_compiler
206206
flag_intel_openmp = " -qopenmp", &
207207
flag_intel_free_form = " -free", &
208208
flag_intel_fixed_form = " -fixed", &
209-
flag_intel_standard_compliance = " -standard-semantics"
209+
flag_intel_standard_compliance = " -standard-semantics", &
210+
flag_intel_unknown_cmd_err = "-diag-error 10006"
210211

211212
character(*), parameter :: &
212213
flag_intel_llvm_check = " -check all,nouninit"
@@ -226,7 +227,8 @@ module fpm_compiler
226227
flag_intel_openmp_win = " /Qopenmp", &
227228
flag_intel_free_form_win = " /free", &
228229
flag_intel_fixed_form_win = " /fixed", &
229-
flag_intel_standard_compliance_win = " /standard-semantics"
230+
flag_intel_standard_compliance_win = " /standard-semantics", &
231+
flag_intel_unknown_cmd_err_win = "/Qdiag-error:10006"
230232

231233
character(*), parameter :: &
232234
flag_nag_coarray = " -coarray=single", &
@@ -441,15 +443,15 @@ subroutine get_debug_compile_flags(id, flags)
441443
flag_intel_backtrace_win
442444
case(id_intel_llvm_nix)
443445
flags = &
444-
flag_intel_warn//&
446+
flag_intel_unknown_cmd_err//&
445447
flag_intel_llvm_check//&
446448
flag_intel_limit//&
447449
flag_intel_debug//&
448450
flag_intel_byterecl//&
449451
flag_intel_backtrace
450452
case(id_intel_llvm_windows)
451453
flags = &
452-
flag_intel_warn_win//&
454+
flag_intel_unknown_cmd_err_win//&
453455
flag_intel_check_win//&
454456
flag_intel_limit_win//&
455457
flag_intel_debug_win//&
@@ -1485,6 +1487,15 @@ logical function check_fortran_source_runs(self, input, compile_flags, link_flag
14851487
if (present(compile_flags)) flags = flags//" "//compile_flags
14861488
if (present(link_flags)) ldflags = ldflags//" "//link_flags
14871489

1490+
!> Intel: Needs -warn last for error on unknown command line arguments to work
1491+
if (self%id == id_intel_llvm_nix) then
1492+
flags = flags//" "//flag_intel_warn
1493+
ldflags = ldflags//" "//flag_intel_warn
1494+
elseif (self%id == id_intel_llvm_windows) then
1495+
flags = flags//" "//flag_intel_warn_win
1496+
ldflags = ldflags//" "//flag_intel_warn_win
1497+
end if
1498+
14881499
!> Compile and link program
14891500
call self%compile_fortran(source, object, flags, logf, stat)
14901501
if (stat==0) &

test/fpm_test/test_compiler.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -46,11 +46,6 @@ subroutine test_check_fortran_source_runs(error)
4646
return
4747
end if
4848

49-
if (compiler%is_intel()) then
50-
print *, "TODO: test_check_fortran_source_runs fails for Intel compilers"
51-
return
52-
end if
53-
5449
!> Test fortran-source runs
5550
if (.not.compiler%check_fortran_source_runs("print *, 'Hello world!'; end")) then
5651
call test_failed(error, "Cannot run Fortran hello world")
@@ -76,15 +71,20 @@ subroutine test_check_fortran_source_runs(error)
7671
end if
7772

7873
!> Test the flag check wrapper
79-
if (compiler%check_flags_supported(compile_flags='-Werror=unknown-flag')) then
74+
if (compiler%check_flags_supported(compile_flags='-Werror=unknown-flag') &
75+
.and. .not. compiler%is_intel()) then ! Intel will not trigger an error
76+
call test_failed(error, "Invalid compile flags did not trigger an error")
77+
return
78+
end if
79+
if (compiler%check_flags_supported(compile_flags='-unknown-flag')) then
8080
call test_failed(error, "Invalid compile flags did not trigger an error")
8181
return
8282
end if
8383
if (compiler%check_flags_supported(link_flags='-Wl,--nonexistent-linker-option')) then
8484
call test_failed(error, "Invalid link flags did not trigger an error")
8585
return
8686
end if
87-
if (compiler%check_flags_supported(compile_flags='-Werror=unknown-flag', &
87+
if (compiler%check_flags_supported(compile_flags='-Werror=eunknown-flag', &
8888
link_flags='-Wl,--nonexistent-linker-option')) then
8989
call test_failed(error, "Invalid compile and link flags did not trigger an error")
9090
return

0 commit comments

Comments
 (0)