Skip to content

Commit 6e43cdb

Browse files
authored
Merge pull request #704 from LKedward/fix-submodule-shaking
Fix submodule shaking
2 parents cb75386 + 3a6cd7f commit 6e43cdb

File tree

4 files changed

+20
-19
lines changed

4 files changed

+20
-19
lines changed

ci/run_tests.sh

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -76,8 +76,6 @@ test ! -e ./build/gfortran_*/submodule_tree_shake/src_parent_unused.f90.o
7676
test ! -e ./build/gfortran_*/submodule_tree_shake/src_parent_unused.f90.o.log
7777
test ! -e ./build/gfortran_*/submodule_tree_shake/src_child_unused.f90.o
7878
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
8179
popd
8280

8381
pushd version_file

example_packages/submodule_tree_shake/src/child1.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ end function my_fun
1010
contains
1111

1212
module procedure my_sub1
13-
a = 1
13+
a = my_fun()
1414
end procedure my_sub1
1515

1616
end submodule child1

src/fpm_source_parsing.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -614,6 +614,7 @@ function parse_sequence(string,t1,t2,t3,t4) result(found)
614614
select case(token_n)
615615
case(1)
616616
incr = len(t1)
617+
if (pos+incr-1>n) return
617618
match = string(pos:pos+incr-1) == t1
618619
case(2)
619620
if (.not.present(t2)) exit

src/fpm_targets.f90

Lines changed: 18 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -615,25 +615,27 @@ recursive subroutine collect_used_modules(target)
615615
end if
616616

617617
if (allocated(target%source)) then
618-
do j=1,size(target%source%modules_used)
619-
620-
if (.not.(target%source%modules_used(j)%s .in. modules_used)) then
621-
622-
modules_used = [modules_used, target%source%modules_used(j)]
623-
624-
! Recurse into child submodules
625-
do k=1,size(targets)
626-
if (allocated(targets(k)%ptr%source)) then
627-
if (targets(k)%ptr%source%unit_type == FPM_UNIT_SUBMODULE) then
628-
if (target%source%modules_used(j)%s .in. targets(k)%ptr%source%parent_modules) then
629-
call collect_used_modules(targets(k)%ptr)
630-
end if
631-
end if
632-
end if
633-
end do
618+
619+
! Add modules from this target and from any of it's children submodules
620+
do j=1,size(target%source%modules_provided)
621+
622+
if (.not.(target%source%modules_provided(j)%s .in. modules_used)) then
623+
624+
modules_used = [modules_used, target%source%modules_provided(j)]
634625

635626
end if
636627

628+
! Recurse into child submodules
629+
do k=1,size(targets)
630+
if (allocated(targets(k)%ptr%source)) then
631+
if (targets(k)%ptr%source%unit_type == FPM_UNIT_SUBMODULE) then
632+
if (target%source%modules_provided(j)%s .in. targets(k)%ptr%source%parent_modules) then
633+
call collect_used_modules(targets(k)%ptr)
634+
end if
635+
end if
636+
end if
637+
end do
638+
637639
end do
638640
end if
639641

0 commit comments

Comments
 (0)