Skip to content

Commit 08b0815

Browse files
committed
refactor: removed parse_cpp_source subroutine and test for it
1 parent 9fc44cc commit 08b0815

File tree

3 files changed

+12
-162
lines changed

3 files changed

+12
-162
lines changed

src/fpm_source_parsing.f90

Lines changed: 7 additions & 77 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ module fpm_source_parsing
2727
implicit none
2828

2929
private
30-
public :: parse_f_source, parse_c_source, parse_cpp_source
30+
public :: parse_f_source, parse_c_source
3131

3232
character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
3333
['iso_c_binding ', &
@@ -436,7 +436,7 @@ function parse_f_source(f_filename,error) result(f_source)
436436
end function parse_f_source
437437

438438

439-
!> Parsing of c source files
439+
!> Parsing of c, cpp source files
440440
!>
441441
!> The following statements are recognised and parsed:
442442
!>
@@ -456,10 +456,14 @@ function parse_c_source(c_filename,error) result(c_source)
456456

457457
c_source%unit_type = FPM_UNIT_CSOURCE
458458

459-
elseif (str_ends_with(lower(c_filename), ".h")) then
459+
else if (str_ends_with(lower(c_filename), ".h")) then
460460

461461
c_source%unit_type = FPM_UNIT_CHEADER
462462

463+
else if (str_ends_with(lower(c_filename), ".cpp")) then
464+
465+
c_source%unit_type = FPM_UNIT_CPPSOURCE
466+
463467
end if
464468

465469
allocate(c_source%modules_used(0))
@@ -513,80 +517,6 @@ function parse_c_source(c_filename,error) result(c_source)
513517

514518
end function parse_c_source
515519

516-
!> Parsing of cpp source files
517-
!>
518-
!> The following statements are recognised and parsed:
519-
!>
520-
!> - `#include` preprocessor statement
521-
!>
522-
function parse_cpp_source(c_filename,error) result(cpp_source)
523-
character(*), intent(in) :: c_filename
524-
type(srcfile_t) :: cpp_source
525-
type(error_t), allocatable, intent(out) :: error
526-
527-
integer :: fh, n_include, i, pass, stat
528-
type(string_t), allocatable :: file_lines(:)
529-
530-
cpp_source%file_name = c_filename
531-
532-
if (str_ends_with(lower(c_filename), ".cpp")) then
533-
534-
cpp_source%unit_type = FPM_UNIT_CPPSOURCE
535-
536-
end if
537-
538-
allocate(cpp_source%modules_used(0))
539-
allocate(cpp_source%modules_provided(0))
540-
allocate(cpp_source%parent_modules(0))
541-
542-
open(newunit=fh,file=c_filename,status='old')
543-
file_lines = read_lines(fh)
544-
close(fh)
545-
546-
! Ignore empty files, returned as FPM_UNIT_UNKNOWN
547-
if (len_trim(file_lines) < 1) then
548-
cpp_source%unit_type = FPM_UNIT_UNKNOWN
549-
return
550-
end if
551-
552-
cpp_source%digest = fnv_1a(file_lines)
553-
554-
do pass = 1,2
555-
n_include = 0
556-
file_loop: do i=1,size(file_lines)
557-
558-
! Process 'INCLUDE' statements
559-
if (index(adjustl(lower(file_lines(i)%s)),'#include') == 1 .and. &
560-
index(file_lines(i)%s,'"') > 0) then
561-
562-
n_include = n_include + 1
563-
564-
if (pass == 2) then
565-
566-
cpp_source%include_dependencies(n_include)%s = &
567-
& split_n(file_lines(i)%s,n=2,delims='"',stat=stat)
568-
if (stat /= 0) then
569-
call file_parse_error(error,c_filename, &
570-
'unable to get cpp include file',i, &
571-
file_lines(i)%s,index(file_lines(i)%s,'"'))
572-
return
573-
end if
574-
575-
end if
576-
577-
end if
578-
579-
end do file_loop
580-
581-
if (pass == 1) then
582-
allocate(cpp_source%include_dependencies(n_include))
583-
end if
584-
585-
end do
586-
587-
end function parse_cpp_source
588-
589-
590520
!> Split a string on one or more delimeters
591521
!> and return the nth substring if it exists
592522
!>

src/fpm_sources.f90

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module fpm_sources
88
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM
99
use fpm_filesystem, only: basename, canon_path, dirname, join_path, list_files, is_hidden_file
1010
use fpm_strings, only: lower, str_ends_with, string_t, operator(.in.)
11-
use fpm_source_parsing, only: parse_f_source, parse_c_source, parse_cpp_source
11+
use fpm_source_parsing, only: parse_f_source, parse_c_source
1212
use fpm_manifest_executable, only: executable_config_t
1313
implicit none
1414

@@ -17,6 +17,7 @@ module fpm_sources
1717

1818
character(4), parameter :: fortran_suffixes(2) = [".f90", &
1919
".f "]
20+
character(4), parameter :: c_suffixes(3) = [".c ", ".h ", ".cpp"]
2021

2122
contains
2223

@@ -35,14 +36,10 @@ function parse_source(source_file_path,error) result(source)
3536
source%exe_name = basename(source_file_path,suffix=.false.)
3637
end if
3738

38-
else if (str_ends_with(lower(source_file_path), [".c", ".h"])) then
39+
else if (str_ends_with(lower(source_file_path), c_suffixes)) then
3940

4041
source = parse_c_source(source_file_path,error)
4142

42-
else if (str_ends_with(lower(source_file_path), [".cpp"])) then
43-
44-
source = parse_cpp_source(source_file_path, error)
45-
4643
end if
4744

4845
if (allocated(error)) then

test/fpm_test/test_source_parsing.f90

Lines changed: 2 additions & 79 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
module test_source_parsing
33
use testsuite, only : new_unittest, unittest_t, error_t, test_failed
44
use fpm_filesystem, only: get_temp_filename
5-
use fpm_source_parsing, only: parse_f_source, parse_c_source, parse_cpp_source
5+
use fpm_source_parsing, only: parse_f_source, parse_c_source
66
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
77
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
88
FPM_UNIT_CPPSOURCE
@@ -42,8 +42,7 @@ subroutine collect_source_parsing(testsuite)
4242
& new_unittest("invalid-module", &
4343
test_invalid_module, should_fail=.true.), &
4444
& new_unittest("invalid-submodule", &
45-
test_invalid_submodule, should_fail=.true.), &
46-
& new_unittest("cppsource", test_cppsource) &
45+
test_invalid_submodule, should_fail=.true.) &
4746
]
4847

4948
end subroutine collect_source_parsing
@@ -838,82 +837,6 @@ subroutine test_csource(error)
838837

839838
end subroutine test_csource
840839

841-
!> Try to parse standard cpp source for includes
842-
subroutine test_cppsource(error)
843-
844-
!> Error handling
845-
type(error_t), allocatable, intent(out) :: error
846-
847-
integer :: unit
848-
character(:), allocatable :: temp_file
849-
type(srcfile_t), allocatable :: f_source
850-
851-
allocate(temp_file, source=get_temp_filename())
852-
temp_file = temp_file//'.cpp'
853-
854-
open(file=temp_file, newunit=unit)
855-
write(unit, '(a)') &
856-
& '#include "file1.h"', &
857-
& '#include "file2.h"', &
858-
& 'void sum(int a) {', &
859-
& ' #include "function_body.cpp"', &
860-
& ' // This is the function body.', &
861-
& ' return', &
862-
& '}'
863-
close(unit)
864-
865-
f_source = parse_cpp_source(temp_file,error)
866-
if (allocated(error)) then
867-
return
868-
end if
869-
870-
if (f_source%unit_type /= FPM_UNIT_CPPSOURCE) then
871-
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_CSOURCE')
872-
return
873-
end if
874-
875-
if (size(f_source%modules_provided) /= 0) then
876-
call test_failed(error,'Unexpected modules_provided - expecting zero')
877-
return
878-
end if
879-
880-
if (size(f_source%modules_used) /= 0) then
881-
call test_failed(error,'Incorrect number of modules_used - expecting zero')
882-
return
883-
end if
884-
885-
if (size(f_source%include_dependencies) /= 3) then
886-
call test_failed(error,'Incorrect number of include_dependencies - expecting two')
887-
return
888-
end if
889-
890-
if (allocated(f_source%link_libraries)) then
891-
call test_failed(error,'Unexpected link_libraries - expecting unallocated')
892-
return
893-
end if
894-
895-
if (size(f_source%parent_modules) /= 0) then
896-
call test_failed(error,'Incorrect number of parent_modules - expecting zero')
897-
return
898-
end if
899-
900-
if (.not.('file1.h' .in. f_source%include_dependencies)) then
901-
call test_failed(error,'Missing file in include_dependencies')
902-
return
903-
end if
904-
905-
if (.not.('file2.h' .in. f_source%include_dependencies)) then
906-
call test_failed(error,'Missing file in include_dependencies')
907-
return
908-
end if
909-
910-
if (.not.('function_body.cpp' .in. f_source%include_dependencies)) then
911-
call test_failed(error,'Missing file in include_dependencies')
912-
return
913-
end if
914-
915-
end subroutine test_cppsource
916-
917840
!> Try to parse fortran program with invalid use statement
918841
subroutine test_invalid_use_stmt(error)
919842

0 commit comments

Comments
 (0)