Skip to content
Merged
27 changes: 27 additions & 0 deletions ci/run_tests.bat
Original file line number Diff line number Diff line change
Expand Up @@ -41,4 +41,31 @@ if errorlevel 1 exit 1
if errorlevel 1 exit 1

.\build\gfortran_debug\test\farewell_test
if errorlevel 1 exit 1


cd ..\with_c
if errorlevel 1 exit 1

..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1

.\build\gfortran_debug\app\with_c
if errorlevel 1 exit 1


cd ..\submodules
if errorlevel 1 exit 1

..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1


cd ..\program_with_module
if errorlevel 1 exit 1

..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1

.\build\gfortran_debug\app\Program_with_module
if errorlevel 1 exit 1
13 changes: 12 additions & 1 deletion ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -17,4 +17,15 @@ cd ../hello_complex
./build/gfortran_debug/app/say_Hello
./build/gfortran_debug/app/say_goodbye
./build/gfortran_debug/test/greet_test
./build/gfortran_debug/test/farewell_test
./build/gfortran_debug/test/farewell_test

cd ../with_c
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/with_c

cd ../submodules
../../../fpm/build/gfortran_debug/app/fpm build

cd ../program_with_module
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/Program_with_module
70 changes: 54 additions & 16 deletions fpm/src/fpm_sources.f90
Original file line number Diff line number Diff line change
Expand Up @@ -310,7 +310,7 @@ function parse_f_source(f_filename,error) result(f_source)
if (.not.validate_name(mod_name)) then
call file_parse_error(error,f_filename, &
'empty or invalid name for module',i, &
file_lines(i)%s)
file_lines(i)%s, index(file_lines(i)%s,mod_name))
return
end if

Expand All @@ -327,6 +327,22 @@ function parse_f_source(f_filename,error) result(f_source)
! Extract name of submodule if is submodule
if (index(adjustl(lower(file_lines(i)%s)),'submodule') == 1) then

mod_name = split_n(file_lines(i)%s,n=3,delims='()',stat=stat)
if (stat /= 0) then
call file_parse_error(error,f_filename, &
'unable to get submodule name',i, &
file_lines(i)%s)
return
end if
if (.not.validate_name(mod_name)) then
call file_parse_error(error,f_filename, &
'empty or invalid name for submodule',i, &
file_lines(i)%s, index(file_lines(i)%s,mod_name))
return
end if

n_mod = n_mod + 1

temp_string = split_n(file_lines(i)%s,n=2,delims='()',stat=stat)
if (stat /= 0) then
call file_parse_error(error,f_filename, &
Expand All @@ -347,22 +363,24 @@ function parse_f_source(f_filename,error) result(f_source)

end if

f_source%modules_used(n_use)%s = lower(temp_string)

if (.not.validate_name(temp_string)) then
call file_parse_error(error,f_filename, &
'empty or invalid name for submodule parent',i, &
file_lines(i)%s, index(file_lines(i)%s,temp_string))
return
end if

f_source%modules_used(n_use)%s = lower(temp_string)

f_source%modules_provided(n_mod)%s = lower(mod_name)

end if

end if

! Detect if is program
if (f_source%unit_type == FPM_UNIT_UNKNOWN .and. &
index(adjustl(lower(file_lines(i)%s)),'program') == 1) then
! Detect if contains a program
! (no modules allowed after program def)
if (index(adjustl(lower(file_lines(i)%s)),'program') == 1) then

f_source%unit_type = FPM_UNIT_PROGRAM

Expand Down Expand Up @@ -526,7 +544,7 @@ function split_n(string,delims,n,stat) result(substring)
return
end if

substring = trim(string_parts(i))
substring = trim(adjustl(string_parts(i)))
stat = 0

end function split_n
Expand All @@ -538,22 +556,42 @@ subroutine resolve_module_dependencies(sources)
!
type(srcfile_t), intent(inout), target :: sources(:)

integer :: n_depend, i, j
type(srcfile_ptr) :: dep

integer :: n_depend, i, pass, j

do i=1,size(sources)

n_depend = size(sources(i)%modules_used)
do pass=1,2

n_depend = 0

do j=1,size(sources(i)%modules_used)

if (sources(i)%modules_used(j)%s .in. sources(i)%modules_provided) then
! Dependency satisfied in same file, skip
cycle
end if

allocate(sources(i)%file_dependencies(n_depend))
dep%ptr => find_module_dependency(sources,sources(i)%modules_used(j)%s)

if (.not.associated(dep%ptr)) then
write(*,*) '(!) Unable to find source for module dependency: ', &
sources(i)%modules_used(j)%s
write(*,*) ' for file ',sources(i)%file_name
! stop
end if

do j=1,n_depend
n_depend = n_depend + 1

if (pass == 2) then
sources(i)%file_dependencies(n_depend) = dep
end if

sources(i)%file_dependencies(j)%ptr => &
find_module_dependency(sources,sources(i)%modules_used(j)%s)
end do

if (.not.associated(sources(i)%file_dependencies(j)%ptr)) then
write(*,*) '(!) Unable to find source for module dependency: ',sources(i)%modules_used(j)%s
! stop
if (pass == 1) then
allocate(sources(i)%file_dependencies(n_depend))
end if

end do
Expand Down
90 changes: 82 additions & 8 deletions fpm/test/test_source_parsing.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ subroutine collect_source_parsing(testsuite)
& new_unittest("intrinsic-modules-used", test_intrinsic_modules_used), &
& new_unittest("include-stmt", test_include_stmt), &
& new_unittest("module", test_module), &
& new_unittest("program-with-module", test_program_with_module), &
& new_unittest("submodule", test_submodule), &
& new_unittest("submodule-ancestor", test_submodule_ancestor), &
& new_unittest("subprogram", test_subprogram), &
Expand Down Expand Up @@ -258,7 +259,7 @@ subroutine test_module(error)
& 'contains', &
& 'module procedure f()', &
& 'end procedure f', &
& 'end submodule test'
& 'end module test'
close(unit)

f_source = parse_f_source(temp_file,error)
Expand Down Expand Up @@ -287,13 +288,76 @@ subroutine test_module(error)
end if

if (.not.('module_one' .in. f_source%modules_used)) then
call test_failed(error,'Missing parent module in modules_used')
call test_failed(error,'Missing module in modules_used')
return
end if

end subroutine test_module


!> Try to parse combined fortran module and program
!> Check that parsed unit type is FPM_UNIT_PROGRAM
subroutine test_program_with_module(error)

!> Error handling
type(error_t), allocatable, intent(out) :: error

integer :: unit
character(:), allocatable :: temp_file
type(srcfile_t), allocatable :: f_source

allocate(temp_file, source=get_temp_filename())

open(file=temp_file, newunit=unit)
write(unit, '(a)') &
& 'module my_mod', &
& 'use module_one', &
& 'interface', &
& ' module subroutine f()', &
& 'end interface', &
& 'contains', &
& 'module procedure f()', &
& 'end procedure f', &
& 'end module test', &
& 'program my_program', &
& 'use my_mod', &
& 'implicit none', &
& 'end my_program'
close(unit)

f_source = parse_f_source(temp_file,error)
if (allocated(error)) then
return
end if

if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_PROGRAM')
return
end if

if (size(f_source%modules_provided) /= 1) then
call test_failed(error,'Unexpected modules_provided - expecting one')
return
end if

if (.not.('my_mod' .in. f_source%modules_provided)) then
call test_failed(error,'Missing module in modules_provided')
return
end if

if (.not.('module_one' .in. f_source%modules_used)) then
call test_failed(error,'Missing module in modules_used')
return
end if

if (.not.('my_mod' .in. f_source%modules_used)) then
call test_failed(error,'Missing module in modules_used')
return
end if

end subroutine test_program_with_module


!> Try to parse fortran submodule for ancestry
subroutine test_submodule(error)

Expand All @@ -308,7 +372,7 @@ subroutine test_submodule(error)

open(file=temp_file, newunit=unit)
write(unit, '(a)') &
& 'submodule (parent) :: child', &
& 'submodule (parent) child', &
& 'use module_one', &
& 'end submodule test'
close(unit)
Expand All @@ -323,8 +387,8 @@ subroutine test_submodule(error)
return
end if

if (size(f_source%modules_provided) /= 0) then
call test_failed(error,'Unexpected modules_provided - expecting zero')
if (size(f_source%modules_provided) /= 1) then
call test_failed(error,'Unexpected modules_provided - expecting one')
return
end if

Expand All @@ -333,6 +397,11 @@ subroutine test_submodule(error)
return
end if

if (.not.('child' .in. f_source%modules_provided)) then
call test_failed(error,'Missing module in modules_provided')
return
end if

if (.not.('module_one' .in. f_source%modules_used)) then
call test_failed(error,'Missing module in modules_used')
return
Expand Down Expand Up @@ -360,7 +429,7 @@ subroutine test_submodule_ancestor(error)

open(file=temp_file, newunit=unit)
write(unit, '(a)') &
& 'submodule (ancestor:parent) :: child', &
& 'submodule (ancestor:parent) child', &
& 'use module_one', &
& 'end submodule test'
close(unit)
Expand All @@ -375,8 +444,8 @@ subroutine test_submodule_ancestor(error)
return
end if

if (size(f_source%modules_provided) /= 0) then
call test_failed(error,'Unexpected modules_provided - expecting zero')
if (size(f_source%modules_provided) /= 1) then
call test_failed(error,'Unexpected modules_provided - expecting one')
return
end if

Expand All @@ -385,6 +454,11 @@ subroutine test_submodule_ancestor(error)
return
end if

if (.not.('child' .in. f_source%modules_provided)) then
call test_failed(error,'Missing module in modules_provided')
return
end if

if (.not.('module_one' .in. f_source%modules_used)) then
call test_failed(error,'Missing module in modules_used')
return
Expand Down
18 changes: 18 additions & 0 deletions test/example_packages/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
# Example packages

See the table below for a list of the example packages provided in this directory including
the features demonstrated in each package and which versions of fpm are supported.


| Name | Features | Bootstrap (Haskell) fpm | fpm |
|---------------------|---------------------------------------------------------------|:-----------------------:|:---:|
| circular_example | Local path dependency; circular dependency | Y | N |
| circular_test | Local path dependency; circular dependency | Y | N |
| hello_complex | Non-standard directory layout; multiple tests and executables | Y | Y |
| hello_fpm | App-only; local path dependency | Y | N |
| hello_world | App-only | Y | Y |
| makefile_complex | External build command (makefile); local path dependency | Y | N |
| program_with_module | App-only; module+program in single source file | Y | Y |
| submodules | Lib-only; submodules (3 levels) | N | Y |
| with_c | Compile with `c` source files | N | Y |
| with_makefile | External build command (makefile) | Y | N |
10 changes: 10 additions & 0 deletions test/example_packages/program_with_module/app/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module greet_m
implicit none
character(*), parameter :: greeting = 'Hello, fpm!'
end module greet_m

program program_with_module
use greet_m, only: greeting
implicit none
print *, greeting
end program program_with_module
1 change: 1 addition & 0 deletions test/example_packages/program_with_module/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "Program_with_module"
1 change: 1 addition & 0 deletions test/example_packages/submodules/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "submodules"
16 changes: 16 additions & 0 deletions test/example_packages/submodules/src/child1.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
submodule(parent) child1
implicit none

interface
module function my_fun() result (b)
integer :: b
end function my_fun
end interface

contains

module procedure my_sub1
a = 1
end procedure my_sub1

end submodule child1
10 changes: 10 additions & 0 deletions test/example_packages/submodules/src/child2.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
submodule(parent) child2
implicit none

contains

module procedure my_sub2
a = 2
end procedure my_sub2

end submodule child2
Loading