Skip to content

Commit 8a80890

Browse files
committed
simply nested conditions
1 parent 0e598bd commit 8a80890

File tree

2 files changed

+179
-50
lines changed

2 files changed

+179
-50
lines changed

src/fpm_source_parsing.f90

Lines changed: 115 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -30,52 +30,128 @@ module fpm_source_parsing
3030
private
3131
public :: parse_f_source, parse_c_source, parse_use_statement
3232

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+
3344
contains
3445

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+
3561
!> 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
4066

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+
4586
end subroutine start_cpp_block
4687

4788
!> 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
5191

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
5596
end if
97+
98+
blk%depth = max(0, blk%depth - 1)
99+
56100
end subroutine end_cpp_block
57101

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+
58119
!> 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)
60121
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
64125
integer :: start_pos, end_pos
65126

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+
66141
is_active = .false.
67142

143+
! There are macros: test if active
68144
if (index(line, '#ifdef') == 1) then
69145
! #ifdef MACRO
70146
start_pos = index(line, ' ') + 1
71147
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)
73149

74150
elseif (index(line, '#ifndef') == 1) then
75151
! #ifndef MACRO
76152
start_pos = index(line, ' ') + 1
77153
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)
79155

80156
elseif (index(line, '#if ') == 1) then
81157
! Handle various #if patterns
@@ -86,21 +162,21 @@ function parse_cpp_condition(line, macros) result(is_active)
86162
if (end_pos > 0) then
87163
macro_name = line(start_pos:start_pos + end_pos - 1)
88164
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)
90166
else
91-
is_active = macro_name .in. macros
167+
is_active = macro_in_list_ci(macro_name, preprocess%macros)
92168
end if
93169
end if
94170
else
95171
! #if MACRO (simple macro check)
96172
start_pos = 4 ! Skip "#if "
97173
end_pos = len_trim(line)
98174
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)
100176
end if
101177
end if
102178

103-
end function parse_cpp_condition
179+
end subroutine parse_cpp_condition
104180

105181
!> Parsing of free-form fortran source files
106182
!>
@@ -142,10 +218,10 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
142218
type(srcfile_t) :: f_source
143219

144220
logical :: inside_module, inside_interface, using, intrinsic_module
145-
logical :: inside_conditional_block, cpp_conditional_parsing
221+
logical :: cpp_conditional_parsing
146222
integer :: stat
147223
integer :: fh, n_use, n_include, n_mod, n_parent, i, j, ic, pass
148-
integer :: conditional_depth
224+
type(cpp_block) :: cpp_blk
149225
type(string_t), allocatable :: file_lines(:), file_lines_lower(:)
150226
character(:), allocatable :: temp_string, mod_name, string_parts(:)
151227

@@ -179,8 +255,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
179255
n_parent = 0
180256
inside_module = .false.
181257
inside_interface = .false.
182-
inside_conditional_block = .false.
183-
conditional_depth = 0
258+
cpp_blk = cpp_block() ! Initialize with default values
184259
file_loop: do i=1,size(file_lines_lower)
185260

186261
! Skip comment lines and empty lines
@@ -201,23 +276,21 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
201276
index(file_lines_lower(i)%s,'#if ') == 1) then
202277

203278
! 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)
211280

212281
elseif (index(file_lines_lower(i)%s,'#endif') == 1) then
213282

214-
call end_cpp_block(conditional_depth, inside_conditional_block)
283+
call end_cpp_block(cpp_blk)
215284

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)
221294

222295
end if
223296

@@ -229,9 +302,7 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
229302
end if
230303

231304
! 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
235306

236307
! Detect exported C-API via bind(C)
237308
if (.not.inside_interface .and. &

test/fpm_test/test_source_parsing.f90

Lines changed: 64 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1335,6 +1335,7 @@ subroutine test_conditional_compilation(error)
13351335

13361336
! Test 2: With preprocessing enabled, should skip dependencies from #ifdef blocks
13371337
call cpp_config%new([string_t::])
1338+
cpp_config%name = "cpp"
13381339

13391340
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
13401341
if (allocated(error)) return
@@ -1391,40 +1392,97 @@ subroutine test_conditional_if_defined(error)
13911392
'#endif', &
13921393
'#ifndef FIFTH_FEATURE', &
13931394
' use fifth_module', &
1395+
' #ifdef NESTED_FEATURE', &
1396+
' use nested_module', &
1397+
' #endif', &
13941398
'#endif', &
13951399
' implicit none', &
13961400
'end module test_mod'
13971401
close(unit)
13981402

1399-
! Without preprocessing - should detect all dependencies
1403+
! Without preprocessing - should detect all dependencies (including nested)
14001404
f_source = parse_f_source(temp_file, error)
14011405
if (allocated(error)) return
14021406

1403-
if (size(f_source%modules_used) /= 5) then
1404-
call test_failed(error, 'Expected 5 module dependencies without preprocessing')
1407+
if (size(f_source%modules_used) /= 6) then
1408+
call test_failed(error, 'Expected 6 module dependencies without preprocessing')
14051409
return
14061410
end if
14071411

14081412
! With preprocessing - should skip all dependencies (no macros defined)
14091413
call cpp_config%new([string_t::])
1414+
cpp_config%name = "cpp"
14101415

14111416
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
14121417
if (allocated(error)) return
14131418

14141419
! Should find 2 dependencies: !defined(OTHER_FEATURE) and #ifndef FIFTH_FEATURE are both true
1420+
! The nested #ifdef NESTED_FEATURE should be inactive since NESTED_FEATURE is not defined
14151421
if (size(f_source%modules_used) /= 2) then
1416-
call test_failed(error, 'Expected 2 module dependencies with preprocessing enabled (negative conditions)')
1422+
if (size(f_source%modules_used) > 0) then
1423+
call test_failed(error, 'Expected 2 module dependencies with preprocessing, got ' // &
1424+
f_source%modules_used(1)%s // ' (and others)')
1425+
else
1426+
call test_failed(error, 'Expected 2 module dependencies with preprocessing, got 0')
1427+
end if
14171428
return
14181429
end if
14191430

14201431
! Test with some macros defined - should find active dependencies
14211432
call cpp_config%new([string_t('SOME_FEATURE'), string_t('SIMPLE_MACRO')])
1433+
cpp_config%name = "cpp"
1434+
1435+
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
1436+
if (allocated(error)) return
1437+
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+
1443+
if (.not.('some_module' .in. f_source%modules_used)) then ! some_module
1444+
call test_failed(error, 'Expected "some_module" dependency with SOME_FEATURE and SIMPLE_MACRO defined')
1445+
return
1446+
end if
1447+
if (.not.('other_module' .in. f_source%modules_used)) then ! some_module
1448+
call test_failed(error, 'Expected "other_module" dependency with SOME_FEATURE and SIMPLE_MACRO defined')
1449+
return
1450+
end if
1451+
if (.not.('third_module' .in. f_source%modules_used)) then ! some_module
1452+
call test_failed(error, 'Expected "third_module" dependency with SOME_FEATURE and SIMPLE_MACRO defined')
1453+
return
1454+
end if
1455+
if (.not.('fifth_module' .in. f_source%modules_used)) then ! some_module
1456+
call test_failed(error, 'Expected "fifth_module" dependency with SOME_FEATURE and SIMPLE_MACRO defined')
1457+
return
1458+
end if
1459+
1460+
! Test nested condition: define outer but not inner macro
1461+
call cpp_config%new([string_t('FIFTH_FEATURE')]) ! This makes #ifndef FIFTH_FEATURE inactive
1462+
cpp_config%name = "cpp"
14221463

14231464
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
14241465
if (allocated(error)) return
14251466

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')
1467+
if (size(f_source%modules_used) /= 1) then
1468+
if (size(f_source%modules_used) > 0) then
1469+
call test_failed(error, 'Expected 1 module dependency with FIFTH_FEATURE defined, got: ' // &
1470+
f_source%modules_used(2)%s // ' (and maybe others)')
1471+
else
1472+
call test_failed(error, 'Expected 1 module dependency with FIFTH_FEATURE defined, got 0')
1473+
end if
1474+
return
1475+
end if
1476+
1477+
! Test nested condition: define both outer condition (negative) and inner (positive)
1478+
call cpp_config%new([string_t('NESTED_FEATURE')]) ! FIFTH_FEATURE not defined, NESTED_FEATURE defined
1479+
cpp_config%name = "cpp"
1480+
1481+
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
1482+
if (allocated(error)) return
1483+
1484+
if (size(f_source%modules_used) /= 3) then
1485+
call test_failed(error, 'Expected 3 module dependencies with nested conditions active')
14281486
return
14291487
end if
14301488

0 commit comments

Comments
 (0)