Skip to content

Commit 8ca69d2

Browse files
committed
make macro parsing case sensitive
1 parent c71951b commit 8ca69d2

File tree

2 files changed

+53
-39
lines changed

2 files changed

+53
-39
lines changed

src/fpm_source_parsing.f90

Lines changed: 47 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -44,32 +44,30 @@ module fpm_source_parsing
4444
contains
4545

4646
!> 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)
4848
character(*), intent(in) :: macro_name
4949
type(string_t), optional, intent(in) :: macros(:)
5050
integer :: i
5151

52-
macro_in_list_ci = .false.
52+
type(string_t) :: lmacro
53+
54+
macro_in_list = .false.
5355
if (.not.present(macros)) return
5456

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
6260

6361
!> 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)
6563
type(cpp_block), intent(inout) :: blk
66-
character(*), intent(in) :: line
64+
character(*), intent(in) :: lower_line, line
6765
type(preprocess_config_t), optional, intent(in) :: preprocess
6866

6967
logical :: is_active
7068
character(:), allocatable :: macro_name
7169

72-
call parse_cpp_condition(line, preprocess, is_active, macro_name)
70+
call parse_cpp_condition(lower_line, line, preprocess, is_active, macro_name)
7371

7472
blk%depth = blk%depth + 1
7573

@@ -119,12 +117,12 @@ subroutine handle_else_block(blk)
119117
end subroutine handle_else_block
120118

121119
!> 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
124122
type(preprocess_config_t), optional, intent(in) :: preprocess
125123
character(:), allocatable, intent(out) :: macro_name
126124
logical, intent(out) :: is_active
127-
integer :: start_pos, end_pos
125+
integer :: start_pos, end_pos, heading_blanks, i
128126

129127
! Always active if CPP preprocessor is not active
130128
if (.not. present(preprocess)) then
@@ -140,42 +138,58 @@ subroutine parse_cpp_condition(line, preprocess, is_active, macro_name)
140138
return
141139
endif
142140

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+
143151
! There are macros: test if active
144-
if (index(line, '#ifdef') == 1) then
152+
if (index(lower_line, '#ifdef') == 1) then
145153
! #ifdef MACRO
146-
start_pos = index(line, ' ') + 1
154+
start_pos = index(lower_line, ' ') + heading_blanks + 1
155+
156+
! Pick non-lowercase macro name
147157
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)
149159

150-
elseif (index(line, '#ifndef') == 1) then
160+
elseif (index(lower_line, '#ifndef') == 1) then
151161
! #ifndef MACRO
152-
start_pos = index(line, ' ') + 1
162+
start_pos = index(lower_line, ' ') + heading_blanks + 1
153163
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)
155165

156-
elseif (index(line, '#if ') == 1) then
166+
elseif (index(lower_line, '#if ') == 1) then
157167
! Handle various #if patterns
158-
if (index(line, 'defined(') > 0) then
168+
if (index(lower_line, 'defined(') > 0) then
159169
! #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+
162176
if (end_pos > 0) then
163177
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)
166180
else
167-
is_active = macro_in_list_ci(macro_name, preprocess%macros)
181+
is_active = macro_in_list(macro_name, preprocess%macros)
168182
end if
169183
else
170184
! More complex condition
171185
is_active = .false.
172186
end if
173187
else
174188
! #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
177191
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)
179193
end if
180194
else
181195
is_active = .false.
@@ -281,7 +295,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
281295
index(file_lines_lower(i)%s,'#if ') == 1) then
282296

283297
! 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)
285299

286300
elseif (index(file_lines_lower(i)%s,'#endif') == 1) then
287301

@@ -295,7 +309,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
295309

296310
! Treat #elif as #else followed by #if
297311
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)
299313

300314
end if
301315

test/fpm_test/test_source_parsing.f90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1435,11 +1435,6 @@ subroutine test_conditional_if_defined(error)
14351435
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
14361436
if (allocated(error)) return
14371437

1438-
if (size(f_source%modules_used) /= 4) then ! some_module
1439-
call test_failed(error, 'Expected 4 module dependencies with SOME_FEATURE and SIMPLE_MACRO defined')
1440-
return
1441-
end if
1442-
14431438
if (.not.('some_module' .in. f_source%modules_used)) then ! some_module
14441439
call test_failed(error, 'Expected "some_module" dependency with SOME_FEATURE and SIMPLE_MACRO defined')
14451440
return
@@ -1455,7 +1450,12 @@ subroutine test_conditional_if_defined(error)
14551450
if (.not.('fifth_module' .in. f_source%modules_used)) then ! some_module
14561451
call test_failed(error, 'Expected "fifth_module" dependency with SOME_FEATURE and SIMPLE_MACRO defined')
14571452
return
1458-
end if
1453+
end if
1454+
1455+
if (size(f_source%modules_used) /= 4) then ! some_module
1456+
call test_failed(error, 'Expected 4 module dependencies with SOME_FEATURE and SIMPLE_MACRO defined')
1457+
return
1458+
end if
14591459

14601460
! Test nested condition: define outer but not inner macro
14611461
call cpp_config%new([string_t('FIFTH_FEATURE')]) ! This makes #ifndef FIFTH_FEATURE inactive

0 commit comments

Comments
 (0)