Skip to content

Commit 4bd3c81

Browse files
committed
Add test for issue #1073
1 parent da6d1bf commit 4bd3c81

File tree

1 file changed

+32
-0
lines changed

1 file changed

+32
-0
lines changed

test/fpm_test/test_source_parsing.f90

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ subroutine collect_source_parsing(testsuite)
3030
& new_unittest("module", test_module), &
3131
& new_unittest("module-with-subprogram", test_module_with_subprogram), &
3232
& new_unittest("module-with-c-api", test_module_with_c_api), &
33+
& new_unittest("module-with-abstract-interface",test_module_with_abstract_interface), &
3334
& new_unittest("module-end-stmt", test_module_end_stmt), &
3435
& new_unittest("program-with-module", test_program_with_module), &
3536
& new_unittest("submodule", test_submodule), &
@@ -632,6 +633,37 @@ subroutine test_module_with_c_api(error)
632633

633634
end subroutine test_module_with_c_api
634635

636+
!> Check parsing of module exporting an abstract interface
637+
!> See also https://github.com/fortran-lang/fpm/issues/1073
638+
subroutine test_module_with_abstract_interface(error)
639+
type(error_t), allocatable, intent(out) :: error
640+
641+
integer :: unit
642+
character(:), allocatable :: temp_file
643+
type(srcfile_t) :: f_source
644+
645+
allocate(temp_file,source=get_temp_filename())
646+
open(file=temp_file,newunit=unit)
647+
write(unit, '(A)') &
648+
& 'module foo', &
649+
& 'abstract interface', &
650+
& ' subroutine bar1()', &
651+
& ' end subroutine', &
652+
& ' subroutine bar2() bind(c)', &
653+
& ' end subroutine', &
654+
& 'end interface', &
655+
& 'end module foo'
656+
close(unit)
657+
658+
f_source = parse_f_source(temp_file,error)
659+
if (allocated(error)) return
660+
if (f_source%unit_type /= FPM_UNIT_MODULE) then
661+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_MODULE')
662+
return
663+
end if
664+
call f_source%test_serialization('srcfile_t: serialization', error)
665+
end subroutine test_module_with_abstract_interface
666+
635667

636668
!> Try to parse combined fortran module and program
637669
!> Check that parsed unit type is FPM_UNIT_PROGRAM

0 commit comments

Comments
 (0)