Skip to content

Commit db67194

Browse files
committed
Add: parsing unit test for program with module case
1 parent f2a5119 commit db67194

File tree

1 file changed

+66
-2
lines changed

1 file changed

+66
-2
lines changed

fpm/test/test_source_parsing.f90

Lines changed: 66 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ subroutine collect_source_parsing(testsuite)
2525
& new_unittest("intrinsic-modules-used", test_intrinsic_modules_used), &
2626
& new_unittest("include-stmt", test_include_stmt), &
2727
& new_unittest("module", test_module), &
28+
& new_unittest("program-with-module", test_program_with_module), &
2829
& new_unittest("submodule", test_submodule), &
2930
& new_unittest("submodule-ancestor", test_submodule_ancestor), &
3031
& new_unittest("subprogram", test_subprogram), &
@@ -258,7 +259,7 @@ subroutine test_module(error)
258259
& 'contains', &
259260
& 'module procedure f()', &
260261
& 'end procedure f', &
261-
& 'end submodule test'
262+
& 'end module test'
262263
close(unit)
263264

264265
f_source = parse_f_source(temp_file,error)
@@ -287,13 +288,76 @@ subroutine test_module(error)
287288
end if
288289

289290
if (.not.('module_one' .in. f_source%modules_used)) then
290-
call test_failed(error,'Missing parent module in modules_used')
291+
call test_failed(error,'Missing module in modules_used')
291292
return
292293
end if
293294

294295
end subroutine test_module
295296

296297

298+
!> Try to parse combined fortran module and program
299+
!> Check that parsed unit type is FPM_UNIT_PROGRAM
300+
subroutine test_program_with_module(error)
301+
302+
!> Error handling
303+
type(error_t), allocatable, intent(out) :: error
304+
305+
integer :: unit
306+
character(:), allocatable :: temp_file
307+
type(srcfile_t), allocatable :: f_source
308+
309+
allocate(temp_file, source=get_temp_filename())
310+
311+
open(file=temp_file, newunit=unit)
312+
write(unit, '(a)') &
313+
& 'module my_mod', &
314+
& 'use module_one', &
315+
& 'interface', &
316+
& ' module subroutine f()', &
317+
& 'end interface', &
318+
& 'contains', &
319+
& 'module procedure f()', &
320+
& 'end procedure f', &
321+
& 'end module test', &
322+
& 'program my_program', &
323+
& 'use my_mod', &
324+
& 'implicit none', &
325+
& 'end my_program'
326+
close(unit)
327+
328+
f_source = parse_f_source(temp_file,error)
329+
if (allocated(error)) then
330+
return
331+
end if
332+
333+
if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
334+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_PROGRAM')
335+
return
336+
end if
337+
338+
if (size(f_source%modules_provided) /= 1) then
339+
call test_failed(error,'Unexpected modules_provided - expecting one')
340+
return
341+
end if
342+
343+
if (.not.('my_mod' .in. f_source%modules_provided)) then
344+
call test_failed(error,'Missing module in modules_provided')
345+
return
346+
end if
347+
348+
if (.not.('module_one' .in. f_source%modules_used)) then
349+
call test_failed(error,'Missing module in modules_used')
350+
return
351+
end if
352+
353+
if (.not.('my_mod' .in. f_source%modules_used)) then
354+
call test_failed(error,'Missing module in modules_used')
355+
return
356+
end if
357+
358+
end subroutine test_program_with_module
359+
360+
297361
!> Try to parse fortran submodule for ancestry
298362
subroutine test_submodule(error)
299363

0 commit comments

Comments
 (0)