Skip to content

Commit e6688d0

Browse files
authored
Merge pull request #490 from LKedward/fix-module-parsing
Fix module parsing
2 parents 2ba3478 + 302782c commit e6688d0

File tree

2 files changed

+34
-20
lines changed

2 files changed

+34
-20
lines changed

src/fpm_source_parsing.f90

Lines changed: 17 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ function parse_f_source(f_filename,error) result(f_source)
7979
integer :: stat
8080
integer :: fh, n_use, n_include, n_mod, i, j, ic, pass
8181
type(string_t), allocatable :: file_lines(:)
82-
character(:), allocatable :: temp_string, mod_name
82+
character(:), allocatable :: temp_string, mod_name, string_parts(:)
8383

8484
f_source%file_name = f_filename
8585

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

194-
mod_name = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat))
195-
if (stat /= 0) then
196-
call file_parse_error(error,f_filename, &
197-
'unable to find module name',i, &
198-
file_lines(i)%s)
199-
return
194+
! Remove any trailing comments
195+
ic = index(file_lines(i)%s,'!')-1
196+
if (ic < 1) then
197+
ic = len(file_lines(i)%s)
198+
end if
199+
temp_string = trim(file_lines(i)%s(1:ic))
200+
201+
! R1405 module-stmt := "MODULE" module-name
202+
! module-stmt has two space-delimited parts only
203+
! (no line continuations)
204+
call split(temp_string,string_parts,' ')
205+
if (size(string_parts) /= 2) then
206+
cycle
200207
end if
201208

202-
if (mod_name == 'procedure' .or. &
203-
mod_name == 'subroutine' .or. &
204-
mod_name == 'function' .or. &
205-
scan(mod_name,'=(')>0 ) then
209+
mod_name = lower(trim(adjustl(string_parts(2))))
210+
if (scan(mod_name,'=(&')>0 ) then
206211
! Ignore these cases:
207-
! module procedure *
208-
! module function *
209-
! module subroutine *
212+
! module <something>&
210213
! module =*
211214
! module (i)
212215
cycle

test/fpm_test/test_source_parsing.f90

Lines changed: 17 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -309,7 +309,7 @@ subroutine test_module(error)
309309

310310
open(file=temp_file, newunit=unit)
311311
write(unit, '(a)') &
312-
& 'module my_mod', &
312+
& 'module my_mod ! A trailing comment', &
313313
& 'use module_one', &
314314
& 'interface', &
315315
& ' module subroutine f()', &
@@ -320,8 +320,21 @@ subroutine test_module(error)
320320
& 'program =1', &
321321
& 'program (i) =1', &
322322
& 'contains', &
323-
& 'module procedure f()', &
324-
& 'end procedure f', &
323+
& 'module subroutine&', &
324+
& ' e()', &
325+
& 'end subroutine e', &
326+
& 'module subroutine f()', &
327+
& 'end subroutine f', &
328+
& 'module function g()', &
329+
& 'end function g', &
330+
& 'module integer function h()', &
331+
& 'end function h', &
332+
& 'module real function i()', &
333+
& 'string = " &', &
334+
& 'module name"', &
335+
& 'string = " &', &
336+
& 'module name !"', &
337+
& 'end function i', &
325338
& 'end module test'
326339
close(unit)
327340

@@ -712,7 +725,7 @@ subroutine test_invalid_module(error)
712725

713726
open(file=temp_file, newunit=unit)
714727
write(unit, '(a)') &
715-
& 'module :: my_mod', &
728+
& 'module ::my_mod', &
716729
& 'end module test'
717730
close(unit)
718731

@@ -721,8 +734,6 @@ subroutine test_invalid_module(error)
721734
return
722735
end if
723736

724-
write(*,*) '"',f_source%modules_used(1)%s,'"'
725-
726737
end subroutine test_invalid_module
727738

728739

0 commit comments

Comments
 (0)