Skip to content

Commit 3970511

Browse files
committed
consider #if defined(MACRO), #if MACRO, #ifndef, etc.
1 parent 9822ec1 commit 3970511

File tree

2 files changed

+153
-11
lines changed

2 files changed

+153
-11
lines changed

src/fpm_source_parsing.f90

Lines changed: 82 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,8 @@
1616
!>
1717
module fpm_source_parsing
1818
use fpm_error, only: error_t, file_parse_error, fatal_error, file_not_found_error
19-
use fpm_strings, only: string_t, string_cat, len_trim, split, lower, str_ends_with, fnv_1a, is_fortran_name
19+
use fpm_strings, only: string_t, string_cat, len_trim, split, lower, str_ends_with, fnv_1a, &
20+
is_fortran_name, operator(.in.)
2021
use fpm_model, only: srcfile_t, &
2122
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
2223
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
@@ -31,6 +32,76 @@ module fpm_source_parsing
3132

3233
contains
3334

35+
!> 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
40+
41+
conditional_depth = conditional_depth + 1
42+
if (conditional_depth == 1) then
43+
inside_conditional_block = .not. is_active
44+
end if
45+
end subroutine start_cpp_block
46+
47+
!> 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
51+
52+
conditional_depth = max(0, conditional_depth - 1)
53+
if (conditional_depth == 0) then
54+
inside_conditional_block = .false.
55+
end if
56+
end subroutine end_cpp_block
57+
58+
!> Parse CPP conditional directive and determine if block should be active
59+
function parse_cpp_condition(line, macros) result(is_active)
60+
character(*), intent(in) :: line
61+
type(string_t), intent(in) :: macros(:)
62+
logical :: is_active
63+
character(:), allocatable :: macro_name
64+
integer :: start_pos, end_pos
65+
66+
is_active = .false.
67+
68+
if (index(line, '#ifdef') == 1) then
69+
! #ifdef MACRO
70+
start_pos = index(line, ' ') + 1
71+
macro_name = trim(adjustl(line(start_pos:)))
72+
is_active = macro_name .in. macros
73+
74+
elseif (index(line, '#ifndef') == 1) then
75+
! #ifndef MACRO
76+
start_pos = index(line, ' ') + 1
77+
macro_name = trim(adjustl(line(start_pos:)))
78+
is_active = .not. (macro_name .in. macros)
79+
80+
elseif (index(line, '#if ') == 1) then
81+
! Handle various #if patterns
82+
if (index(line, 'defined(') > 0) then
83+
! #if defined(MACRO) or #if !defined(MACRO)
84+
start_pos = index(line, 'defined(') + 8
85+
end_pos = index(line(start_pos:), ')') - 1
86+
if (end_pos > 0) then
87+
macro_name = line(start_pos:start_pos + end_pos - 1)
88+
if (index(line, '!defined(') > 0) then
89+
is_active = .not. (macro_name .in. macros)
90+
else
91+
is_active = macro_name .in. macros
92+
end if
93+
end if
94+
else
95+
! #if MACRO (simple macro check)
96+
start_pos = 4 ! Skip "#if "
97+
end_pos = len_trim(line)
98+
macro_name = trim(adjustl(line(start_pos:end_pos)))
99+
is_active = macro_name .in. macros
100+
end if
101+
end if
102+
103+
end function parse_cpp_condition
104+
34105
!> Parsing of free-form fortran source files
35106
!>
36107
!> The following statements are recognised and parsed:
@@ -127,24 +198,25 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
127198
! Check for conditional compilation directives
128199
if (index(file_lines_lower(i)%s,'#ifdef') == 1 .or. &
129200
index(file_lines_lower(i)%s,'#ifndef') == 1 .or. &
130-
index(file_lines_lower(i)%s,'#if') == 1) then
201+
index(file_lines_lower(i)%s,'#if ') == 1) then
131202

132-
conditional_depth = conditional_depth + 1
133-
if (conditional_depth == 1) then
134-
inside_conditional_block = .true.
203+
! 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.)
135210
end if
136211

137212
elseif (index(file_lines_lower(i)%s,'#endif') == 1) then
138213

139-
conditional_depth = max(0, conditional_depth - 1)
140-
if (conditional_depth == 0) then
141-
inside_conditional_block = .false.
142-
end if
214+
call end_cpp_block(conditional_depth, inside_conditional_block)
143215

144216
elseif (index(file_lines_lower(i)%s,'#else') == 1 .or. &
145217
index(file_lines_lower(i)%s,'#elif') == 1) then
146218
! For simplicity, treat #else/#elif as keeping the conditional block active
147-
! In a more sophisticated implementation, we would evaluate conditions
219+
! TODO: More sophisticated handling would flip the condition for #else
148220
continue
149221

150222
end if

test/fpm_test/test_source_parsing.f90

Lines changed: 71 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,8 @@ subroutine collect_source_parsing(testsuite)
5050
& new_unittest("invalid-submodule", &
5151
test_invalid_submodule, should_fail=.true.), &
5252
& new_unittest("use-statement",test_use_statement), &
53-
& new_unittest("conditional-compilation", test_conditional_compilation) &
53+
& new_unittest("conditional-compilation", test_conditional_compilation), &
54+
& new_unittest("conditional-if-defined", test_conditional_if_defined) &
5455
]
5556

5657
end subroutine collect_source_parsing
@@ -1360,5 +1361,74 @@ subroutine test_conditional_compilation(error)
13601361

13611362
end subroutine test_conditional_compilation
13621363

1364+
!> Test conditional compilation parsing with #if defined() syntax
1365+
subroutine test_conditional_if_defined(error)
1366+
1367+
!> Error handling
1368+
type(error_t), allocatable, intent(out) :: error
1369+
1370+
type(srcfile_t) :: f_source
1371+
character(:), allocatable :: temp_file
1372+
integer :: unit
1373+
type(preprocess_config_t) :: cpp_config
1374+
1375+
temp_file = get_temp_filename()
1376+
1377+
open(file=temp_file, newunit=unit)
1378+
write(unit, '(a)') &
1379+
'module test_mod', &
1380+
'#if defined(SOME_FEATURE)', &
1381+
' use some_module', &
1382+
'#endif', &
1383+
'#if !defined(OTHER_FEATURE)', &
1384+
' use other_module', &
1385+
'#endif', &
1386+
'#if SIMPLE_MACRO', &
1387+
' use third_module', &
1388+
'#endif', &
1389+
'#ifdef FOURTH_FEATURE', &
1390+
' use fourth_module', &
1391+
'#endif', &
1392+
'#ifndef FIFTH_FEATURE', &
1393+
' use fifth_module', &
1394+
'#endif', &
1395+
' implicit none', &
1396+
'end module test_mod'
1397+
close(unit)
1398+
1399+
! Without preprocessing - should detect all dependencies
1400+
f_source = parse_f_source(temp_file, error)
1401+
if (allocated(error)) return
1402+
1403+
if (size(f_source%modules_used) /= 5) then
1404+
call test_failed(error, 'Expected 5 module dependencies without preprocessing')
1405+
return
1406+
end if
1407+
1408+
! With preprocessing - should skip all dependencies (no macros defined)
1409+
call cpp_config%new([string_t::])
1410+
1411+
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
1412+
if (allocated(error)) return
1413+
1414+
! Should find 2 dependencies: !defined(OTHER_FEATURE) and #ifndef FIFTH_FEATURE are both true
1415+
if (size(f_source%modules_used) /= 2) then
1416+
call test_failed(error, 'Expected 2 module dependencies with preprocessing enabled (negative conditions)')
1417+
return
1418+
end if
1419+
1420+
! Test with some macros defined - should find active dependencies
1421+
call cpp_config%new([string_t('SOME_FEATURE'), string_t('SIMPLE_MACRO')])
1422+
1423+
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
1424+
if (allocated(error)) return
1425+
1426+
if (size(f_source%modules_used) /= 2) then
1427+
call test_failed(error, 'Expected 2 module dependencies with SOME_FEATURE and SIMPLE_MACRO defined')
1428+
return
1429+
end if
1430+
1431+
end subroutine test_conditional_if_defined
1432+
13631433

13641434
end module test_source_parsing

0 commit comments

Comments
 (0)