@@ -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