Skip to content

Commit 99543ae

Browse files
committed
add custom source extension capability to preprocess
support preprocessor suffixes fix for allocatable string replace function wiht subroutine fix allocations check present use macros only if allocated
1 parent 80869ad commit 99543ae

File tree

11 files changed

+206
-40
lines changed

11 files changed

+206
-40
lines changed

ci/run_tests.sh

+4
Original file line numberDiff line numberDiff line change
@@ -150,6 +150,10 @@ pushd preprocess_cpp_deps
150150
"$fpm" build
151151
popd
152152

153+
pushd preprocess_cpp_suffix
154+
"$fpm" run
155+
popd
156+
153157
pushd preprocess_per_dependency
154158
"$fpm" run
155159
popd
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
build/*
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
program test_preprocess_suffix
2+
use preprocess_cpp
3+
#ifndef TESTMACRO
4+
stop -1
5+
#else
6+
stop 0
7+
#endif
8+
end program test_preprocess_suffix
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
name = "preprocess_cpp_suffix"
2+
version = "1"
3+
4+
[preprocess]
5+
[preprocess.cpp]
6+
macros = ["TESTMACRO", "TESTMACRO2=3", "TESTMACRO3={version}"]
7+
suffixes = ["fpp"]
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
module preprocess_cpp
2+
implicit none
3+
private
4+
5+
public :: say_hello
6+
contains
7+
subroutine say_hello
8+
print *, "Hello, preprocess_cpp!"
9+
#ifndef TESTMACRO
10+
This breaks the build.
11+
#endif
12+
13+
#if TESTMACRO2 != 3
14+
This breaks the build.
15+
#endif
16+
17+
#if TESTMACRO3 != 1
18+
This breaks the build.
19+
#endif
20+
21+
end subroutine say_hello
22+
end module preprocess_cpp

src/fpm.f90

+15-23
Original file line numberDiff line numberDiff line change
@@ -110,37 +110,23 @@ subroutine build_model(model, settings, package, error)
110110
model%packages(i)%version = package%version%s()
111111

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

115115
if (allocated(dependency%preprocess)) then
116116
do j = 1, size(dependency%preprocess)
117-
if (dependency%preprocess(j)%name == "cpp") then
118-
if (.not. has_cpp) has_cpp = .true.
119-
if (allocated(dependency%preprocess(j)%macros)) then
120-
model%packages(i)%macros = [model%packages(i)%macros, dependency%preprocess(j)%macros]
121-
end if
122-
else
123-
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
124-
' is not supported; will ignore it'
125-
end if
117+
call model%packages(i)%preprocess%add_config(dependency%preprocess(j))
126118
end do
127119
end if
128120

129121
!> Add this dependency's package-level macros
130122
if (allocated(dep%preprocess)) then
131123
do j = 1, size(dep%preprocess)
132-
if (dep%preprocess(j)%name == "cpp") then
133-
if (.not. has_cpp) has_cpp = .true.
134-
if (allocated(dep%preprocess(j)%macros)) then
135-
model%packages(i)%macros = [model%packages(i)%macros, dep%preprocess(j)%macros]
136-
end if
137-
else
138-
write(stderr, '(a)') 'Warning: Preprocessor ' // package%preprocess(i)%name // &
139-
' is not supported; will ignore it'
140-
end if
124+
call model%packages(i)%preprocess%add_config(dep%preprocess(j))
141125
end do
142126
end if
143127

128+
if (model%packages(i)%preprocess%is_cpp()) has_cpp = .true.
129+
144130
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
145131

146132
if (allocated(dependency%library)) then
@@ -149,7 +135,7 @@ subroutine build_model(model, settings, package, error)
149135
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
150136
if (is_dir(lib_dir)) then
151137
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
152-
error=error)
138+
with_f_ext=model%packages(i)%preprocess%suffixes, error=error)
153139
if (allocated(error)) exit
154140
end if
155141
end if
@@ -187,7 +173,8 @@ subroutine build_model(model, settings, package, error)
187173
! Add sources from executable directories
188174
if (is_dir('app') .and. package%build%auto_executables) then
189175
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
190-
with_executables=.true., error=error)
176+
with_executables=.true., with_f_ext=model%packages(1)%preprocess%suffixes,&
177+
error=error)
191178

192179
if (allocated(error)) then
193180
return
@@ -196,7 +183,8 @@ subroutine build_model(model, settings, package, error)
196183
end if
197184
if (is_dir('example') .and. package%build%auto_examples) then
198185
call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, &
199-
with_executables=.true., error=error)
186+
with_executables=.true., &
187+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
200188

201189
if (allocated(error)) then
202190
return
@@ -205,7 +193,8 @@ subroutine build_model(model, settings, package, error)
205193
end if
206194
if (is_dir('test') .and. package%build%auto_tests) then
207195
call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, &
208-
with_executables=.true., error=error)
196+
with_executables=.true., &
197+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
209198

210199
if (allocated(error)) then
211200
return
@@ -215,6 +204,7 @@ subroutine build_model(model, settings, package, error)
215204
if (allocated(package%executable)) then
216205
call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, &
217206
auto_discover=package%build%auto_executables, &
207+
with_f_ext=model%packages(1)%preprocess%suffixes, &
218208
error=error)
219209

220210
if (allocated(error)) then
@@ -225,6 +215,7 @@ subroutine build_model(model, settings, package, error)
225215
if (allocated(package%example)) then
226216
call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, &
227217
auto_discover=package%build%auto_examples, &
218+
with_f_ext=model%packages(1)%preprocess%suffixes, &
228219
error=error)
229220

230221
if (allocated(error)) then
@@ -235,6 +226,7 @@ subroutine build_model(model, settings, package, error)
235226
if (allocated(package%test)) then
236227
call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, &
237228
auto_discover=package%build%auto_tests, &
229+
with_f_ext=model%packages(1)%preprocess%suffixes, &
238230
error=error)
239231

240232
if (allocated(error)) then

src/fpm/manifest/preprocess.f90

+74
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module fpm_manifest_preprocess
1414
use fpm_error, only : error_t, syntax_error
1515
use fpm_strings, only : string_t
1616
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
17+
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
1718
implicit none
1819
private
1920

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

43+
!> Operations
44+
procedure :: destroy
45+
procedure :: add_config
46+
47+
!> Properties
48+
procedure :: is_cpp
49+
procedure :: is_fypp
50+
4251
end type preprocess_config_t
4352

4453
interface operator(==)
@@ -228,4 +237,69 @@ logical function preprocess_is_same(this,that)
228237

229238
end function preprocess_is_same
230239

240+
!> Clean preprocessor structure
241+
elemental subroutine destroy(this)
242+
class(preprocess_config_t), intent(inout) :: this
243+
244+
if (allocated(this%name))deallocate(this%name)
245+
if (allocated(this%suffixes))deallocate(this%suffixes)
246+
if (allocated(this%directories))deallocate(this%directories)
247+
if (allocated(this%macros))deallocate(this%macros)
248+
249+
end subroutine destroy
250+
251+
!> Add preprocessor settings
252+
subroutine add_config(this,that)
253+
class(preprocess_config_t), intent(inout) :: this
254+
type(preprocess_config_t), intent(in) :: that
255+
256+
if (.not.that%name=="cpp") then
257+
write(stderr, '(a)') 'Warning: Preprocessor ' // that%name // &
258+
' is not supported; will ignore it'
259+
return
260+
end if
261+
262+
if (.not.allocated(this%name)) this%name = that%name
263+
264+
! Add macros
265+
if (allocated(that%macros)) then
266+
if (allocated(this%macros)) then
267+
this%macros = [this%macros, that%macros]
268+
else
269+
allocate(this%macros, source = that%macros)
270+
end if
271+
endif
272+
273+
! Add suffixes
274+
if (allocated(that%suffixes)) then
275+
if (allocated(this%suffixes)) then
276+
this%suffixes = [this%suffixes, that%suffixes]
277+
else
278+
allocate(this%suffixes, source = that%suffixes)
279+
end if
280+
endif
281+
282+
! Add directories
283+
if (allocated(that%directories)) then
284+
if (allocated(this%directories)) then
285+
this%directories = [this%directories, that%directories]
286+
else
287+
allocate(this%directories, source = that%directories)
288+
end if
289+
endif
290+
291+
end subroutine add_config
292+
293+
! Check cpp
294+
logical function is_cpp(this)
295+
class(preprocess_config_t), intent(in) :: this
296+
is_cpp = this%name == "cpp"
297+
end function is_cpp
298+
299+
! Check cpp
300+
logical function is_fypp(this)
301+
class(preprocess_config_t), intent(in) :: this
302+
is_fypp = this%name == "fypp"
303+
end function is_fypp
304+
231305
end module fpm_manifest_preprocess

src/fpm_model.f90

+2-1
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ module fpm_model
3939
use fpm_compiler, only: compiler_t, archiver_t, debug
4040
use fpm_dependency, only: dependency_tree_t
4141
use fpm_strings, only: string_t, str, len_trim
42+
use fpm_manifest_preprocess, only: preprocess_config_t
4243
implicit none
4344

4445
private
@@ -137,7 +138,7 @@ module fpm_model
137138
type(srcfile_t), allocatable :: sources(:)
138139

139140
!> List of macros.
140-
type(string_t), allocatable :: macros(:)
141+
type(preprocess_config_t) :: preprocess
141142

142143
!> Package version number.
143144
character(:), allocatable :: version

0 commit comments

Comments
 (0)