Skip to content

Commit 0e598bd

Browse files
committed
pass preprocessor config to source parsing
1 parent 3970511 commit 0e598bd

File tree

2 files changed

+26
-15
lines changed

2 files changed

+26
-15
lines changed

src/fpm.f90

Lines changed: 10 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -147,7 +147,8 @@ subroutine build_model(model, settings, package, error)
147147
lib_dir = join_path(dep%proj_dir, manifest%library%source_dir)
148148
if (is_dir(lib_dir)) then
149149
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
150-
with_f_ext=model%packages(i)%preprocess%suffixes, error=error)
150+
with_f_ext=model%packages(i)%preprocess%suffixes, error=error, &
151+
preprocess=model%packages(i)%preprocess)
151152
if (allocated(error)) exit
152153
end if
153154
end if
@@ -186,7 +187,7 @@ subroutine build_model(model, settings, package, error)
186187
if (is_dir('app') .and. package%build%auto_executables) then
187188
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
188189
with_executables=.true., with_f_ext=model%packages(1)%preprocess%suffixes,&
189-
error=error)
190+
error=error,preprocess=model%packages(1)%preprocess)
190191

191192
if (allocated(error)) then
192193
return
@@ -196,7 +197,8 @@ subroutine build_model(model, settings, package, error)
196197
if (is_dir('example') .and. package%build%auto_examples) then
197198
call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, &
198199
with_executables=.true., &
199-
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
200+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
201+
preprocess=model%packages(1)%preprocess)
200202

201203
if (allocated(error)) then
202204
return
@@ -206,7 +208,8 @@ subroutine build_model(model, settings, package, error)
206208
if (is_dir('test') .and. package%build%auto_tests) then
207209
call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, &
208210
with_executables=.true., &
209-
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
211+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
212+
preprocess=model%packages(1)%preprocess)
210213

211214
if (allocated(error)) then
212215
return
@@ -217,7 +220,7 @@ subroutine build_model(model, settings, package, error)
217220
call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, &
218221
auto_discover=package%build%auto_executables, &
219222
with_f_ext=model%packages(1)%preprocess%suffixes, &
220-
error=error)
223+
error=error,preprocess=model%packages(1)%preprocess)
221224

222225
if (allocated(error)) then
223226
return
@@ -228,7 +231,7 @@ subroutine build_model(model, settings, package, error)
228231
call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, &
229232
auto_discover=package%build%auto_examples, &
230233
with_f_ext=model%packages(1)%preprocess%suffixes, &
231-
error=error)
234+
error=error,preprocess=model%packages(1)%preprocess)
232235

233236
if (allocated(error)) then
234237
return
@@ -239,7 +242,7 @@ subroutine build_model(model, settings, package, error)
239242
call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, &
240243
auto_discover=package%build%auto_tests, &
241244
with_f_ext=model%packages(1)%preprocess%suffixes, &
242-
error=error)
245+
error=error,preprocess=model%packages(1)%preprocess)
243246

244247
if (allocated(error)) then
245248
return

src/fpm_sources.f90

Lines changed: 16 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module fpm_sources
1111
use fpm_strings, only: lower, str_ends_with, string_t, operator(.in.)
1212
use fpm_source_parsing, only: parse_f_source, parse_c_source
1313
use fpm_manifest_executable, only: executable_config_t
14+
use fpm_manifest_preprocess, only: preprocess_config_t
1415
implicit none
1516

1617
private
@@ -25,18 +26,19 @@ module fpm_sources
2526

2627
!> Wrapper to source parsing routines.
2728
!> Selects parsing routine based on source file name extension
28-
function parse_source(source_file_path,custom_f_ext,error) result(source)
29+
type(srcfile_t) function parse_source(source_file_path,custom_f_ext,error,preprocess) result(source)
2930
character(*), intent(in) :: source_file_path
3031
type(string_t), optional, intent(in) :: custom_f_ext(:)
3132
type(error_t), allocatable, intent(out) :: error
32-
type(srcfile_t) :: source
33+
type(preprocess_config_t), optional, intent(in) :: preprocess
34+
3335
type(string_t), allocatable :: f_ext(:)
3436

3537
call list_fortran_suffixes(f_ext,custom_f_ext)
3638

3739
if (str_ends_with(lower(source_file_path), f_ext)) then
3840

39-
source = parse_f_source(source_file_path, error)
41+
source = parse_f_source(source_file_path, error, preprocess)
4042

4143
if (source%unit_type == FPM_UNIT_PROGRAM) then
4244
source%exe_name = basename(source_file_path,suffix=.false.)
@@ -78,7 +80,8 @@ subroutine list_fortran_suffixes(suffixes,with_f_ext)
7880
end subroutine list_fortran_suffixes
7981

8082
!> Add to `sources` by looking for source files in `directory`
81-
subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_ext,recurse,error)
83+
subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_ext,recurse,error,&
84+
preprocess)
8285
!> List of `[[srcfile_t]]` objects to append to. Allocated if not allocated
8386
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
8487
!> Directory in which to search for source files
@@ -93,6 +96,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_
9396
logical, intent(in), optional :: recurse
9497
!> Error handling
9598
type(error_t), allocatable, intent(out) :: error
99+
!> Optional source preprocessor configuration
100+
type(preprocess_config_t), optional, intent(in) :: preprocess
96101

97102
integer :: i
98103
logical, allocatable :: is_source(:), exclude_source(:)
@@ -132,7 +137,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_
132137

133138
do i = 1, size(src_file_names)
134139

135-
dir_sources(i) = parse_source(src_file_names(i)%s,with_f_ext,error)
140+
dir_sources(i) = parse_source(src_file_names(i)%s,with_f_ext,error,preprocess)
136141
if (allocated(error)) return
137142

138143
dir_sources(i)%unit_scope = scope
@@ -163,7 +168,7 @@ end subroutine add_sources_from_dir
163168
!> Add to `sources` using the executable and test entries in the manifest and
164169
!> applies any executable-specific overrides such as `executable%name`.
165170
!> Adds all sources (including modules) from each `executable%source_dir`
166-
subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f_ext,error)
171+
subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f_ext,error,preprocess)
167172
!> List of `[[srcfile_t]]` objects to append to. Allocated if not allocated
168173
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
169174
!> List of `[[executable_config_t]]` entries from manifest
@@ -176,6 +181,8 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f
176181
type(string_t), intent(in), optional :: with_f_ext(:)
177182
!> Error handling
178183
type(error_t), allocatable, intent(out) :: error
184+
!> Optional source preprocessor configuration
185+
type(preprocess_config_t), optional, intent(in) :: preprocess
179186

180187
integer :: i, j
181188

@@ -186,7 +193,8 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f
186193

187194
do i=1,size(exe_dirs)
188195
call add_sources_from_dir(sources,exe_dirs(i)%s, scope, &
189-
with_executables=auto_discover, with_f_ext=with_f_ext,recurse=.false., error=error)
196+
with_executables=auto_discover, with_f_ext=with_f_ext,recurse=.false., &
197+
error=error, preprocess=preprocess)
190198

191199
if (allocated(error)) then
192200
return
@@ -217,7 +225,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f
217225

218226
! Add if not already discovered (auto_discovery off)
219227
associate(exe => executables(i))
220-
exe_source = parse_source(join_path(exe%source_dir,exe%main),with_f_ext,error)
228+
exe_source = parse_source(join_path(exe%source_dir,exe%main),with_f_ext,error,preprocess)
221229
exe_source%exe_name = exe%name
222230
if (allocated(exe%link)) then
223231
exe_source%link_libraries = exe%link

0 commit comments

Comments
 (0)