Skip to content

Commit

Permalink
Support of additional suffixes of Fortran files for preprocessing #982
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz authored Jan 21, 2024
2 parents 70b1a48 + e3e32cd commit 31ea224
Show file tree
Hide file tree
Showing 11 changed files with 208 additions and 40 deletions.
4 changes: 4 additions & 0 deletions ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,10 @@ pushd preprocess_cpp_deps
"$fpm" build
popd

pushd preprocess_cpp_suffix
"$fpm" run
popd

pushd preprocess_per_dependency
"$fpm" run
popd
Expand Down
1 change: 1 addition & 0 deletions example_packages/preprocess_cpp_suffix/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
build/*
8 changes: 8 additions & 0 deletions example_packages/preprocess_cpp_suffix/app/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
program test_preprocess_suffix
use preprocess_cpp
#ifndef TESTMACRO
stop -1
#else
stop 0
#endif
end program test_preprocess_suffix
7 changes: 7 additions & 0 deletions example_packages/preprocess_cpp_suffix/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
name = "preprocess_cpp_suffix"
version = "1"

[preprocess]
[preprocess.cpp]
macros = ["TESTMACRO", "TESTMACRO2=3", "TESTMACRO3={version}"]
suffixes = ["fpp"]
22 changes: 22 additions & 0 deletions example_packages/preprocess_cpp_suffix/src/preprocess_cpp.fpp
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
module preprocess_cpp
implicit none
private

public :: say_hello
contains
subroutine say_hello
print *, "Hello, preprocess_cpp!"
#ifndef TESTMACRO
This breaks the build.
#endif

#if TESTMACRO2 != 3
This breaks the build.
#endif

#if TESTMACRO3 != 1
This breaks the build.
#endif

end subroutine say_hello
end module preprocess_cpp
38 changes: 15 additions & 23 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -110,37 +110,23 @@ subroutine build_model(model, settings, package, error)
model%packages(i)%version = package%version%s()

!> Add this dependency's manifest macros
allocate(model%packages(i)%macros(0))
call model%packages(i)%preprocess%destroy()

if (allocated(dependency%preprocess)) then
do j = 1, size(dependency%preprocess)
if (dependency%preprocess(j)%name == "cpp") then
if (.not. has_cpp) has_cpp = .true.
if (allocated(dependency%preprocess(j)%macros)) then
model%packages(i)%macros = [model%packages(i)%macros, dependency%preprocess(j)%macros]
end if
else
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
' is not supported; will ignore it'
end if
call model%packages(i)%preprocess%add_config(dependency%preprocess(j))
end do
end if

!> Add this dependency's package-level macros
if (allocated(dep%preprocess)) then
do j = 1, size(dep%preprocess)
if (dep%preprocess(j)%name == "cpp") then
if (.not. has_cpp) has_cpp = .true.
if (allocated(dep%preprocess(j)%macros)) then
model%packages(i)%macros = [model%packages(i)%macros, dep%preprocess(j)%macros]
end if
else
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
' is not supported; will ignore it'
end if
call model%packages(i)%preprocess%add_config(dep%preprocess(j))
end do
end if

if (model%packages(i)%preprocess%is_cpp()) has_cpp = .true.

if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))

if (allocated(dependency%library)) then
Expand All @@ -149,7 +135,7 @@ subroutine build_model(model, settings, package, error)
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
if (is_dir(lib_dir)) then
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
error=error)
with_f_ext=model%packages(i)%preprocess%suffixes, error=error)
if (allocated(error)) exit
end if
end if
Expand Down Expand Up @@ -187,7 +173,8 @@ subroutine build_model(model, settings, package, error)
! Add sources from executable directories
if (is_dir('app') .and. package%build%auto_executables) then
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
with_executables=.true., error=error)
with_executables=.true., with_f_ext=model%packages(1)%preprocess%suffixes,&
error=error)

if (allocated(error)) then
return
Expand All @@ -196,7 +183,8 @@ subroutine build_model(model, settings, package, error)
end if
if (is_dir('example') .and. package%build%auto_examples) then
call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, &
with_executables=.true., error=error)
with_executables=.true., &
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)

if (allocated(error)) then
return
Expand All @@ -205,7 +193,8 @@ subroutine build_model(model, settings, package, error)
end if
if (is_dir('test') .and. package%build%auto_tests) then
call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, &
with_executables=.true., error=error)
with_executables=.true., &
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)

if (allocated(error)) then
return
Expand All @@ -215,6 +204,7 @@ subroutine build_model(model, settings, package, error)
if (allocated(package%executable)) then
call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, &
auto_discover=package%build%auto_executables, &
with_f_ext=model%packages(1)%preprocess%suffixes, &
error=error)

if (allocated(error)) then
Expand All @@ -225,6 +215,7 @@ subroutine build_model(model, settings, package, error)
if (allocated(package%example)) then
call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, &
auto_discover=package%build%auto_examples, &
with_f_ext=model%packages(1)%preprocess%suffixes, &
error=error)

if (allocated(error)) then
Expand All @@ -235,6 +226,7 @@ subroutine build_model(model, settings, package, error)
if (allocated(package%test)) then
call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, &
auto_discover=package%build%auto_tests, &
with_f_ext=model%packages(1)%preprocess%suffixes, &
error=error)

if (allocated(error)) then
Expand Down
76 changes: 76 additions & 0 deletions src/fpm/manifest/preprocess.f90
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module fpm_manifest_preprocess
use fpm_error, only : error_t, syntax_error
use fpm_strings, only : string_t
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
implicit none
private

Expand All @@ -39,6 +40,14 @@ module fpm_manifest_preprocess
!> Print information on this instance
procedure :: info

!> Operations
procedure :: destroy
procedure :: add_config

!> Properties
procedure :: is_cpp
procedure :: is_fypp

end type preprocess_config_t

interface operator(==)
Expand Down Expand Up @@ -228,4 +237,71 @@ logical function preprocess_is_same(this,that)

end function preprocess_is_same

!> Clean preprocessor structure
elemental subroutine destroy(this)
class(preprocess_config_t), intent(inout) :: this

if (allocated(this%name))deallocate(this%name)
if (allocated(this%suffixes))deallocate(this%suffixes)
if (allocated(this%directories))deallocate(this%directories)
if (allocated(this%macros))deallocate(this%macros)

end subroutine destroy

!> Add preprocessor settings
subroutine add_config(this,that)
class(preprocess_config_t), intent(inout) :: this
type(preprocess_config_t), intent(in) :: that

if (.not.that%is_cpp()) then
write(stderr, '(a)') 'Warning: Preprocessor ' // that%name // &
' is not supported; will ignore it'
return
end if

if (.not.allocated(this%name)) this%name = that%name

! Add macros
if (allocated(that%macros)) then
if (allocated(this%macros)) then
this%macros = [this%macros, that%macros]
else
allocate(this%macros, source = that%macros)
end if
endif

! Add suffixes
if (allocated(that%suffixes)) then
if (allocated(this%suffixes)) then
this%suffixes = [this%suffixes, that%suffixes]
else
allocate(this%suffixes, source = that%suffixes)
end if
endif

! Add directories
if (allocated(that%directories)) then
if (allocated(this%directories)) then
this%directories = [this%directories, that%directories]
else
allocate(this%directories, source = that%directories)
end if
endif

end subroutine add_config

! Check cpp
logical function is_cpp(this)
class(preprocess_config_t), intent(in) :: this
is_cpp = .false.
if (allocated(this%name)) is_cpp = this%name == "cpp"
end function is_cpp

! Check cpp
logical function is_fypp(this)
class(preprocess_config_t), intent(in) :: this
is_fypp = .false.
if (allocated(this%name)) is_fypp = this%name == "fypp"
end function is_fypp

end module fpm_manifest_preprocess
3 changes: 2 additions & 1 deletion src/fpm_model.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module fpm_model
use fpm_compiler, only: compiler_t, archiver_t, debug
use fpm_dependency, only: dependency_tree_t
use fpm_strings, only: string_t, str, len_trim
use fpm_manifest_preprocess, only: preprocess_config_t
implicit none

private
Expand Down Expand Up @@ -137,7 +138,7 @@ module fpm_model
type(srcfile_t), allocatable :: sources(:)

!> List of macros.
type(string_t), allocatable :: macros(:)
type(preprocess_config_t) :: preprocess

!> Package version number.
character(:), allocatable :: version
Expand Down
Loading

0 comments on commit 31ea224

Please sign in to comment.