Skip to content

Commit e08b64a

Browse files
committed
Fix: issue with pruning of non-module dependencies
Make sure to always enumerate used modules from non-module sources because these can't be pruned. Adds unit test for this case.
1 parent b0c855d commit e08b64a

File tree

2 files changed

+82
-3
lines changed

2 files changed

+82
-3
lines changed

src/fpm_targets.f90

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -486,14 +486,22 @@ subroutine prune_build_targets(targets, root_package)
486486
nexec = 0
487487
allocate(modules_used(0))
488488

489-
! Enumerate modules used by executables and their dependencies
489+
! Enumerate modules used by executables, non-module subprograms and their dependencies
490490
do i=1,size(targets)
491491

492492
if (targets(i)%ptr%target_type == FPM_TARGET_EXECUTABLE) then
493493

494494
nexec = nexec + 1
495495
call collect_used_modules(targets(i)%ptr)
496496

497+
elseif (allocated(targets(i)%ptr%source)) then
498+
499+
if (targets(i)%ptr%source%unit_type == FPM_UNIT_SUBPROGRAM) then
500+
501+
call collect_used_modules(targets(i)%ptr)
502+
503+
end if
504+
497505
end if
498506

499507
end do

test/fpm_test/test_module_dependencies.f90

Lines changed: 73 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,9 @@ subroutine collect_module_dependencies(testsuite)
5353
& new_unittest("invalid-subdirectory-module-use", &
5454
test_invalid_subdirectory_module_use, should_fail=.true.), &
5555
& new_unittest("tree-shake-module", &
56-
test_tree_shake_module, should_fail=.false.) &
56+
test_tree_shake_module, should_fail=.false.), &
57+
& new_unittest("tree-shake-subprogram-with-module", &
58+
test_tree_shake_subprogram_with_module, should_fail=.false.) &
5759
]
5860

5961
end subroutine collect_module_dependencies
@@ -534,7 +536,7 @@ subroutine test_tree_shake_module(error)
534536
if (allocated(error)) return
535537

536538
if (size(targets) /= 5) then
537-
call test_failed(error,scope_str//'Incorrect number of targets - expecting three')
539+
call test_failed(error,scope_str//'Incorrect number of targets - expecting five')
538540
return
539541
end if
540542

@@ -568,6 +570,75 @@ subroutine test_tree_shake_module(error)
568570
end subroutine test_tree_shake_module
569571

570572

573+
!> Check tree-shaking of modules used via a subprogram source
574+
!> (Subprogram type is a source containing any non-module subroutines/functions)
575+
!> Subprograms cannot be pruned, so neither can their dependencies
576+
subroutine test_tree_shake_subprogram_with_module(error)
577+
578+
!> Error handling
579+
type(error_t), allocatable, intent(out) :: error
580+
581+
type(fpm_model_t) :: model
582+
type(build_target_ptr), allocatable :: targets(:)
583+
character(:), allocatable :: scope_str
584+
585+
allocate(model%external_modules(0))
586+
allocate(model%packages(1))
587+
allocate(model%packages(1)%sources(4))
588+
589+
model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", &
590+
scope = FPM_SCOPE_LIB, &
591+
provides=[string_t('my_mod_1')]) ! used via subprogram
592+
593+
model%packages(1)%sources(2) = new_test_source(FPM_UNIT_SUBPROGRAM,file_name="src/my_subprogram.f90", &
594+
scope = FPM_SCOPE_LIB, &
595+
uses=[string_t('my_mod_1')]) ! subprogram (never pruned)
596+
597+
model%packages(1)%sources(3) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_3.f90", &
598+
scope = FPM_SCOPE_LIB, &
599+
provides=[string_t('my_mod_3')]) ! unused module
600+
601+
model%packages(1)%sources(4) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", &
602+
scope=FPM_SCOPE_APP)
603+
604+
call targets_from_sources(targets,model,prune=.true.,error=error)
605+
if (allocated(error)) return
606+
607+
if (size(targets) /= 5) then
608+
call test_failed(error,scope_str//'Incorrect number of targets - expecting five')
609+
return
610+
end if
611+
612+
call check_target(targets(1)%ptr,type=FPM_TARGET_ARCHIVE,n_depends=2, &
613+
deps=[targets(2)], &
614+
links=[targets(2),targets(3)],error=error)
615+
616+
if (allocated(error)) return
617+
618+
call check_target(targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
619+
source=model%packages(1)%sources(1),error=error)
620+
621+
if (allocated(error)) return
622+
623+
call check_target(targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
624+
deps=[targets(2)],source=model%packages(1)%sources(2),error=error)
625+
626+
if (allocated(error)) return
627+
628+
call check_target(targets(4)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
629+
source=model%packages(1)%sources(4),error=error)
630+
631+
if (allocated(error)) return
632+
633+
call check_target(targets(5)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=2, &
634+
deps=[targets(1),targets(4)], &
635+
links=[targets(4)], error=error)
636+
637+
if (allocated(error)) return
638+
639+
end subroutine test_tree_shake_subprogram_with_module
640+
641+
571642
!> Check program using a non-library module in a differente sub-directory
572643
subroutine test_invalid_subdirectory_module_use(error)
573644

0 commit comments

Comments
 (0)