Skip to content

Commit a523d30

Browse files
committed
add tests
1 parent 39522f0 commit a523d30

File tree

2 files changed

+94
-2
lines changed

2 files changed

+94
-2
lines changed

src/fpm_model.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ module fpm_model
5252
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
5353
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
5454
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
55-
FPM_UNIT_CPPSOURCE, FPM_SCOPE_NAME
55+
FPM_UNIT_CPPSOURCE, FPM_SCOPE_NAME, FPM_UNIT_NAME
5656

5757
!> Source type unknown
5858
integer, parameter :: FPM_UNIT_UNKNOWN = -1

test/fpm_test/test_source_parsing.f90

Lines changed: 93 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module test_source_parsing
55
use fpm_source_parsing, only: parse_f_source, parse_c_source, parse_use_statement
66
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
77
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
8-
FPM_UNIT_CPPSOURCE
8+
FPM_UNIT_CPPSOURCE, FPM_UNIT_NAME
99
use fpm_strings, only: operator(.in.), lower
1010
use fpm_error, only: file_parse_error, fatal_error
1111
implicit none
@@ -27,6 +27,8 @@ subroutine collect_source_parsing(testsuite)
2727
& new_unittest("nonintrinsic-modules-used", test_nonintrinsic_modules_used), &
2828
& new_unittest("include-stmt", test_include_stmt), &
2929
& new_unittest("program", test_program), &
30+
& new_unittest("program-noheader", test_program_noheader), &
31+
& new_unittest("program-noheader-2", test_program_noheader_2), &
3032
& new_unittest("module", test_module), &
3133
& new_unittest("module-with-subprogram", test_module_with_subprogram), &
3234
& new_unittest("module-with-c-api", test_module_with_c_api), &
@@ -380,6 +382,96 @@ subroutine test_program(error)
380382

381383
end subroutine test_program
382384

385+
!> Try to parse a simple fortran program with no "program" header
386+
subroutine test_program_noheader(error)
387+
388+
!> Error handling
389+
type(error_t), allocatable, intent(out) :: error
390+
391+
integer :: unit
392+
character(:), allocatable :: temp_file
393+
type(srcfile_t), allocatable :: f_source
394+
395+
allocate(temp_file, source=get_temp_filename())
396+
397+
open(file=temp_file, newunit=unit)
398+
write(unit, '(a)') &
399+
& 'use program_one', &
400+
& 'implicit none', &
401+
& 'integer :: module, program', &
402+
& 'module = 1', &
403+
& 'module= 1', &
404+
& 'module =1', &
405+
& 'module (i) =1', &
406+
& 'program = 123', &
407+
& 'contains', &
408+
& 'subroutine f()', &
409+
& 'end subroutine f', &
410+
& 'end program my_program'
411+
close(unit)
412+
413+
f_source = parse_f_source(temp_file,error)
414+
if (allocated(error)) then
415+
return
416+
end if
417+
418+
if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
419+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_PROGRAM, found '//&
420+
FPM_UNIT_NAME(f_source%unit_type))
421+
return
422+
end if
423+
424+
if (size(f_source%modules_provided) /= 0) then
425+
call test_failed(error,'Unexpected modules_provided - expecting zero')
426+
return
427+
end if
428+
429+
if (size(f_source%modules_used) /= 1) then
430+
call test_failed(error,'Incorrect number of modules_used - expecting one')
431+
return
432+
end if
433+
434+
if (.not.('program_one' .in. f_source%modules_used)) then
435+
call test_failed(error,'Missing module in modules_used')
436+
return
437+
end if
438+
439+
call f_source%test_serialization('srcfile_t: serialization', error)
440+
441+
end subroutine test_program_noheader
442+
443+
!> Try to parse a simple fortran program with no "program" header
444+
subroutine test_program_noheader_2(error)
445+
446+
!> Error handling
447+
type(error_t), allocatable, intent(out) :: error
448+
449+
integer :: unit
450+
character(:), allocatable :: temp_file
451+
type(srcfile_t), allocatable :: f_source
452+
453+
allocate(temp_file, source=get_temp_filename())
454+
455+
open(file=temp_file, newunit=unit)
456+
write(unit, '(a)') &
457+
& 'print *, "Hello World"', &
458+
& 'end program'
459+
close(unit)
460+
461+
f_source = parse_f_source(temp_file,error)
462+
if (allocated(error)) then
463+
return
464+
end if
465+
466+
if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
467+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_PROGRAM, found '//&
468+
FPM_UNIT_NAME(f_source%unit_type))
469+
return
470+
end if
471+
472+
call f_source%test_serialization('srcfile_t: serialization', error)
473+
474+
end subroutine test_program_noheader_2
383475

384476
!> Try to parse fortran module
385477
subroutine test_module(error)

0 commit comments

Comments
 (0)