@@ -44,32 +44,30 @@ module fpm_source_parsing
44
44
contains
45
45
46
46
! > Case-insensitive check if macro_name is in the macros list
47
- logical function macro_in_list_ci (macro_name , macros )
47
+ logical function macro_in_list (macro_name , macros )
48
48
character (* ), intent (in ) :: macro_name
49
49
type (string_t), optional , intent (in ) :: macros(:)
50
50
integer :: i
51
51
52
- macro_in_list_ci = .false.
52
+ type (string_t) :: lmacro
53
+
54
+ macro_in_list = .false.
53
55
if (.not. present (macros)) return
54
56
55
- do i = 1 , size (macros)
56
- if (string_t(lower(macro_name)) == macros(i)) then
57
- macro_in_list_ci = .true.
58
- return
59
- end if
60
- end do
61
- end function macro_in_list_ci
57
+ macro_in_list = macro_name .in . macros
58
+
59
+ end function macro_in_list
62
60
63
61
! > Start a CPP conditional block (active or inactive)
64
- subroutine start_cpp_block (blk , line , preprocess )
62
+ subroutine start_cpp_block (blk , lower_line , line , preprocess )
65
63
type (cpp_block), intent (inout ) :: blk
66
- character (* ), intent (in ) :: line
64
+ character (* ), intent (in ) :: lower_line, line
67
65
type (preprocess_config_t), optional , intent (in ) :: preprocess
68
66
69
67
logical :: is_active
70
68
character (:), allocatable :: macro_name
71
69
72
- call parse_cpp_condition(line, preprocess, is_active, macro_name)
70
+ call parse_cpp_condition(lower_line, line, preprocess, is_active, macro_name)
73
71
74
72
blk% depth = blk% depth + 1
75
73
@@ -119,12 +117,12 @@ subroutine handle_else_block(blk)
119
117
end subroutine handle_else_block
120
118
121
119
! > Parse CPP conditional directive and determine if block should be active
122
- subroutine parse_cpp_condition (line , preprocess , is_active , macro_name )
123
- character (* ), intent (in ) :: line
120
+ subroutine parse_cpp_condition (lower_line , line , preprocess , is_active , macro_name )
121
+ character (* ), intent (in ) :: lower_line, line
124
122
type (preprocess_config_t), optional , intent (in ) :: preprocess
125
123
character (:), allocatable , intent (out ) :: macro_name
126
124
logical , intent (out ) :: is_active
127
- integer :: start_pos, end_pos
125
+ integer :: start_pos, end_pos, heading_blanks, i
128
126
129
127
! Always active if CPP preprocessor is not active
130
128
if (.not. present (preprocess)) then
@@ -140,42 +138,58 @@ subroutine parse_cpp_condition(line, preprocess, is_active, macro_name)
140
138
return
141
139
endif
142
140
141
+ ! Find offset between lowercase adjustl and standard line
142
+ heading_blanks = 0
143
+ do i= 1 ,len (line)
144
+ if (line(i:i)==' ' ) then
145
+ heading_blanks = heading_blanks+1
146
+ else
147
+ exit
148
+ end if
149
+ end do
150
+
143
151
! There are macros: test if active
144
- if (index (line , ' #ifdef' ) == 1 ) then
152
+ if (index (lower_line , ' #ifdef' ) == 1 ) then
145
153
! #ifdef MACRO
146
- start_pos = index (line, ' ' ) + 1
154
+ start_pos = index (lower_line, ' ' ) + heading_blanks + 1
155
+
156
+ ! Pick non-lowercase macro name
147
157
macro_name = trim (adjustl (line(start_pos:)))
148
- is_active = macro_in_list_ci (macro_name, preprocess% macros)
158
+ is_active = macro_in_list (macro_name, preprocess% macros)
149
159
150
- elseif (index (line , ' #ifndef' ) == 1 ) then
160
+ elseif (index (lower_line , ' #ifndef' ) == 1 ) then
151
161
! #ifndef MACRO
152
- start_pos = index (line , ' ' ) + 1
162
+ start_pos = index (lower_line , ' ' ) + heading_blanks + 1
153
163
macro_name = trim (adjustl (line(start_pos:)))
154
- is_active = .not. macro_in_list_ci (macro_name, preprocess% macros)
164
+ is_active = .not. macro_in_list (macro_name, preprocess% macros)
155
165
156
- elseif (index (line , ' #if ' ) == 1 ) then
166
+ elseif (index (lower_line , ' #if ' ) == 1 ) then
157
167
! Handle various #if patterns
158
- if (index (line , ' defined(' ) > 0 ) then
168
+ if (index (lower_line , ' defined(' ) > 0 ) then
159
169
! #if defined(MACRO) or #if !defined(MACRO)
160
- start_pos = index (line, ' defined(' ) + 8
161
- end_pos = index (line(start_pos:), ' )' ) - 1
170
+ start_pos = index (lower_line, ' defined(' ) + 8
171
+ end_pos = index (lower_line(start_pos:), ' )' ) - 1
172
+
173
+ start_pos = start_pos+ heading_blanks
174
+ end_pos = end_pos+ heading_blanks
175
+
162
176
if (end_pos > 0 ) then
163
177
macro_name = line(start_pos:start_pos + end_pos - 1 )
164
- if (index (line , ' !defined(' ) > 0 ) then
165
- is_active = .not. macro_in_list_ci (macro_name, preprocess% macros)
178
+ if (index (lower_line , ' !defined(' ) > 0 ) then
179
+ is_active = .not. macro_in_list (macro_name, preprocess% macros)
166
180
else
167
- is_active = macro_in_list_ci (macro_name, preprocess% macros)
181
+ is_active = macro_in_list (macro_name, preprocess% macros)
168
182
end if
169
183
else
170
184
! More complex condition
171
185
is_active = .false.
172
186
end if
173
187
else
174
188
! #if MACRO (simple macro check)
175
- start_pos = 4 ! Skip "#if "
176
- end_pos = len_trim (line)
189
+ start_pos = 4 + heading_blanks ! Skip "#if "
190
+ end_pos = len_trim (lower_line) + heading_blanks
177
191
macro_name = trim (adjustl (line(start_pos:end_pos)))
178
- is_active = macro_in_list_ci (macro_name, preprocess% macros)
192
+ is_active = macro_in_list (macro_name, preprocess% macros)
179
193
end if
180
194
else
181
195
is_active = .false.
@@ -281,7 +295,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
281
295
index (file_lines_lower(i)% s,' #if ' ) == 1 ) then
282
296
283
297
! Determine if this conditional block should be active
284
- call start_cpp_block(cpp_blk, file_lines_lower(i)% s, preprocess)
298
+ call start_cpp_block(cpp_blk, file_lines_lower(i)% s, file_lines(i) % s, preprocess)
285
299
286
300
elseif (index (file_lines_lower(i)% s,' #endif' ) == 1 ) then
287
301
@@ -295,7 +309,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
295
309
296
310
! Treat #elif as #else followed by #if
297
311
call handle_else_block(cpp_blk)
298
- call start_cpp_block(cpp_blk, file_lines_lower(i)% s, preprocess)
312
+ call start_cpp_block(cpp_blk, file_lines_lower(i)% s, file_lines(i) % s, preprocess)
299
313
300
314
end if
301
315
0 commit comments