Skip to content

Commit 39a97c4

Browse files
authored
Add flags to link main programs with C/C++ main (#896)
2 parents d9d93c2 + c461c64 commit 39a97c4

File tree

2 files changed

+110
-32
lines changed

2 files changed

+110
-32
lines changed

src/fpm_compiler.F90

Lines changed: 62 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -96,6 +96,8 @@ module fpm_compiler
9696
procedure :: get_include_flag
9797
!> Get feature flag
9898
procedure :: get_feature_flag
99+
!> Get flags for the main linking command
100+
procedure :: get_main_flags
99101
!> Compile a Fortran object
100102
procedure :: compile_fortran
101103
!> Compile a C object
@@ -106,6 +108,8 @@ module fpm_compiler
106108
procedure :: link
107109
!> Check whether compiler is recognized
108110
procedure :: is_unknown
111+
!> Check whether compiler is Intel family
112+
procedure :: is_intel
109113
!> Enumerate libraries, based on compiler and platform
110114
procedure :: enumerate_libraries
111115
end type compiler_t
@@ -211,7 +215,7 @@ module fpm_compiler
211215
flag_cray_implicit_typing = " -el", &
212216
flag_cray_fixed_form = " -ffixed", &
213217
flag_cray_free_form = " -ffree"
214-
218+
215219
contains
216220

217221

@@ -440,7 +444,7 @@ pure subroutine set_cpp_preprocessor_flags(id, flags)
440444

441445
end subroutine set_cpp_preprocessor_flags
442446

443-
!> This function will parse and read the macros list and
447+
!> This function will parse and read the macros list and
444448
!> return them as defined flags.
445449
function get_macros(id, macros_list, version) result(macros)
446450
integer(compiler_enum), intent(in) :: id
@@ -450,7 +454,7 @@ function get_macros(id, macros_list, version) result(macros)
450454
character(len=:), allocatable :: macros
451455
character(len=:), allocatable :: macro_definition_symbol
452456
character(:), allocatable :: valued_macros(:)
453-
457+
454458

455459
integer :: i
456460

@@ -473,10 +477,10 @@ function get_macros(id, macros_list, version) result(macros)
473477
end if
474478

475479
do i = 1, size(macros_list)
476-
480+
477481
!> Split the macro name and value.
478482
call split(macros_list(i)%s, valued_macros, delimiters="=")
479-
483+
480484
if (size(valued_macros) > 1) then
481485
!> Check if the value of macro starts with '{' character.
482486
if (str_begins_with_str(trim(valued_macros(size(valued_macros))), "{")) then
@@ -486,15 +490,15 @@ function get_macros(id, macros_list, version) result(macros)
486490

487491
!> Check if the string contains "version" as substring.
488492
if (index(valued_macros(size(valued_macros)), "version") /= 0) then
489-
493+
490494
!> These conditions are placed in order to ensure proper spacing between the macros.
491495
macros = macros//macro_definition_symbol//trim(valued_macros(1))//'='//version
492496
cycle
493497
end if
494498
end if
495-
end if
499+
end if
496500
end if
497-
501+
498502
macros = macros//macro_definition_symbol//macros_list(i)%s
499503

500504
end do
@@ -664,6 +668,49 @@ function get_feature_flag(self, feature) result(flags)
664668
end function get_feature_flag
665669

666670

671+
!> Get special flags for the main linker
672+
subroutine get_main_flags(self, language, flags)
673+
class(compiler_t), intent(in) :: self
674+
character(len=*), intent(in) :: language
675+
character(len=:), allocatable, intent(out) :: flags
676+
677+
flags = ""
678+
select case(language)
679+
680+
case("fortran")
681+
flags = ""
682+
683+
case("c")
684+
685+
! If the main program is on a C/C++ source, the Intel Fortran compiler requires option
686+
! -nofor-main to avoid "duplicate main" errors.
687+
! https://stackoverflow.com/questions/36221612/p3dfft-compilation-ifort-compiler-error-multiple-definiton-of-main
688+
select case(self%id)
689+
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_llvm_nix)
690+
flags = '-nofor-main'
691+
case(id_intel_classic_windows,id_intel_llvm_windows)
692+
flags = '/nofor-main'
693+
case (id_pgi,id_nvhpc)
694+
flags = '-Mnomain'
695+
end select
696+
697+
case("c++","cpp","cxx")
698+
699+
select case(self%id)
700+
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_llvm_nix)
701+
flags = '-nofor-main'
702+
case(id_intel_classic_windows,id_intel_llvm_windows)
703+
flags = '/nofor-main'
704+
case (id_pgi,id_nvhpc)
705+
flags = '-Mnomain'
706+
end select
707+
708+
case default
709+
error stop "Unknown language '"//language//'", try "fortran", "c", "c++"'
710+
end select
711+
712+
end subroutine get_main_flags
713+
667714
subroutine get_default_c_compiler(f_compiler, c_compiler)
668715
character(len=*), intent(in) :: f_compiler
669716
character(len=:), allocatable, intent(out) :: c_compiler
@@ -883,6 +930,12 @@ pure function is_unknown(self)
883930
is_unknown = self%id == id_unknown
884931
end function is_unknown
885932

933+
pure logical function is_intel(self)
934+
class(compiler_t), intent(in) :: self
935+
is_intel = any(self%id == [id_intel_classic_mac,id_intel_classic_nix,id_intel_classic_windows,&
936+
id_intel_llvm_nix,id_intel_llvm_unknown,id_intel_llvm_windows])
937+
end function is_intel
938+
886939
!>
887940
!> Enumerate libraries, based on compiler and platform
888941
!>
@@ -917,7 +970,7 @@ subroutine new_compiler(self, fc, cc, cxx, echo, verbose)
917970
logical, intent(in) :: verbose
918971

919972
self%id = get_compiler_id(fc)
920-
973+
921974
self%echo = echo
922975
self%verbose = verbose
923976
self%fc = fc

src/fpm_targets.f90

Lines changed: 48 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -194,7 +194,7 @@ subroutine build_target_list(targets,model)
194194
type(fpm_model_t), intent(inout), target :: model
195195

196196
integer :: i, j, n_source, exe_type
197-
character(:), allocatable :: xsuffix, exe_dir
197+
character(:), allocatable :: xsuffix, exe_dir, compile_flags
198198
logical :: with_lib
199199

200200
! Check for empty build (e.g. header-only lib)
@@ -240,14 +240,14 @@ subroutine build_target_list(targets,model)
240240
features = model%packages(j)%features, &
241241
macros = model%packages(j)%macros, &
242242
version = model%packages(j)%version)
243-
243+
244244

245245
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
246246
! Archive depends on object
247247
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
248248
end if
249249

250-
case (FPM_UNIT_CPPSOURCE)
250+
case (FPM_UNIT_CPPSOURCE)
251251

252252
call add_target(targets,package=model%packages(j)%name,source = sources(i), &
253253
type = FPM_TARGET_CPP_OBJECT, &
@@ -307,14 +307,29 @@ subroutine build_target_list(targets,model)
307307
output_name = join_path(exe_dir, &
308308
sources(i)%exe_name//xsuffix))
309309

310+
associate(target => targets(size(targets))%ptr)
311+
312+
! Linker-only flags are necessary on some compilers for codes with non-Fortran main
313+
select case (exe_type)
314+
case (FPM_TARGET_C_OBJECT)
315+
call model%compiler%get_main_flags("c",compile_flags)
316+
case (FPM_TARGET_CPP_OBJECT)
317+
call model%compiler%get_main_flags("c++",compile_flags)
318+
case default
319+
compile_flags = ""
320+
end select
321+
target%compile_flags = target%compile_flags//' '//compile_flags
322+
310323
! Executable depends on object
311-
call add_dependency(targets(size(targets))%ptr, targets(size(targets)-1)%ptr)
324+
call add_dependency(target, targets(size(targets)-1)%ptr)
312325

313326
if (with_lib) then
314327
! Executable depends on library
315-
call add_dependency(targets(size(targets))%ptr, targets(1)%ptr)
328+
call add_dependency(target, targets(1)%ptr)
316329
end if
317330

331+
endassociate
332+
318333
end select
319334

320335
end do
@@ -385,7 +400,7 @@ subroutine collect_exe_link_dependencies(targets)
385400
dep%source%unit_type /= FPM_UNIT_MODULE .and. &
386401
index(dirname(dep%source%file_name), exe_source_dir) == 1) then
387402

388-
call add_dependency(exe, dep)
403+
call add_dependency(exe, dep)
389404

390405
end if
391406

@@ -583,13 +598,13 @@ subroutine prune_build_targets(targets, root_package)
583598
type(build_target_ptr), intent(inout), allocatable :: targets(:)
584599

585600
!> Name of root package
586-
character(*), intent(in) :: root_package
601+
character(*), intent(in) :: root_package
587602

588603
integer :: i, j, nexec
589604
type(string_t), allocatable :: modules_used(:)
590605
logical :: exclude_target(size(targets))
591606
logical, allocatable :: exclude_from_archive(:)
592-
607+
593608
if (size(targets) < 1) then
594609
return
595610
end if
@@ -599,7 +614,7 @@ subroutine prune_build_targets(targets, root_package)
599614

600615
! Enumerate modules used by executables, non-module subprograms and their dependencies
601616
do i=1,size(targets)
602-
617+
603618
if (targets(i)%ptr%target_type == FPM_TARGET_EXECUTABLE) then
604619

605620
nexec = nexec + 1
@@ -620,16 +635,16 @@ subroutine prune_build_targets(targets, root_package)
620635
! If there aren't any executables, then prune
621636
! based on modules used in root package
622637
if (nexec < 1) then
623-
638+
624639
do i=1,size(targets)
625-
640+
626641
if (targets(i)%ptr%package_name == root_package .and. &
627642
targets(i)%ptr%target_type /= FPM_TARGET_ARCHIVE) then
628-
643+
629644
call collect_used_modules(targets(i)%ptr)
630-
645+
631646
end if
632-
647+
633648
end do
634649

635650
end if
@@ -651,11 +666,11 @@ subroutine prune_build_targets(targets, root_package)
651666
do j=1,size(target%source%modules_provided)
652667

653668
if (target%source%modules_provided(j)%s .in. modules_used) then
654-
669+
655670
exclude_target(i) = .false.
656671
target%skip = .false.
657672

658-
end if
673+
end if
659674

660675
end do
661676

@@ -667,11 +682,11 @@ subroutine prune_build_targets(targets, root_package)
667682
do j=1,size(target%source%parent_modules)
668683

669684
if (target%source%parent_modules(j)%s .in. modules_used) then
670-
685+
671686
exclude_target(i) = .false.
672687
target%skip = .false.
673688

674-
end if
689+
end if
675690

676691
end do
677692

@@ -684,7 +699,7 @@ subroutine prune_build_targets(targets, root_package)
684699
target%skip = .false.
685700
end if
686701

687-
end associate
702+
end associate
688703
end do
689704

690705
targets = pack(targets,.not.exclude_target)
@@ -809,20 +824,30 @@ subroutine resolve_target_linking(targets, model)
809824
do i=1,size(targets)
810825

811826
associate(target => targets(i)%ptr)
827+
828+
! May have been previously allocated
829+
if (.not.allocated(target%compile_flags)) allocate(character(len=0) :: target%compile_flags)
830+
831+
target%compile_flags = target%compile_flags//' '
832+
812833
if (target%target_type /= FPM_TARGET_C_OBJECT .and. target%target_type /= FPM_TARGET_CPP_OBJECT) then
813-
target%compile_flags = model%fortran_compile_flags &
834+
target%compile_flags = target%compile_flags//model%fortran_compile_flags &
814835
& // get_feature_flags(model%compiler, target%features)
815836
else if (target%target_type == FPM_TARGET_C_OBJECT) then
816-
target%compile_flags = model%c_compile_flags
837+
target%compile_flags = target%compile_flags//model%c_compile_flags
817838
else if(target%target_type == FPM_TARGET_CPP_OBJECT) then
818-
target%compile_flags = model%cxx_compile_flags
839+
target%compile_flags = target%compile_flags//model%cxx_compile_flags
819840
end if
820841

842+
! If the main program is a C/C++ one, Intel compilers require additional
843+
! linking flag -nofor-main to avoid a "duplicate main" error, see
844+
! https://stackoverflow.com/questions/36221612/p3dfft-compilation-ifort-compiler-error-multiple-definiton-of-main
845+
821846
!> Get macros as flags.
822847
target%compile_flags = target%compile_flags // get_macros(model%compiler%id, &
823848
target%macros, &
824849
target%version)
825-
850+
826851
if (len(global_include_flags) > 0) then
827852
target%compile_flags = target%compile_flags//global_include_flags
828853
end if

0 commit comments

Comments
 (0)