Skip to content

Commit 270f102

Browse files
authored
Merge branch 'main' into features_application
2 parents 8e37737 + e01591b commit 270f102

File tree

14 files changed

+538
-64
lines changed

14 files changed

+538
-64
lines changed

ci/run_tests.sh

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -164,6 +164,11 @@ pushd program_with_module
164164
"$fpm" run --target Program_with_module
165165
popd
166166

167+
pushd program_with_cpp_guarded_module
168+
"$fpm" build
169+
"$fpm" run
170+
popd
171+
167172
pushd link_executable
168173
"$fpm" build
169174
"$fpm" run --target gomp_test
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
build/*
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
program program_with_module
2+
#if defined(HAVE_MODULE)
3+
use greet_m, only: greeting
4+
#endif
5+
implicit none
6+
7+
#ifndef HAVE_MODULE
8+
print *, 'OK without module'
9+
#else
10+
print *, greeting
11+
#endif
12+
end program program_with_module
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
name = "Program_with_cpp_guarded_module"
2+
# Enable CPP but do not define macros
3+
[preprocess.cpp]

src/fpm.f90

Lines changed: 10 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -169,7 +169,8 @@ subroutine build_model(model, settings, package_config, error)
169169
lib_dir = join_path(dep%proj_dir, manifest%library%source_dir)
170170
if (is_dir(lib_dir)) then
171171
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
172-
with_f_ext=model%packages(i)%preprocess%suffixes, error=error)
172+
with_f_ext=model%packages(i)%preprocess%suffixes, error=error, &
173+
preprocess=model%packages(i)%preprocess)
173174
if (allocated(error)) exit
174175
end if
175176
end if
@@ -223,7 +224,7 @@ subroutine build_model(model, settings, package_config, error)
223224
if (is_dir('app') .and. auto_exe) then
224225
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
225226
with_executables=.true., with_f_ext=model%packages(1)%preprocess%suffixes,&
226-
error=error)
227+
error=error,preprocess=model%packages(1)%preprocess)
227228

228229
if (allocated(error)) then
229230
return
@@ -233,7 +234,8 @@ subroutine build_model(model, settings, package_config, error)
233234
if (is_dir('example') .and. auto_example) then
234235
call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, &
235236
with_executables=.true., &
236-
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
237+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
238+
preprocess=model%packages(1)%preprocess)
237239

238240
if (allocated(error)) then
239241
return
@@ -243,7 +245,8 @@ subroutine build_model(model, settings, package_config, error)
243245
if (is_dir('test') .and. auto_test) then
244246
call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, &
245247
with_executables=.true., &
246-
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
248+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
249+
preprocess=model%packages(1)%preprocess)
247250

248251
if (allocated(error)) then
249252
return
@@ -254,7 +257,7 @@ subroutine build_model(model, settings, package_config, error)
254257
call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, &
255258
auto_discover=auto_exe, &
256259
with_f_ext=model%packages(1)%preprocess%suffixes, &
257-
error=error)
260+
error=error,preprocess=model%packages(1)%preprocess)
258261

259262
if (allocated(error)) then
260263
return
@@ -265,7 +268,7 @@ subroutine build_model(model, settings, package_config, error)
265268
call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, &
266269
auto_discover=auto_example, &
267270
with_f_ext=model%packages(1)%preprocess%suffixes, &
268-
error=error)
271+
error=error,preprocess=model%packages(1)%preprocess)
269272

270273
if (allocated(error)) then
271274
return
@@ -276,7 +279,7 @@ subroutine build_model(model, settings, package_config, error)
276279
call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, &
277280
auto_discover=auto_test, &
278281
with_f_ext=model%packages(1)%preprocess%suffixes, &
279-
error=error)
282+
error=error,preprocess=model%packages(1)%preprocess)
280283

281284
if (allocated(error)) then
282285
return

src/fpm/manifest/feature.f90

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -40,12 +40,7 @@ module fpm_manifest_feature
4040
use fpm_error, only: error_t, fatal_error, syntax_error
4141
use fpm_environment, only: OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, OS_CYGWIN, OS_SOLARIS, &
4242
OS_FREEBSD, OS_OPENBSD, OS_ALL, OS_NAME, match_os_type
43-
use fpm_compiler, only: compiler_enum, compiler_id_name, match_compiler_type, &
44-
id_unknown, id_gcc, id_f95, id_caf, &
45-
id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows, &
46-
id_intel_llvm_nix, id_intel_llvm_windows, id_intel_llvm_unknown, &
47-
id_pgi, id_nvhpc, id_nag, id_flang, id_flang_new, id_f18, &
48-
id_ibmxl, id_cray, id_lahey, id_lfortran, id_all
43+
use fpm_compiler, only: compiler_enum, compiler_id_name, match_compiler_type, id_all
4944
use fpm_strings, only: string_t, lower, operator(==)
5045
use tomlf, only: toml_table, toml_array, toml_key, toml_stat
5146
use fpm_toml, only: get_value, len, serializable_t, set_value, set_string, set_list, add_table, &

src/fpm/manifest/feature_collection.f90

Lines changed: 13 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,7 @@ module fpm_manifest_feature_collection
1515
id_unknown, id_gcc, id_f95, id_caf, &
1616
id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows, &
1717
id_intel_llvm_nix, id_intel_llvm_windows, id_intel_llvm_unknown, &
18-
id_pgi, id_nvhpc, id_nag, id_flang, id_flang_new, id_f18, &
19-
id_ibmxl, id_cray, id_lahey, id_lfortran, id_all
18+
id_pgi, id_nvhpc, id_nag, id_flang, id_lahey, id_lfortran, id_all
2019
use fpm_strings, only: string_t, lower, operator(==), split, str
2120
use tomlf, only: toml_table, toml_array, toml_key, toml_stat
2221
use fpm_toml, only: get_value, len, serializable_t, set_value, set_string, set_list, add_table, &
@@ -857,38 +856,38 @@ function default_release_feature() result(collection)
857856
collection%base%default = .true.
858857

859858
! Add release variants for different compilers
860-
call collection%push_variant(default_variant('release-caf', id_caf, OS_ALL, &
859+
call collection%push_variant(default_variant('release', id_caf, OS_ALL, &
861860
' -O3 -Wimplicit-interface -fPIC -fmax-errors=1 -funroll-loops'))
862861

863-
call collection%push_variant(default_variant('release-gfortran', id_gcc, OS_ALL, &
862+
call collection%push_variant(default_variant('release', id_gcc, OS_ALL, &
864863
' -O3 -Wimplicit-interface -fPIC -fmax-errors=1 -funroll-loops -fcoarray=single'))
865864

866-
call collection%push_variant(default_variant('release-f95', id_f95, OS_ALL, &
865+
call collection%push_variant(default_variant('release', id_f95, OS_ALL, &
867866
' -O3 -Wimplicit-interface -fPIC -fmax-errors=1 -ffast-math -funroll-loops'))
868867

869-
call collection%push_variant(default_variant('release-nvfortran', id_nvhpc, OS_ALL, &
868+
call collection%push_variant(default_variant('release', id_nvhpc, OS_ALL, &
870869
' -Mbackslash'))
871870

872-
call collection%push_variant(default_variant('release-ifort', id_intel_classic_nix, OS_ALL, &
871+
call collection%push_variant(default_variant('release', id_intel_classic_nix, OS_LINUX, &
873872
' -fp-model precise -pc64 -align all -error-limit 1 -reentrancy&
874873
& threaded -nogen-interfaces -assume byterecl'))
875874

876-
call collection%push_variant(default_variant('release-ifort-windows', id_intel_classic_nix, &
875+
call collection%push_variant(default_variant('release', id_intel_classic_windows, &
877876
OS_WINDOWS, ' /fp:precise /align:all /error-limit:1 /reentrancy:threaded&
878877
& /nogen-interfaces /assume:byterecl'))
879878

880-
call collection%push_variant(default_variant('release-ifx', id_intel_llvm_nix, OS_ALL, &
881-
' -fp-model=precise -pc64 -align all -error-limit 1 -reentrancy&
882-
& threaded -nogen-interfaces -assume byterecl'))
879+
call collection%push_variant(default_variant('release', id_intel_llvm_nix, &
880+
OS_LINUX, ' -fp-model=precise -pc64 -align all -error-limit 1 -reentrancy threaded&
881+
& -nogen-interfaces -assume byterecl'))
883882

884-
call collection%push_variant(default_variant('release-ifx-windows', id_intel_llvm_nix, &
883+
call collection%push_variant(default_variant('release', id_intel_llvm_nix, &
885884
OS_WINDOWS, ' /fp:precise /align:all /error-limit:1 /reentrancy:threaded&
886885
& /nogen-interfaces /assume:byterecl'))
887886

888-
call collection%push_variant(default_variant('release-nagfor', id_nag, OS_ALL, &
887+
call collection%push_variant(default_variant('release', id_nag, OS_ALL, &
889888
' -O4 -coarray=single -PIC'))
890889

891-
call collection%push_variant(default_variant('release-lfortran', id_lfortran, OS_ALL, &
890+
call collection%push_variant(default_variant('release', id_lfortran, OS_ALL, &
892891
' flag_lfortran_opt'))
893892

894893
end function default_release_feature

src/fpm_compiler.F90

Lines changed: 49 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@
1010
! Intel oneAPI ifx icx -module -I -qopenmp X
1111
! PGI pgfortran pgcc -module -I -mp X
1212
! NVIDIA nvfortran nvc -module -I -mp X
13-
! LLVM flang flang clang -module -I -mp X
13+
! LLVM flang flang clang -module-dir -I -fopenmp X
1414
! LFortran lfortran --- -J -I --openmp X
1515
! Lahey/Futjitsu lfc ? -M -I -openmp ?
1616
! NAG nagfor ? -mdir -I -openmp x
@@ -71,8 +71,8 @@ module fpm_compiler
7171
id_pgi, &
7272
id_nvhpc, &
7373
id_nag, &
74+
id_flang_classic, &
7475
id_flang, &
75-
id_flang_new, &
7676
id_f18, &
7777
id_ibmxl, &
7878
id_cray, &
@@ -275,7 +275,13 @@ module fpm_compiler
275275
flag_cray_free_form = " -ffree"
276276

277277
character(*), parameter :: &
278-
flag_flang_new_openmp = " -fopenmp"
278+
flag_flang_new_openmp = " -fopenmp", &
279+
flag_flang_new_debug = " -g", &
280+
flag_flang_new_opt = " -O3", &
281+
flag_flang_new_pic = " -fPIC", &
282+
flag_flang_new_free_form = " -ffree-form", &
283+
flag_flang_new_fixed_form = " -ffixed-form", &
284+
flag_flang_new_no_implicit_typing = " -fimplicit-none"
279285

280286
contains
281287

@@ -296,11 +302,11 @@ function get_default_flags(self, release) result(flags)
296302
! Append position-independent code (PIC) flag, that is necessary
297303
! building shared libraries
298304
select case (self%id)
299-
case (id_gcc, id_f95, id_caf, id_flang, id_f18, id_lfortran, &
305+
case (id_gcc, id_f95, id_caf, id_flang_classic, id_f18, id_lfortran, &
300306
id_intel_classic_nix, id_intel_classic_mac, id_intel_llvm_nix, &
301307
id_pgi, id_nvhpc, id_nag, id_cray, id_ibmxl)
302308
pic_flag = " -fPIC"
303-
case (id_flang_new)
309+
case (id_flang)
304310
! flang-new doesn't support -fPIC on Windows MSVC target
305311
if (get_os_type() == OS_WINDOWS) then
306312
pic_flag = ""
@@ -414,6 +420,11 @@ subroutine get_release_compile_flags(id, flags)
414420
flags = &
415421
flag_lfortran_opt
416422

423+
case(id_flang)
424+
flags = &
425+
flag_flang_new_opt//&
426+
flag_flang_new_pic
427+
417428
end select
418429
end subroutine get_release_compile_flags
419430

@@ -509,6 +520,12 @@ subroutine get_debug_compile_flags(id, flags)
509520

510521
case(id_lfortran)
511522
flags = ""
523+
524+
case(id_flang)
525+
flags = &
526+
flag_flang_new_debug//&
527+
flag_flang_new_pic
528+
512529
end select
513530
end subroutine get_debug_compile_flags
514531

@@ -521,7 +538,7 @@ pure subroutine set_cpp_preprocessor_flags(id, flags)
521538
select case(id)
522539
case default
523540
flag_cpp_preprocessor = ""
524-
case(id_caf, id_gcc, id_f95, id_nvhpc, id_flang_new)
541+
case(id_caf, id_gcc, id_f95, id_nvhpc, id_flang)
525542
flag_cpp_preprocessor = "-cpp"
526543
case(id_intel_classic_windows, id_intel_llvm_windows)
527544
flag_cpp_preprocessor = "/fpp"
@@ -616,7 +633,7 @@ function get_include_flag(self, path) result(flags)
616633
flags = "-I "//path
617634

618635
case(id_caf, id_gcc, id_f95, id_cray, id_nvhpc, id_pgi, &
619-
& id_flang, id_flang_new, id_f18, &
636+
& id_flang_classic, id_flang, id_f18, &
620637
& id_intel_classic_nix, id_intel_classic_mac, &
621638
& id_intel_llvm_nix, id_lahey, id_nag, id_ibmxl, &
622639
& id_lfortran)
@@ -640,10 +657,10 @@ function get_module_flag(self, path) result(flags)
640657
case(id_caf, id_gcc, id_f95, id_cray, id_lfortran)
641658
flags = "-J "//path
642659

643-
case(id_nvhpc, id_pgi, id_flang)
660+
case(id_nvhpc, id_pgi, id_flang_classic)
644661
flags = "-module "//path
645662

646-
case(id_flang_new, id_f18)
663+
case(id_flang, id_f18)
647664
flags = "-module-dir "//path
648665

649666
case(id_intel_classic_nix, id_intel_classic_mac, &
@@ -674,7 +691,7 @@ function get_shared_flag(self) result(shared_flag)
674691
select case (self%id)
675692
case default
676693
shared_flag = "-shared"
677-
case (id_gcc, id_f95, id_flang, id_flang_new, id_lfortran)
694+
case (id_gcc, id_f95, id_flang_classic, id_flang, id_lfortran)
678695
shared_flag = "-shared"
679696
case (id_intel_classic_nix, id_intel_llvm_nix, id_pgi, id_nvhpc)
680697
shared_flag = "-shared"
@@ -709,6 +726,9 @@ function get_feature_flag(self, feature) result(flags)
709726
case(id_cray)
710727
flags = flag_cray_no_implicit_typing
711728

729+
case(id_flang)
730+
flags = flag_flang_new_no_implicit_typing
731+
712732
end select
713733

714734
case("implicit-typing")
@@ -740,7 +760,7 @@ function get_feature_flag(self, feature) result(flags)
740760
case(id_caf, id_gcc, id_f95)
741761
flags = flag_gnu_free_form
742762

743-
case(id_pgi, id_nvhpc, id_flang)
763+
case(id_pgi, id_nvhpc, id_flang_classic)
744764
flags = flag_pgi_free_form
745765

746766
case(id_nag)
@@ -756,14 +776,17 @@ function get_feature_flag(self, feature) result(flags)
756776
case(id_cray)
757777
flags = flag_cray_free_form
758778

779+
case(id_flang)
780+
flags = flag_flang_new_free_form
781+
759782
end select
760783

761784
case("fixed-form")
762785
select case(self%id)
763786
case(id_caf, id_gcc, id_f95)
764787
flags = flag_gnu_fixed_form
765788

766-
case(id_pgi, id_nvhpc, id_flang)
789+
case(id_pgi, id_nvhpc, id_flang_classic)
767790
flags = flag_pgi_fixed_form
768791

769792
case(id_nag)
@@ -782,6 +805,9 @@ function get_feature_flag(self, feature) result(flags)
782805
case(id_lfortran)
783806
flags = flag_lfortran_fixed_form
784807

808+
case(id_flang)
809+
flags = flag_flang_new_fixed_form
810+
785811
end select
786812

787813
case("default-form")
@@ -851,7 +877,7 @@ subroutine get_default_c_compiler(f_compiler, c_compiler)
851877
case(id_intel_llvm_nix,id_intel_llvm_windows)
852878
c_compiler = 'icx'
853879

854-
case(id_flang, id_flang_new, id_f18)
880+
case(id_flang_classic, id_flang, id_f18)
855881
c_compiler='clang'
856882

857883
case(id_ibmxl)
@@ -886,7 +912,7 @@ subroutine get_default_cxx_compiler(f_compiler, cxx_compiler)
886912
case(id_intel_llvm_nix,id_intel_llvm_windows)
887913
cxx_compiler = 'icpx'
888914

889-
case(id_flang, id_flang_new, id_f18)
915+
case(id_flang_classic, id_flang, id_f18)
890916
cxx_compiler='clang++'
891917

892918
case(id_ibmxl)
@@ -1000,7 +1026,7 @@ function match_compiler_type(compiler) result(id)
10001026
end if
10011027

10021028
if (check_compiler(compiler, "flang-new")) then
1003-
id = id_flang_new
1029+
id = id_flang
10041030
return
10051031
end if
10061032

@@ -1009,6 +1035,11 @@ function match_compiler_type(compiler) result(id)
10091035
return
10101036
end if
10111037

1038+
if (check_compiler(compiler, "flang-classic")) then
1039+
id = id_flang_classic
1040+
return
1041+
end if
1042+
10121043
if (check_compiler(compiler, "flang")) then
10131044
id = id_flang
10141045
return
@@ -1061,7 +1092,7 @@ pure elemental subroutine validate_compiler_name(compiler_name, is_valid)
10611092
case("gfortran", "ifort", "ifx", "pgfortran", &
10621093
"nvfortran", "flang", "caf", &
10631094
"f95", "lfortran", "lfc", "nagfor",&
1064-
"crayftn", "xlf90", "ftn95")
1095+
"crayftn", "xlf90", "ftn95", "all")
10651096
is_valid = .true.
10661097
case default
10671098
is_valid = .false.
@@ -1793,8 +1824,8 @@ pure function compiler_id_name(id) result(name)
17931824
case(id_pgi); name = "pgfortran"
17941825
case(id_nvhpc); name = "nvfortran"
17951826
case(id_nag); name = "nagfor"
1796-
case(id_flang); name = "flang"
1797-
case(id_flang_new); name = "flang-new"
1827+
case(id_flang_classic); name = "flang"
1828+
case(id_flang); name = "flang-new"
17981829
case(id_f18); name = "f18"
17991830
case(id_ibmxl); name = "xlf90"
18001831
case(id_cray); name = "crayftn"

0 commit comments

Comments
 (0)