Skip to content

Commit 219c98c

Browse files
committed
Add: tree-shaking/pruning of unused modules
1 parent 17ac86b commit 219c98c

File tree

2 files changed

+129
-1
lines changed

2 files changed

+129
-1
lines changed

src/fpm_source_parsing.f90

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -248,7 +248,14 @@ function parse_f_source(f_filename,error) result(f_source)
248248
f_source%unit_type = FPM_UNIT_MODULE
249249
end if
250250

251-
inside_module = .true.
251+
if (.not.inside_module) then
252+
inside_module = .true.
253+
else
254+
! Must have missed an end module statement (can't assume a pure module)
255+
if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
256+
f_source%unit_type = FPM_UNIT_SUBPROGRAM
257+
end if
258+
end if
252259

253260
cycle
254261

@@ -362,6 +369,12 @@ function parse_f_source(f_filename,error) result(f_source)
362369

363370
end do file_loop
364371

372+
! If unable to parse end of module statement, then can't assume pure module
373+
! (there could be non-module subprograms present)
374+
if (inside_module .and. f_source%unit_type == FPM_UNIT_MODULE) then
375+
f_source%unit_type = FPM_UNIT_SUBPROGRAM
376+
end if
377+
365378
if (pass == 1) then
366379
allocate(f_source%modules_used(n_use))
367380
allocate(f_source%include_dependencies(n_include))

src/fpm_targets.f90

Lines changed: 115 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -136,6 +136,8 @@ subroutine targets_from_sources(targets,model,error)
136136
call resolve_module_dependencies(targets,model%external_modules,error)
137137
if (allocated(error)) return
138138

139+
call prune_build_targets(targets)
140+
139141
call resolve_target_linking(targets,model)
140142

141143
end subroutine targets_from_sources
@@ -453,6 +455,119 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
453455
end function find_module_dependency
454456

455457

458+
!> Perform tree-shaking to remove unused module targets
459+
subroutine prune_build_targets(targets)
460+
type(build_target_ptr), intent(inout), allocatable :: targets(:)
461+
462+
integer :: i, j, nexec
463+
type(string_t), allocatable :: modules_used(:)
464+
logical :: exclude_target(size(targets))
465+
logical, allocatable :: exclude_from_archive(:)
466+
467+
nexec = 0
468+
allocate(modules_used(0))
469+
470+
! Enumerate modules used by executables and their dependencies
471+
do i=1,size(targets)
472+
473+
if (targets(i)%ptr%target_type == FPM_TARGET_EXECUTABLE) then
474+
475+
nexec = nexec + 1
476+
call collect_used_modules(targets(i)%ptr)
477+
478+
end if
479+
480+
end do
481+
482+
! Can't prune targets without executables
483+
! (everything will be built)
484+
if (nexec < 1) then
485+
return
486+
end if
487+
488+
exclude_target(:) = .false.
489+
490+
! Exclude purely module targets if they are not used anywhere
491+
do i=1,size(targets)
492+
associate(target=>targets(i)%ptr)
493+
494+
if (allocated(target%source)) then
495+
if (target%source%unit_type == FPM_UNIT_MODULE) then
496+
497+
exclude_target(i) = .true.
498+
target%skip = .true.
499+
500+
do j=1,size(target%source%modules_provided)
501+
502+
if (target%source%modules_provided(j)%s .in. modules_used) then
503+
504+
exclude_target(i) = .false.
505+
target%skip = .false.
506+
507+
end if
508+
509+
end do
510+
511+
end if
512+
end if
513+
514+
end associate
515+
end do
516+
517+
targets = pack(targets,.not.exclude_target)
518+
519+
! Remove unused targets from archive dependency list
520+
if (targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
521+
associate(archive=>targets(1)%ptr)
522+
523+
allocate(exclude_from_archive(size(archive%dependencies)))
524+
exclude_from_archive(:) = .false.
525+
526+
do i=1,size(archive%dependencies)
527+
528+
if (archive%dependencies(i)%ptr%skip) then
529+
530+
exclude_from_archive(i) = .true.
531+
532+
end if
533+
534+
end do
535+
536+
archive%dependencies = pack(archive%dependencies,.not.exclude_from_archive)
537+
538+
end associate
539+
end if
540+
541+
contains
542+
543+
recursive subroutine collect_used_modules(target)
544+
type(build_target_t), intent(in) :: target
545+
546+
integer :: j
547+
548+
if (allocated(target%source)) then
549+
do j=1,size(target%source%modules_used)
550+
551+
if (.not.(target%source%modules_used(j)%s .in. modules_used)) then
552+
553+
modules_used = [modules_used, target%source%modules_used(j)]
554+
555+
end if
556+
557+
end do
558+
end if
559+
560+
do j=1,size(target%dependencies)
561+
562+
call collect_used_modules(target%dependencies(j)%ptr)
563+
564+
end do
565+
566+
end subroutine collect_used_modules
567+
568+
end subroutine prune_build_targets
569+
570+
456571
!> Construct the linker flags string for each target
457572
!> `target%link_flags` includes non-library objects and library flags
458573
!>

0 commit comments

Comments
 (0)