Skip to content

Commit 9fc44cc

Browse files
committed
test: added test for cpp_source parsing
1 parent 26468d2 commit 9fc44cc

File tree

1 file changed

+80
-3
lines changed

1 file changed

+80
-3
lines changed

test/fpm_test/test_source_parsing.f90

Lines changed: 80 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,9 +2,10 @@
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
5+
use fpm_source_parsing, only: parse_f_source, parse_c_source, parse_cpp_source
66
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
7-
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE
7+
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
8+
FPM_UNIT_CPPSOURCE
89
use fpm_strings, only: operator(.in.)
910
implicit none
1011
private
@@ -41,7 +42,8 @@ subroutine collect_source_parsing(testsuite)
4142
& new_unittest("invalid-module", &
4243
test_invalid_module, should_fail=.true.), &
4344
& new_unittest("invalid-submodule", &
44-
test_invalid_submodule, should_fail=.true.) &
45+
test_invalid_submodule, should_fail=.true.), &
46+
& new_unittest("cppsource", test_cppsource) &
4547
]
4648

4749
end subroutine collect_source_parsing
@@ -836,6 +838,81 @@ subroutine test_csource(error)
836838

837839
end subroutine test_csource
838840

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
839916

840917
!> Try to parse fortran program with invalid use statement
841918
subroutine test_invalid_use_stmt(error)

0 commit comments

Comments
 (0)