@@ -30,52 +30,128 @@ module fpm_source_parsing
30
30
private
31
31
public :: parse_f_source, parse_c_source, parse_use_statement
32
32
33
+ type :: cpp_block
34
+ ! Nested block total depth
35
+ integer :: depth = 0
36
+ ! Whether currently inside an inactive conditional block
37
+ logical :: inside_inactive_block = .false.
38
+ ! Depth at which we became inactive (0 if active)
39
+ integer :: inactive_depth = 0
40
+ ! Current macro
41
+ character (:), allocatable :: name
42
+ end type cpp_block
43
+
33
44
contains
34
45
46
+ ! > Case-insensitive check if macro_name is in the macros list
47
+ logical function macro_in_list_ci (macro_name , macros )
48
+ character (* ), intent (in ) :: macro_name
49
+ type (string_t), intent (in ) :: macros(:)
50
+ integer :: i
51
+
52
+ macro_in_list_ci = .false.
53
+ do i = 1 , size (macros)
54
+ if (lower(trim (macro_name)) == lower(trim (macros(i)% s))) then
55
+ macro_in_list_ci = .true.
56
+ return
57
+ end if
58
+ end do
59
+ end function macro_in_list_ci
60
+
35
61
! > Start a CPP conditional block (active or inactive)
36
- pure subroutine start_cpp_block (conditional_depth , inside_conditional_block , is_active )
37
- integer , intent (inout ) :: conditional_depth
38
- logical , intent (inout ) :: inside_conditional_block
39
- logical , intent (in ) :: is_active
62
+ subroutine start_cpp_block (blk , line , preprocess )
63
+ type (cpp_block) , intent (inout ) :: blk
64
+ character ( * ) , intent (in ) :: line
65
+ type (preprocess_config_t), optional , intent (in ) :: preprocess
40
66
41
- conditional_depth = conditional_depth + 1
42
- if (conditional_depth == 1 ) then
43
- inside_conditional_block = .not. is_active
44
- end if
67
+ logical :: is_active
68
+ character (:), allocatable :: macro_name
69
+
70
+ call parse_cpp_condition(line, preprocess, is_active, macro_name)
71
+
72
+ blk% depth = blk% depth + 1
73
+
74
+ ! If we're not already in an inactive block, check this condition
75
+ enter_inactive: if (.not. blk% inside_inactive_block) then
76
+ blk% name = macro_name
77
+ if (.not. is_active) then
78
+ ! This condition is false, so we enter an inactive block
79
+ blk% inside_inactive_block = .true.
80
+ blk% inactive_depth = blk% depth
81
+ end if
82
+ end if enter_inactive
83
+
84
+ ! If we're already in an inactive block, stay inactive regardless of this condition
85
+
45
86
end subroutine start_cpp_block
46
87
47
88
! > End a CPP conditional block
48
- pure subroutine end_cpp_block (conditional_depth , inside_conditional_block )
49
- integer , intent (inout ) :: conditional_depth
50
- logical , intent (inout ) :: inside_conditional_block
89
+ subroutine end_cpp_block (blk )
90
+ type (cpp_block), intent (inout ) :: blk
51
91
52
- conditional_depth = max (0 , conditional_depth - 1 )
53
- if (conditional_depth == 0 ) then
54
- inside_conditional_block = .false.
92
+ ! If we're ending the block where we became inactive, reactivate
93
+ if (blk% inside_inactive_block .and. blk% depth == blk% inactive_depth) then
94
+ blk% inside_inactive_block = .false.
95
+ blk% inactive_depth = 0
55
96
end if
97
+
98
+ blk% depth = max (0 , blk% depth - 1 )
99
+
56
100
end subroutine end_cpp_block
57
101
102
+ ! > Handle #else directive by flipping the current condition
103
+ subroutine handle_else_block (blk )
104
+ type (cpp_block), intent (inout ) :: blk
105
+
106
+ ! #else only matters if we're at the same level where we became inactive
107
+ if (blk% inside_inactive_block .and. blk% depth == blk% inactive_depth) then
108
+ ! We're in an inactive block at this level, #else makes it active
109
+ blk% inside_inactive_block = .false.
110
+ blk% inactive_depth = 0
111
+ elseif (.not. blk% inside_inactive_block .and. blk% depth > 0 ) then
112
+ ! We're in an active block at this level, #else makes it inactive
113
+ blk% inside_inactive_block = .true.
114
+ blk% inactive_depth = blk% depth
115
+ end if
116
+
117
+ end subroutine handle_else_block
118
+
58
119
! > Parse CPP conditional directive and determine if block should be active
59
- function parse_cpp_condition (line , macros ) result( is_active)
120
+ subroutine parse_cpp_condition (line , preprocess , is_active , macro_name )
60
121
character (* ), intent (in ) :: line
61
- type (string_t ), intent (in ) :: macros(:)
62
- logical :: is_active
63
- character (:), allocatable :: macro_name
122
+ type (preprocess_config_t ), optional , intent (in ) :: preprocess
123
+ character (:), allocatable , intent ( out ) :: macro_name
124
+ logical , intent ( out ) :: is_active
64
125
integer :: start_pos, end_pos
65
126
127
+ ! Always active if CPP preprocessor is not active
128
+ if (.not. present (preprocess)) then
129
+ is_active = .true.
130
+ macro_name = " "
131
+ return
132
+ endif
133
+
134
+ ! If CPP is not enabled, always active
135
+ if (.not. preprocess% is_cpp()) then
136
+ is_active = .true.
137
+ macro_name = " "
138
+ return
139
+ endif
140
+
66
141
is_active = .false.
67
142
143
+ ! There are macros: test if active
68
144
if (index (line, ' #ifdef' ) == 1 ) then
69
145
! #ifdef MACRO
70
146
start_pos = index (line, ' ' ) + 1
71
147
macro_name = trim (adjustl (line(start_pos:)))
72
- is_active = macro_name . in . macros
148
+ is_active = macro_in_list_ci( macro_name, preprocess % macros)
73
149
74
150
elseif (index (line, ' #ifndef' ) == 1 ) then
75
151
! #ifndef MACRO
76
152
start_pos = index (line, ' ' ) + 1
77
153
macro_name = trim (adjustl (line(start_pos:)))
78
- is_active = .not. (macro_name . in . macros)
154
+ is_active = .not. macro_in_list_ci (macro_name, preprocess % macros)
79
155
80
156
elseif (index (line, ' #if ' ) == 1 ) then
81
157
! Handle various #if patterns
@@ -86,21 +162,21 @@ function parse_cpp_condition(line, macros) result(is_active)
86
162
if (end_pos > 0 ) then
87
163
macro_name = line(start_pos:start_pos + end_pos - 1 )
88
164
if (index (line, ' !defined(' ) > 0 ) then
89
- is_active = .not. (macro_name . in . macros)
165
+ is_active = .not. macro_in_list_ci (macro_name, preprocess % macros)
90
166
else
91
- is_active = macro_name . in . macros
167
+ is_active = macro_in_list_ci( macro_name, preprocess % macros)
92
168
end if
93
169
end if
94
170
else
95
171
! #if MACRO (simple macro check)
96
172
start_pos = 4 ! Skip "#if "
97
173
end_pos = len_trim (line)
98
174
macro_name = trim (adjustl (line(start_pos:end_pos)))
99
- is_active = macro_name . in . macros
175
+ is_active = macro_in_list_ci( macro_name, preprocess % macros)
100
176
end if
101
177
end if
102
178
103
- end function parse_cpp_condition
179
+ end subroutine parse_cpp_condition
104
180
105
181
! > Parsing of free-form fortran source files
106
182
! >
@@ -142,10 +218,10 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
142
218
type (srcfile_t) :: f_source
143
219
144
220
logical :: inside_module, inside_interface, using, intrinsic_module
145
- logical :: inside_conditional_block, cpp_conditional_parsing
221
+ logical :: cpp_conditional_parsing
146
222
integer :: stat
147
223
integer :: fh, n_use, n_include, n_mod, n_parent, i, j, ic, pass
148
- integer :: conditional_depth
224
+ type (cpp_block) :: cpp_blk
149
225
type (string_t), allocatable :: file_lines(:), file_lines_lower(:)
150
226
character (:), allocatable :: temp_string, mod_name, string_parts(:)
151
227
@@ -179,8 +255,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
179
255
n_parent = 0
180
256
inside_module = .false.
181
257
inside_interface = .false.
182
- inside_conditional_block = .false.
183
- conditional_depth = 0
258
+ cpp_blk = cpp_block() ! Initialize with default values
184
259
file_loop: do i= 1 ,size (file_lines_lower)
185
260
186
261
! Skip comment lines and empty lines
@@ -201,23 +276,21 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
201
276
index (file_lines_lower(i)% s,' #if ' ) == 1 ) then
202
277
203
278
! Determine if this conditional block should be active
204
- if (present (preprocess) .and. allocated (preprocess% macros)) then
205
- call start_cpp_block(conditional_depth, inside_conditional_block, &
206
- parse_cpp_condition(file_lines_lower(i)% s, preprocess% macros))
207
- else
208
- ! No macros defined, treat all conditions as inactive
209
- call start_cpp_block(conditional_depth, inside_conditional_block, .false. )
210
- end if
279
+ call start_cpp_block(cpp_blk, file_lines_lower(i)% s, preprocess)
211
280
212
281
elseif (index (file_lines_lower(i)% s,' #endif' ) == 1 ) then
213
282
214
- call end_cpp_block(conditional_depth, inside_conditional_block )
283
+ call end_cpp_block(cpp_blk )
215
284
216
- elseif (index (file_lines_lower(i)% s,' #else' ) == 1 .or. &
217
- index (file_lines_lower(i)% s,' #elif' ) == 1 ) then
218
- ! For simplicity, treat #else/#elif as keeping the conditional block active
219
- ! TODO: More sophisticated handling would flip the condition for #else
220
- continue
285
+ elseif (index (file_lines_lower(i)% s,' #else' ) == 1 ) then
286
+
287
+ call handle_else_block(cpp_blk)
288
+
289
+ elseif (index (file_lines_lower(i)% s,' #elif' ) == 1 ) then
290
+
291
+ ! Treat #elif as #else followed by #if
292
+ call handle_else_block(cpp_blk)
293
+ call start_cpp_block(cpp_blk, file_lines_lower(i)% s, preprocess)
221
294
222
295
end if
223
296
@@ -229,9 +302,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
229
302
end if
230
303
231
304
! Skip content inside conditional blocks when conditional parsing is enabled
232
- if (cpp_conditional_parsing .and. inside_conditional_block) then
233
- cycle
234
- end if
305
+ if (cpp_conditional_parsing .and. cpp_blk% inside_inactive_block) cycle
235
306
236
307
! Detect exported C-API via bind(C)
237
308
if (.not. inside_interface .and. &
0 commit comments