@@ -194,7 +194,7 @@ subroutine build_target_list(targets,model)
194
194
type (fpm_model_t), intent (inout ), target :: model
195
195
196
196
integer :: i, j, n_source, exe_type
197
- character (:), allocatable :: xsuffix, exe_dir
197
+ character (:), allocatable :: xsuffix, exe_dir, compile_flags
198
198
logical :: with_lib
199
199
200
200
! Check for empty build (e.g. header-only lib)
@@ -240,14 +240,14 @@ subroutine build_target_list(targets,model)
240
240
features = model% packages(j)% features, &
241
241
macros = model% packages(j)% macros, &
242
242
version = model% packages(j)% version)
243
-
243
+
244
244
245
245
if (with_lib .and. sources(i)% unit_scope == FPM_SCOPE_LIB) then
246
246
! Archive depends on object
247
247
call add_dependency(targets(1 )% ptr, targets(size (targets))% ptr)
248
248
end if
249
249
250
- case (FPM_UNIT_CPPSOURCE)
250
+ case (FPM_UNIT_CPPSOURCE)
251
251
252
252
call add_target(targets,package= model% packages(j)% name,source = sources(i), &
253
253
type = FPM_TARGET_CPP_OBJECT, &
@@ -307,14 +307,29 @@ subroutine build_target_list(targets,model)
307
307
output_name = join_path(exe_dir, &
308
308
sources(i)% exe_name// xsuffix))
309
309
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
+
310
323
! 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)
312
325
313
326
if (with_lib) then
314
327
! Executable depends on library
315
- call add_dependency(targets( size (targets)) % ptr , targets(1 )% ptr)
328
+ call add_dependency(target , targets(1 )% ptr)
316
329
end if
317
330
331
+ endassociate
332
+
318
333
end select
319
334
320
335
end do
@@ -385,7 +400,7 @@ subroutine collect_exe_link_dependencies(targets)
385
400
dep% source% unit_type /= FPM_UNIT_MODULE .and. &
386
401
index (dirname(dep% source% file_name), exe_source_dir) == 1 ) then
387
402
388
- call add_dependency(exe, dep)
403
+ call add_dependency(exe, dep)
389
404
390
405
end if
391
406
@@ -583,13 +598,13 @@ subroutine prune_build_targets(targets, root_package)
583
598
type (build_target_ptr), intent (inout ), allocatable :: targets(:)
584
599
585
600
! > Name of root package
586
- character (* ), intent (in ) :: root_package
601
+ character (* ), intent (in ) :: root_package
587
602
588
603
integer :: i, j, nexec
589
604
type (string_t), allocatable :: modules_used(:)
590
605
logical :: exclude_target(size (targets))
591
606
logical , allocatable :: exclude_from_archive(:)
592
-
607
+
593
608
if (size (targets) < 1 ) then
594
609
return
595
610
end if
@@ -599,7 +614,7 @@ subroutine prune_build_targets(targets, root_package)
599
614
600
615
! Enumerate modules used by executables, non-module subprograms and their dependencies
601
616
do i= 1 ,size (targets)
602
-
617
+
603
618
if (targets(i)% ptr% target_type == FPM_TARGET_EXECUTABLE) then
604
619
605
620
nexec = nexec + 1
@@ -620,16 +635,16 @@ subroutine prune_build_targets(targets, root_package)
620
635
! If there aren't any executables, then prune
621
636
! based on modules used in root package
622
637
if (nexec < 1 ) then
623
-
638
+
624
639
do i= 1 ,size (targets)
625
-
640
+
626
641
if (targets(i)% ptr% package_name == root_package .and. &
627
642
targets(i)% ptr% target_type /= FPM_TARGET_ARCHIVE) then
628
-
643
+
629
644
call collect_used_modules(targets(i)% ptr)
630
-
645
+
631
646
end if
632
-
647
+
633
648
end do
634
649
635
650
end if
@@ -651,11 +666,11 @@ subroutine prune_build_targets(targets, root_package)
651
666
do j= 1 ,size (target % source% modules_provided)
652
667
653
668
if (target % source% modules_provided(j)% s .in . modules_used) then
654
-
669
+
655
670
exclude_target(i) = .false.
656
671
target % skip = .false.
657
672
658
- end if
673
+ end if
659
674
660
675
end do
661
676
@@ -667,11 +682,11 @@ subroutine prune_build_targets(targets, root_package)
667
682
do j= 1 ,size (target % source% parent_modules)
668
683
669
684
if (target % source% parent_modules(j)% s .in . modules_used) then
670
-
685
+
671
686
exclude_target(i) = .false.
672
687
target % skip = .false.
673
688
674
- end if
689
+ end if
675
690
676
691
end do
677
692
@@ -684,7 +699,7 @@ subroutine prune_build_targets(targets, root_package)
684
699
target % skip = .false.
685
700
end if
686
701
687
- end associate
702
+ end associate
688
703
end do
689
704
690
705
targets = pack (targets,.not. exclude_target)
@@ -809,20 +824,30 @@ subroutine resolve_target_linking(targets, model)
809
824
do i= 1 ,size (targets)
810
825
811
826
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
+
812
833
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 &
814
835
& // get_feature_flags(model% compiler, target % features)
815
836
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
817
838
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
819
840
end if
820
841
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
+
821
846
! > Get macros as flags.
822
847
target % compile_flags = target % compile_flags // get_macros(model% compiler% id, &
823
848
target % macros, &
824
849
target % version)
825
-
850
+
826
851
if (len (global_include_flags) > 0 ) then
827
852
target % compile_flags = target % compile_flags// global_include_flags
828
853
end if
0 commit comments