Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
31 changes: 17 additions & 14 deletions src/fpm_source_parsing.f90
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,7 @@ function parse_f_source(f_filename,error) result(f_source)
integer :: stat
integer :: fh, n_use, n_include, n_mod, i, j, ic, pass
type(string_t), allocatable :: file_lines(:)
character(:), allocatable :: temp_string, mod_name
character(:), allocatable :: temp_string, mod_name, string_parts(:)

f_source%file_name = f_filename

Expand Down Expand Up @@ -191,22 +191,25 @@ function parse_f_source(f_filename,error) result(f_source)
! Extract name of module if is module
if (index(adjustl(lower(file_lines(i)%s)),'module ') == 1) then

mod_name = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat))
if (stat /= 0) then
call file_parse_error(error,f_filename, &
'unable to find module name',i, &
file_lines(i)%s)
return
! Remove any trailing comments
ic = index(file_lines(i)%s,'!')-1
if (ic < 1) then
ic = len(file_lines(i)%s)
end if
temp_string = trim(file_lines(i)%s(1:ic))

! R1405 module-stmt := "MODULE" module-name
! module-stmt has two space-delimited parts only
! (no line continuations)
call split(temp_string,string_parts,' ')
if (size(string_parts) /= 2) then
cycle
end if

if (mod_name == 'procedure' .or. &
mod_name == 'subroutine' .or. &
mod_name == 'function' .or. &
scan(mod_name,'=(')>0 ) then
mod_name = lower(trim(adjustl(string_parts(2))))
if (scan(mod_name,'=(&')>0 ) then
! Ignore these cases:
! module procedure *
! module function *
! module subroutine *
! module <something>&
! module =*
! module (i)
cycle
Expand Down
23 changes: 17 additions & 6 deletions test/fpm_test/test_source_parsing.f90
Original file line number Diff line number Diff line change
Expand Up @@ -309,7 +309,7 @@ subroutine test_module(error)

open(file=temp_file, newunit=unit)
write(unit, '(a)') &
& 'module my_mod', &
& 'module my_mod ! A trailing comment', &
& 'use module_one', &
& 'interface', &
& ' module subroutine f()', &
Expand All @@ -320,8 +320,21 @@ subroutine test_module(error)
& 'program =1', &
& 'program (i) =1', &
& 'contains', &
& 'module procedure f()', &
& 'end procedure f', &
& 'module subroutine&', &
& ' e()', &
& 'end subroutine e', &
& 'module subroutine f()', &
& 'end subroutine f', &
& 'module function g()', &
& 'end function g', &
& 'module integer function h()', &
& 'end function h', &
& 'module real function i()', &
& 'string = " &', &
& 'module name"', &
& 'string = " &', &
& 'module name !"', &
& 'end function i', &
& 'end module test'
close(unit)

Expand Down Expand Up @@ -712,7 +725,7 @@ subroutine test_invalid_module(error)

open(file=temp_file, newunit=unit)
write(unit, '(a)') &
& 'module :: my_mod', &
& 'module ::my_mod', &
& 'end module test'
close(unit)

Expand All @@ -721,8 +734,6 @@ subroutine test_invalid_module(error)
return
end if

write(*,*) '"',f_source%modules_used(1)%s,'"'

end subroutine test_invalid_module


Expand Down