Skip to content

Commit 1c60d12

Browse files
authored
Enable cpp preprocessor flag for dependencies (#783)
Enable cpp preprocessor flag for dependencies, fix #782.
2 parents 1c211f6 + 358bdd3 commit 1c60d12

File tree

8 files changed

+50
-27
lines changed

8 files changed

+50
-27
lines changed

ci/run_tests.sh

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -142,6 +142,10 @@ pushd preprocess_cpp_c
142142
"$fpm" run
143143
popd
144144

145+
pushd preprocess_cpp_deps
146+
"$fpm" build
147+
popd
148+
145149
pushd preprocess_hello
146150
"$fpm" build
147151
popd

example_packages/README.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@ the features demonstrated in each package and which versions of fpm are supporte
2727
| makefile_complex | External build command (makefile); local path dependency | Y | N |
2828
| preprocess_cpp | Lib only; C preprocessing; Macro parsing | N | Y |
2929
| preprocess_cpp_c | C App; progate macros from fpm.toml to app | N | Y |
30+
| preprocess_cpp_deps | App; cpp preprocessor settings in local path dependency only | N | Y |
3031
| preprocess_hello | App only; Macros remain local to the package | N | Y |
3132
| preprocess_hello_dependency | Lib only; Macros not getting passed here from root | N | Y |
3233
| program_with_module | App-only; module+program in single source file | Y | Y |
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
program hello_fpm
2+
use utils, only: say_hello
3+
4+
call say_hello()
5+
6+
end program hello_fpm
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
name = "utils"
2+
3+
[preprocess]
4+
[preprocess.cpp]
5+
macros = ["X=1"]
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
module utils
2+
3+
implicit none
4+
5+
contains
6+
7+
subroutine say_hello()
8+
print '(a,1x,i0)', "Hello, X =", X
9+
end subroutine say_hello
10+
11+
end module utils
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
name = "preprocess_cpp_deps"
2+
3+
[dependencies]
4+
utils = { path = "crate/utils" }

src/fpm.f90

Lines changed: 16 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ 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_preprocessor_flags
15+
use fpm_compiler, only: new_compiler, new_archiver, set_cpp_preprocessor_flags
1616

1717

1818
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -45,6 +45,7 @@ subroutine build_model(model, settings, package, error)
4545
type(package_config_t) :: dependency
4646
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, cxxflags, ldflags
4747
character(len=:), allocatable :: version
48+
logical :: has_cpp
4849

4950
logical :: duplicates_found = .false.
5051
type(string_t) :: include_dir
@@ -79,8 +80,6 @@ subroutine build_model(model, settings, package, error)
7980
end select
8081
end if
8182

82-
call set_preprocessor_flags(model%compiler%id, flags, package)
83-
8483
cflags = trim(settings%cflag)
8584
cxxflags = trim(settings%cxxflag)
8685
ldflags = trim(settings%ldflag)
@@ -92,15 +91,11 @@ subroutine build_model(model, settings, package, error)
9291
end if
9392
model%build_prefix = join_path("build", basename(model%compiler%fc))
9493

95-
model%fortran_compile_flags = flags
96-
model%c_compile_flags = cflags
97-
model%cxx_compile_flags = cxxflags
98-
model%link_flags = ldflags
99-
10094
model%include_tests = settings%build_tests
10195

10296
allocate(model%packages(model%deps%ndep))
10397

98+
has_cpp = .false.
10499
do i = 1, model%deps%ndep
105100
associate(dep => model%deps%dep(i))
106101
manifest = join_path(dep%proj_dir, "fpm.toml")
@@ -115,8 +110,14 @@ subroutine build_model(model, settings, package, error)
115110

116111
if (allocated(dependency%preprocess)) then
117112
do j = 1, size(dependency%preprocess)
118-
if (package%preprocess(j)%name == "cpp" .and. allocated(dependency%preprocess(j)%macros)) then
113+
if (dependency%preprocess(j)%name == "cpp") then
114+
if (.not. has_cpp) has_cpp = .true.
115+
if (allocated(dependency%preprocess(j)%macros)) then
119116
model%packages(i)%macros = dependency%preprocess(j)%macros
117+
end if
118+
else
119+
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
120+
' is not supported; will ignore it'
120121
end if
121122
end do
122123
end if
@@ -156,6 +157,12 @@ subroutine build_model(model, settings, package, error)
156157
end do
157158
if (allocated(error)) return
158159

160+
if (has_cpp) call set_cpp_preprocessor_flags(model%compiler%id, flags)
161+
model%fortran_compile_flags = flags
162+
model%c_compile_flags = cflags
163+
model%cxx_compile_flags = cxxflags
164+
model%link_flags = ldflags
165+
159166
! Add sources from executable directories
160167
if (is_dir('app') .and. package%build%auto_executables) then
161168
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &

src/fpm_compiler.f90

Lines changed: 3 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -394,18 +394,10 @@ subroutine get_debug_compile_flags(id, flags)
394394
end select
395395
end subroutine get_debug_compile_flags
396396

397-
subroutine set_preprocessor_flags (id, flags, package)
397+
pure subroutine set_cpp_preprocessor_flags(id, flags)
398398
integer(compiler_enum), intent(in) :: id
399399
character(len=:), allocatable, intent(inout) :: flags
400-
type(package_config_t), intent(in) :: package
401400
character(len=:), allocatable :: flag_cpp_preprocessor
402-
403-
integer :: i
404-
405-
!> Check if there is a preprocess table
406-
if (.not.allocated(package%preprocess)) then
407-
return
408-
end if
409401

410402
!> Modify the flag_cpp_preprocessor on the basis of the compiler.
411403
select case(id)
@@ -421,16 +413,9 @@ subroutine set_preprocessor_flags (id, flags, package)
421413
flag_cpp_preprocessor = "--cpp"
422414
end select
423415

424-
do i = 1, size(package%preprocess)
425-
if (package%preprocess(i)%name == "cpp") then
426-
flags = flag_cpp_preprocessor// flags
427-
exit
428-
else
429-
write(stderr, '(a)') 'Warning: preprocessor ' // package%preprocess(i)%name // ' is not supported; will ignore it'
430-
end if
431-
end do
416+
flags = flag_cpp_preprocessor// flags
432417

433-
end subroutine set_preprocessor_flags
418+
end subroutine set_cpp_preprocessor_flags
434419

435420
!> This function will parse and read the macros list and
436421
!> return them as defined flags.

0 commit comments

Comments
 (0)