Skip to content

Commit 04a13b6

Browse files
authored
fix #elif cpp preprocessing (#1197)
2 parents 54978e6 + f791261 commit 04a13b6

File tree

2 files changed

+266
-0
lines changed

2 files changed

+266
-0
lines changed

src/fpm_source_parsing.f90

Lines changed: 27 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -191,6 +191,33 @@ subroutine parse_cpp_condition(lower_line, line, preprocess, is_active, macro_na
191191
macro_name = trim(adjustl(line(start_pos:end_pos)))
192192
is_active = macro_in_list(macro_name, preprocess%macros)
193193
end if
194+
elseif (index(lower_line, '#elif') == 1) then
195+
! #elif defined(MACRO) or #elif !defined(MACRO)
196+
if (index(lower_line, 'defined(') > 0) then
197+
start_pos = index(lower_line, 'defined(') + 8
198+
end_pos = index(lower_line(start_pos:), ')') - 1
199+
200+
start_pos = start_pos + heading_blanks
201+
end_pos = end_pos + heading_blanks
202+
203+
if (end_pos > 0) then
204+
macro_name = line(start_pos:start_pos + end_pos - 1)
205+
if (index(lower_line, '!defined(') > 0) then
206+
is_active = .not. macro_in_list(macro_name, preprocess%macros)
207+
else
208+
is_active = macro_in_list(macro_name, preprocess%macros)
209+
end if
210+
else
211+
is_active = .false.
212+
macro_name = ""
213+
end if
214+
else
215+
! simple form: #elif MACRO
216+
start_pos = 6 + heading_blanks ! skip "#elif "
217+
end_pos = len_trim(lower_line) + heading_blanks
218+
macro_name = trim(adjustl(line(start_pos:end_pos)))
219+
is_active = macro_in_list(macro_name, preprocess%macros)
220+
end if
194221
else
195222
is_active = .false.
196223
end if

test/fpm_test/test_source_parsing.f90

Lines changed: 239 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,9 @@ subroutine collect_source_parsing(testsuite)
5151
test_invalid_submodule, should_fail=.true.), &
5252
& new_unittest("use-statement",test_use_statement), &
5353
& new_unittest("conditional-compilation", test_conditional_compilation), &
54+
& new_unittest("conditional-compilation-elif", test_conditional_compilation_elif), &
55+
& new_unittest("conditional-compilation-elif-else", test_conditional_compilation_elif_else), &
56+
& new_unittest("conditional-compilation_ifdef_else", test_conditional_compilation_ifdef_else), &
5457
& new_unittest("conditional-if-defined", test_conditional_if_defined) &
5558
]
5659

@@ -1361,6 +1364,242 @@ subroutine test_conditional_compilation(error)
13611364
end if
13621365

13631366
end subroutine test_conditional_compilation
1367+
!> Test conditional compilation parsing with CPP preprocessing
1368+
subroutine test_conditional_compilation_elif(error)
1369+
1370+
!> Error handling
1371+
type(error_t), allocatable, intent(out) :: error
1372+
1373+
type(srcfile_t) :: f_source
1374+
character(:), allocatable :: temp_file
1375+
integer :: unit
1376+
type(preprocess_config_t) :: cpp_config
1377+
1378+
! Test 1: Without preprocessing, should include dependencies from #ifdef blocks
1379+
temp_file = get_temp_filename()
1380+
1381+
open(file=temp_file, newunit=unit)
1382+
write(unit, '(a)') &
1383+
'module test_mod', &
1384+
'#ifdef SOME_FEATURE', &
1385+
' use nonexistent_module', &
1386+
'#elif defined(ANOTHER_FEATURE)', &
1387+
' use another_nonexistent_module', &
1388+
'#endif', &
1389+
' implicit none', &
1390+
'contains', &
1391+
' subroutine test_sub()', &
1392+
' print *, "test"', &
1393+
' end subroutine', &
1394+
'end module test_mod'
1395+
close(unit)
1396+
1397+
! Parse without preprocessing - should detect the use statement
1398+
f_source = parse_f_source(temp_file, error)
1399+
if (allocated(error)) return
1400+
1401+
if (size(f_source%modules_used) /= 2) then
1402+
call test_failed(error, 'Expected 2 module dependency without preprocessing, got different count')
1403+
return
1404+
end if
1405+
1406+
if (f_source%modules_used(1)%s /= 'nonexistent_module') then
1407+
call test_failed(error, 'Expected nonexistent_module, got: '//f_source%modules_used(1)%s)
1408+
return
1409+
end if
1410+
1411+
if (f_source%modules_used(2)%s /= 'another_nonexistent_module') then
1412+
call test_failed(error, 'Expected another_nonexistent_module, got: '//f_source%modules_used(2)%s)
1413+
return
1414+
end if
1415+
1416+
! Test 2: With preprocessing enabled, should skip dependencies from #ifdef blocks
1417+
call cpp_config%new([string_t::])
1418+
cpp_config%name = "cpp"
1419+
1420+
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
1421+
if (allocated(error)) return
1422+
1423+
if (size(f_source%modules_used) /= 0) then
1424+
call test_failed(error, 'Expected 0 module dependencies with preprocessing, got some dependencies')
1425+
return
1426+
end if
1427+
1428+
if (f_source%unit_type /= FPM_UNIT_MODULE) then
1429+
call test_failed(error, 'Expected module unit type')
1430+
return
1431+
end if
1432+
1433+
if (size(f_source%modules_provided) /= 1) then
1434+
call test_failed(error, 'Expected 1 provided module')
1435+
return
1436+
end if
1437+
1438+
if (f_source%modules_provided(1)%s /= 'test_mod') then
1439+
call test_failed(error, 'Expected test_mod, got: '//f_source%modules_provided(1)%s)
1440+
return
1441+
end if
1442+
1443+
end subroutine test_conditional_compilation_elif
1444+
!> Test conditional compilation parsing with CPP preprocessing
1445+
subroutine test_conditional_compilation_elif_else(error)
1446+
1447+
!> Error handling
1448+
type(error_t), allocatable, intent(out) :: error
1449+
1450+
type(srcfile_t) :: f_source
1451+
character(:), allocatable :: temp_file
1452+
integer :: unit
1453+
type(preprocess_config_t) :: cpp_config
1454+
1455+
! Test 1: Without preprocessing, should include dependencies from #ifdef blocks
1456+
temp_file = get_temp_filename()
1457+
1458+
open(file=temp_file, newunit=unit)
1459+
write(unit, '(a)') &
1460+
'module test_mod', &
1461+
'#ifdef SOME_FEATURE', &
1462+
' use nonexistent_module', &
1463+
'#elif defined(ANOTHER_FEATURE)', &
1464+
' use another_nonexistent_module', &
1465+
'#else',&
1466+
' use a_third_module',&
1467+
'#endif', &
1468+
' implicit none', &
1469+
'contains', &
1470+
' subroutine test_sub()', &
1471+
' print *, "test"', &
1472+
' end subroutine', &
1473+
'end module test_mod'
1474+
close(unit)
1475+
1476+
! Parse without preprocessing - should detect the use statement
1477+
f_source = parse_f_source(temp_file, error)
1478+
if (allocated(error)) return
1479+
1480+
if (size(f_source%modules_used) /= 3) then
1481+
call test_failed(error, 'Expected 3 module dependency without preprocessing, got different count')
1482+
return
1483+
end if
1484+
1485+
if (f_source%modules_used(1)%s /= 'nonexistent_module') then
1486+
call test_failed(error, 'Expected nonexistent_module, got: '//f_source%modules_used(1)%s)
1487+
return
1488+
end if
1489+
if (f_source%modules_used(2)%s /= 'another_nonexistent_module') then
1490+
call test_failed(error, 'Expected another_nonexistent_module, got: '//f_source%modules_used(2)%s)
1491+
return
1492+
end if
1493+
if (f_source%modules_used(3)%s /= 'a_third_module') then
1494+
call test_failed(error, 'Expected a_third_module, got: '//f_source%modules_used(3)%s)
1495+
return
1496+
end if
1497+
1498+
! Test 2: With preprocessing enabled, should skip dependencies from #ifdef blocks
1499+
call cpp_config%new([string_t::])
1500+
cpp_config%name = "cpp"
1501+
1502+
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
1503+
if (allocated(error)) return
1504+
1505+
if (size(f_source%modules_used) /= 1) then
1506+
call test_failed(error, 'Expected 1 module dependencies with preprocessing, got some dependencies')
1507+
return
1508+
end if
1509+
1510+
if (f_source%unit_type /= FPM_UNIT_MODULE) then
1511+
call test_failed(error, 'Expected module unit type')
1512+
return
1513+
end if
1514+
1515+
if (size(f_source%modules_provided) /= 1) then
1516+
call test_failed(error, 'Expected 1 provided module')
1517+
return
1518+
end if
1519+
1520+
if (f_source%modules_provided(1)%s /= 'test_mod') then
1521+
call test_failed(error, 'Expected test_mod, got: '//f_source%modules_provided(1)%s)
1522+
return
1523+
end if
1524+
1525+
end subroutine test_conditional_compilation_elif_else
1526+
1527+
subroutine test_conditional_compilation_ifdef_else(error)
1528+
1529+
!> Error handling
1530+
type(error_t), allocatable, intent(out) :: error
1531+
1532+
type(srcfile_t) :: f_source
1533+
character(:), allocatable :: temp_file
1534+
integer :: unit
1535+
type(preprocess_config_t) :: cpp_config
1536+
1537+
! Test 1: Without preprocessing, should include dependencies from #ifdef blocks
1538+
temp_file = get_temp_filename()
1539+
1540+
open(file=temp_file, newunit=unit)
1541+
write(unit, '(a)') &
1542+
'module test_mod', &
1543+
'#ifdef SOME_FEATURE', &
1544+
' use nonexistent_module', &
1545+
'#else',&
1546+
' use a_second_module',&
1547+
'#endif', &
1548+
' implicit none', &
1549+
'contains', &
1550+
' subroutine test_sub()', &
1551+
' print *, "test"', &
1552+
' end subroutine', &
1553+
'end module test_mod'
1554+
close(unit)
1555+
1556+
! Parse without preprocessing - should detect the use statement
1557+
f_source = parse_f_source(temp_file, error)
1558+
if (allocated(error)) return
1559+
1560+
if (size(f_source%modules_used) /= 2) then
1561+
call test_failed(error, 'Expected 2 module dependency without preprocessing, got different count')
1562+
return
1563+
end if
1564+
1565+
if (f_source%modules_used(1)%s /= 'nonexistent_module') then
1566+
call test_failed(error, 'Expected nonexistent_module, got: '//f_source%modules_used(1)%s)
1567+
return
1568+
end if
1569+
1570+
if (f_source%modules_used(2)%s /= 'a_second_module') then
1571+
call test_failed(error, 'Expected a_second_module, got: '//f_source%modules_used(2)%s)
1572+
return
1573+
end if
1574+
1575+
! Test 2: With preprocessing enabled, should skip dependencies from #ifdef blocks
1576+
call cpp_config%new([string_t::])
1577+
cpp_config%name = "cpp"
1578+
1579+
f_source = parse_f_source(temp_file, error, preprocess=cpp_config)
1580+
if (allocated(error)) return
1581+
1582+
if (size(f_source%modules_used) /= 1) then
1583+
call test_failed(error, 'Expected 1 module dependencies with preprocessing, got some dependencies')
1584+
return
1585+
end if
1586+
1587+
if (f_source%unit_type /= FPM_UNIT_MODULE) then
1588+
call test_failed(error, 'Expected module unit type')
1589+
return
1590+
end if
1591+
1592+
if (size(f_source%modules_provided) /= 1) then
1593+
call test_failed(error, 'Expected 1 provided module')
1594+
return
1595+
end if
1596+
1597+
if (f_source%modules_provided(1)%s /= 'test_mod') then
1598+
call test_failed(error, 'Expected test_mod, got: '//f_source%modules_provided(1)%s)
1599+
return
1600+
end if
1601+
1602+
end subroutine test_conditional_compilation_ifdef_else
13641603

13651604
!> Test conditional compilation parsing with #if defined() syntax
13661605
subroutine test_conditional_if_defined(error)

0 commit comments

Comments
 (0)