Skip to content

Commit cb75386

Browse files
authored
Merge pull request #676 from LKedward/tree-shaking
Tree shaking for modules
2 parents 7734124 + 13f9c85 commit cb75386

28 files changed

+1009
-66
lines changed

ci/run_tests.sh

+18
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,24 @@ test ! -x ./build/gfortran_*/app/unused
6262
test ! -x ./build/gfortran_*/test/unused_test
6363
popd
6464

65+
pushd tree_shake
66+
"$fpm" build
67+
"$fpm" run
68+
"$fpm" test
69+
test ! -e ./build/gfortran_*/tree_shake/src_farewell_m.f90.o
70+
test ! -e ./build/gfortran_*/tree_shake/src_farewell_m.f90.o.log
71+
popd
72+
73+
pushd submodule_tree_shake
74+
"$fpm" run
75+
test ! -e ./build/gfortran_*/submodule_tree_shake/src_parent_unused.f90.o
76+
test ! -e ./build/gfortran_*/submodule_tree_shake/src_parent_unused.f90.o.log
77+
test ! -e ./build/gfortran_*/submodule_tree_shake/src_child_unused.f90.o
78+
test ! -e ./build/gfortran_*/submodule_tree_shake/src_child_unused.f90.o.log
79+
test ! -e ./build/gfortran_*/submodule_tree_shake/src_grandchild.f90.o
80+
test ! -e ./build/gfortran_*/submodule_tree_shake/src_grandchild.f90.o.log
81+
popd
82+
6583
pushd version_file
6684
"$fpm" build
6785
"$fpm" run

example_packages/README.md

+2
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,8 @@ the features demonstrated in each package and which versions of fpm are supporte
2020
| makefile_complex | External build command (makefile); local path dependency | Y | N |
2121
| program_with_module | App-only; module+program in single source file | Y | Y |
2222
| submodules | Lib-only; submodules (3 levels) | N | Y |
23+
| tree_shake | Test tree-shaking/pruning of unused module dependencies | N | Y |
24+
| submodule_tree_shake| Test tree-shaking/pruning with submodules dependencies | N | Y |
2325
| link_external | Link external library | N | Y |
2426
| link_executable | Link external library to a single executable | N | Y |
2527
| version_file | Read version number from a file in the project root | N | Y |
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
build/*
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
program test
2+
use parent
3+
4+
integer :: a, b
5+
6+
call my_sub1(a)
7+
call my_sub2(b)
8+
9+
end program test
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
name = "submodule_tree_shake"
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
submodule(parent) child1
2+
implicit none
3+
4+
interface
5+
module function my_fun() result (b)
6+
integer :: b
7+
end function my_fun
8+
end interface
9+
10+
contains
11+
12+
module procedure my_sub1
13+
a = 1
14+
end procedure my_sub1
15+
16+
end submodule child1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
submodule(parent) child2
2+
implicit none
3+
4+
contains
5+
6+
module procedure my_sub2
7+
a = 2
8+
end procedure my_sub2
9+
10+
end submodule child2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
submodule(parent_unused) child_unused
2+
implicit none
3+
4+
contains
5+
6+
module procedure unused_sub
7+
a = 1
8+
end procedure unused_sub
9+
10+
end submodule child_unused
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
submodule(parent:child1) grandchild
2+
implicit none
3+
4+
contains
5+
6+
module procedure my_fun
7+
b = 2
8+
end procedure my_fun
9+
10+
end submodule grandchild
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
module parent
2+
implicit none
3+
4+
interface
5+
6+
module subroutine my_sub1(a)
7+
integer, intent(out) :: a
8+
end subroutine my_sub1
9+
10+
module subroutine my_sub2(a)
11+
integer, intent(out) :: a
12+
end subroutine my_sub2
13+
end interface
14+
15+
end module parent
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
module parent_unused
2+
implicit none
3+
4+
interface
5+
6+
module subroutine unused_sub(a)
7+
integer, intent(out) :: a
8+
end subroutine unused_sub
9+
10+
end interface
11+
12+
end module parent_unused
+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
build/*
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
program say_Hello
2+
use greet_m, only: make_greeting
3+
4+
implicit none
5+
6+
interface
7+
function external_function() result(i)
8+
integer :: i
9+
end function external_function
10+
end interface
11+
12+
print *, make_greeting("World")
13+
print *, external_function()
14+
15+
end program say_Hello

example_packages/tree_shake/fpm.toml

+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
name = "tree_shake"
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
! This module is not used by any other sources,
2+
! however because it also contains an external function
3+
! it cannot be dropped during tree-shaking/pruning
4+
module extra_m
5+
use subdir_constants, only: FAREWELL_STR
6+
implicit none
7+
private
8+
9+
integer, parameter :: m = 0
10+
end
11+
12+
function external_function() result(i)
13+
integer :: i
14+
i = 1
15+
end function external_function
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
! This module is not used by any other sources
2+
! and only contains a module (no non-module subprograms),
3+
! therefore it should be dropped during tree-shaking/pruning
4+
module farewell_m
5+
use subdir_constants, only: FAREWELL_STR
6+
implicit none
7+
private
8+
9+
public :: make_farewell
10+
contains
11+
function make_farewell(name) result(greeting)
12+
character(len=*), intent(in) :: name
13+
character(len=:), allocatable :: greeting
14+
15+
greeting = FAREWELL_STR // name // "!"
16+
end function make_farewell
17+
end module farewell_m
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
! This module is directly by the executables and
2+
! hence should not be dropped during tree-shaking/pruning
3+
module greet_m
4+
use subdir_constants, only: GREET_STR
5+
implicit none
6+
private
7+
8+
public :: make_greeting
9+
contains
10+
function make_greeting(name) result(greeting)
11+
character(len=*), intent(in) :: name
12+
character(len=:), allocatable :: greeting
13+
14+
greeting = GREET_STR // name // "!"
15+
end function make_greeting
16+
end module greet_m
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
! This module is used indirectly by the executables
2+
! and hence should not be dropped during tree-shaking/pruning
3+
module subdir_constants
4+
implicit none
5+
6+
character(*), parameter :: GREET_STR = 'Hello, '
7+
character(*), parameter :: FAREWELL_STR = 'Goodbye, '
8+
9+
end module subdir_constants
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
program greet_test
2+
use greet_m, only: make_greeting
3+
use iso_fortran_env, only: error_unit, output_unit
4+
5+
implicit none
6+
7+
character(len=:), allocatable :: greeting
8+
9+
allocate(character(len=0) :: greeting)
10+
greeting = make_greeting("World")
11+
12+
if (greeting == "Hello, World!") then
13+
write(output_unit, *) "Passed"
14+
else
15+
write(error_unit, *) "Failed"
16+
call exit(1)
17+
end if
18+
end program greet_test

src/fpm.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -278,7 +278,7 @@ subroutine cmd_build(settings)
278278
call fpm_stop(1,'*cmd_build*:model error:'//error%message)
279279
end if
280280

281-
call targets_from_sources(targets, model, error)
281+
call targets_from_sources(targets, model, settings%prune, error)
282282
if (allocated(error)) then
283283
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
284284
end if
@@ -324,7 +324,7 @@ subroutine cmd_run(settings,test)
324324
call fpm_stop(1, '*cmd_run*:model error:'//error%message)
325325
end if
326326

327-
call targets_from_sources(targets, model, error)
327+
call targets_from_sources(targets, model, settings%prune, error)
328328
if (allocated(error)) then
329329
call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
330330
end if

src/fpm/cmd/install.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ subroutine cmd_install(settings)
3838
call build_model(model, settings%fpm_build_settings, package, error)
3939
call handle_error(error)
4040

41-
call targets_from_sources(targets, model, error)
41+
call targets_from_sources(targets, model, settings%prune, error)
4242
call handle_error(error)
4343

4444
installable = (allocated(package%library) .and. package%install%library) &

0 commit comments

Comments
 (0)