@@ -11,6 +11,7 @@ module fpm_sources
11
11
use fpm_strings, only: lower, str_ends_with, string_t, operator (.in .)
12
12
use fpm_source_parsing, only: parse_f_source, parse_c_source
13
13
use fpm_manifest_executable, only: executable_config_t
14
+ use fpm_manifest_preprocess, only: preprocess_config_t
14
15
implicit none
15
16
16
17
private
@@ -25,18 +26,19 @@ module fpm_sources
25
26
26
27
! > Wrapper to source parsing routines.
27
28
! > 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)
29
30
character (* ), intent (in ) :: source_file_path
30
31
type (string_t), optional , intent (in ) :: custom_f_ext(:)
31
32
type (error_t), allocatable , intent (out ) :: error
32
- type (srcfile_t) :: source
33
+ type (preprocess_config_t), optional , intent (in ) :: preprocess
34
+
33
35
type (string_t), allocatable :: f_ext(:)
34
36
35
37
call list_fortran_suffixes(f_ext,custom_f_ext)
36
38
37
39
if (str_ends_with(lower(source_file_path), f_ext)) then
38
40
39
- source = parse_f_source(source_file_path, error)
41
+ source = parse_f_source(source_file_path, error, preprocess )
40
42
41
43
if (source% unit_type == FPM_UNIT_PROGRAM) then
42
44
source% exe_name = basename(source_file_path,suffix= .false. )
@@ -78,7 +80,8 @@ subroutine list_fortran_suffixes(suffixes,with_f_ext)
78
80
end subroutine list_fortran_suffixes
79
81
80
82
! > 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 )
82
85
! > List of `[[srcfile_t]]` objects to append to. Allocated if not allocated
83
86
type (srcfile_t), allocatable , intent (inout ), target :: sources(:)
84
87
! > Directory in which to search for source files
@@ -93,6 +96,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_
93
96
logical , intent (in ), optional :: recurse
94
97
! > Error handling
95
98
type (error_t), allocatable , intent (out ) :: error
99
+ ! > Optional source preprocessor configuration
100
+ type (preprocess_config_t), optional , intent (in ) :: preprocess
96
101
97
102
integer :: i
98
103
logical , allocatable :: is_source(:), exclude_source(:)
@@ -132,7 +137,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_
132
137
133
138
do i = 1 , size (src_file_names)
134
139
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 )
136
141
if (allocated (error)) return
137
142
138
143
dir_sources(i)% unit_scope = scope
@@ -163,7 +168,7 @@ end subroutine add_sources_from_dir
163
168
! > Add to `sources` using the executable and test entries in the manifest and
164
169
! > applies any executable-specific overrides such as `executable%name`.
165
170
! > 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 )
167
172
! > List of `[[srcfile_t]]` objects to append to. Allocated if not allocated
168
173
type (srcfile_t), allocatable , intent (inout ), target :: sources(:)
169
174
! > List of `[[executable_config_t]]` entries from manifest
@@ -176,6 +181,8 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f
176
181
type (string_t), intent (in ), optional :: with_f_ext(:)
177
182
! > Error handling
178
183
type (error_t), allocatable , intent (out ) :: error
184
+ ! > Optional source preprocessor configuration
185
+ type (preprocess_config_t), optional , intent (in ) :: preprocess
179
186
180
187
integer :: i, j
181
188
@@ -186,7 +193,8 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f
186
193
187
194
do i= 1 ,size (exe_dirs)
188
195
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)
190
198
191
199
if (allocated (error)) then
192
200
return
@@ -217,7 +225,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f
217
225
218
226
! Add if not already discovered (auto_discovery off)
219
227
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 )
221
229
exe_source% exe_name = exe% name
222
230
if (allocated (exe% link)) then
223
231
exe_source% link_libraries = exe% link
0 commit comments