Skip to content

Commit b587fdf

Browse files
committed
ifx crash: fix fPIC logic
1 parent ad69e28 commit b587fdf

File tree

3 files changed

+44
-20
lines changed

3 files changed

+44
-20
lines changed

ci/run_tests.sh

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -317,7 +317,7 @@ popd
317317

318318
# Test shared library dependencies
319319
pushd shared_lib
320-
"$fpm" build || EXIT_CODE=$?
320+
"$fpm" build --verbose || EXIT_CODE=$?
321321
test $EXIT_CODE -eq 0
322322
popd
323323

src/fpm.f90

Lines changed: 36 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,9 @@ module fpm
1212
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1313
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1414
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
15-
use fpm_compiler, only: new_compiler, new_archiver, set_cpp_preprocessor_flags
15+
use fpm_compiler, only: new_compiler, new_archiver, set_cpp_preprocessor_flags, &
16+
id_intel_classic_nix,id_intel_classic_mac,id_intel_llvm_nix, &
17+
id_intel_llvm_unknown
1618

1719

1820
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -335,28 +337,46 @@ subroutine new_compiler_flags(model, settings, package)
335337
type(fpm_build_settings), intent(in) :: settings
336338
type(package_config_t), intent(in) :: package
337339

338-
logical :: release_profile, debug_profile
340+
logical :: release_request, debug_request, need_defaults
341+
character(len=:), allocatable :: fallback
339342

340-
release_profile = .false.
341-
debug_profile = .false.
342-
if (allocated(settings%profile)) release_profile = settings%profile == "release"
343-
if (allocated(settings%profile)) debug_profile = settings%profile == "debug"
344-
345-
! Debug./Release profile requested but not defined:
346-
! fallback to backward-compatible behavior
347-
if ( (release_profile .and. package%find_profile("release")==0) &
348-
.or. (debug_profile .and. package%find_profile("debug")==0) ) then
343+
! Default: "debug" if not requested
344+
release_request = .false.
345+
debug_request = .not.allocated(settings%profile)
346+
if (allocated(settings%profile)) release_request = settings%profile == "release"
347+
if (allocated(settings%profile)) debug_request = settings%profile == "debug"
348+
349+
need_defaults = release_request .or. debug_request
350+
351+
! Backward-compatible: if debug/release requested, but a user-defined profile is not defined,
352+
! apply fpm compiler defaults
353+
if (need_defaults) then
354+
355+
need_defaults = (release_request .and. package%find_profile("release")<=0) &
356+
.or. (debug_request .and. package%find_profile("debug")<=0)
349357

350-
model%fortran_compile_flags = assemble_flags(settings%flag,package%flags,&
351-
model%compiler%get_default_flags(release_profile))
358+
end if
359+
360+
! Fix: Always include compiler default flags for Intel ifx -fPIC issue
361+
if (need_defaults) then
352362

363+
fallback = model%compiler%get_default_flags(release_request)
364+
365+
elseif (any(model%compiler%id==[id_intel_classic_mac, &
366+
id_intel_classic_nix, &
367+
id_intel_llvm_nix, &
368+
id_intel_llvm_unknown])) then
369+
370+
! Intel compilers need -fPIC for shared libraries (except Windows)
371+
fallback = " -fPIC"
353372

354373
else
355374

356-
model%fortran_compile_flags = assemble_flags(settings%flag, package%flags)
375+
if (allocated(fallback)) deallocate(fallback) ! trigger .not.present
357376

358-
end if
359-
377+
endif
378+
379+
model%fortran_compile_flags = assemble_flags(settings%flag, package%flags, fallback)
360380
model%c_compile_flags = assemble_flags(settings%cflag, package%c_flags)
361381
model%cxx_compile_flags = assemble_flags(settings%cxxflag, package%cxx_flags)
362382
model%link_flags = assemble_flags(settings%ldflag, package%link_time_flags)

src/fpm_targets.f90

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1076,7 +1076,7 @@ end subroutine prune_build_targets
10761076
subroutine resolve_target_linking(targets, model, library, error)
10771077
type(build_target_ptr), intent(inout), target :: targets(:)
10781078
type(fpm_model_t), intent(in) :: model
1079-
type(library_config_t), intent(in), optional :: library
1079+
type(library_config_t), intent(in), optional :: library
10801080
type(error_t), allocatable, intent(out) :: error
10811081

10821082
integer :: i,j
@@ -1085,8 +1085,10 @@ subroutine resolve_target_linking(targets, model, library, error)
10851085
character(:), allocatable :: global_link_flags, local_link_flags
10861086
character(:), allocatable :: global_include_flags, shared_lib_paths
10871087

1088+
10881089
if (size(targets) == 0) return
10891090

1091+
10901092
global_link_flags = ""
10911093
if (allocated(model%link_libraries)) then
10921094
if (size(model%link_libraries) > 0) then
@@ -1116,13 +1118,14 @@ subroutine resolve_target_linking(targets, model, library, error)
11161118

11171119
associate(target => targets(i)%ptr)
11181120

1121+
11191122
! If the main program is a C/C++ one, some compilers require additional linking flags, see
11201123
! https://stackoverflow.com/questions/36221612/p3dfft-compilation-ifort-compiler-error-multiple-definiton-of-main
11211124
! In this case, compile_flags were already allocated
11221125
if (.not.allocated(target%compile_flags)) allocate(character(len=0) :: target%compile_flags)
11231126

11241127
target%compile_flags = target%compile_flags//' '
1125-
1128+
11261129
select case (target%target_type)
11271130
case (FPM_TARGET_C_OBJECT)
11281131
target%compile_flags = target%compile_flags//model%c_compile_flags
@@ -1141,7 +1144,8 @@ subroutine resolve_target_linking(targets, model, library, error)
11411144
if (len(global_include_flags) > 0) then
11421145
target%compile_flags = target%compile_flags//global_include_flags
11431146
end if
1144-
1147+
1148+
11451149
call target%set_output_dir(get_output_dir(model%build_prefix, target%compile_flags))
11461150

11471151
end associate

0 commit comments

Comments
 (0)