@@ -270,7 +270,7 @@ subroutine targets_from_sources(targets,model,prune,library,error)
270
270
should_prune = prune
271
271
if (present (library)) should_prune = should_prune .and. library% monolithic()
272
272
273
- if (should_prune) call prune_build_targets(targets,root_package = model% package_name)
273
+ call prune_build_targets(targets,model% package_name,should_prune )
274
274
275
275
call resolve_target_linking(targets,model,library,error)
276
276
if (allocated (error)) return
@@ -321,9 +321,7 @@ subroutine build_target_list(targets,model,library)
321
321
322
322
if (n_source < 1 ) return
323
323
324
- with_lib = any ([((model% packages(j)% sources(i)% unit_scope == FPM_SCOPE_LIB, &
325
- i= 1 ,size (model% packages(j)% sources)), &
326
- j= 1 ,size (model% packages))])
324
+ with_lib = any (model% packages% has_library())
327
325
328
326
if (with_lib .and. present (library)) then
329
327
shared_lib = library% shared()
@@ -737,13 +735,16 @@ end function find_module_dependency
737
735
738
736
739
737
! > Perform tree-shaking to remove unused module targets
740
- subroutine prune_build_targets (targets , root_package )
738
+ subroutine prune_build_targets (targets , root_package , prune_unused_objects )
741
739
742
740
! > Build target list to prune
743
741
type (build_target_ptr), intent (inout ), allocatable :: targets(:)
744
742
745
743
! > Name of root package
746
744
character (* ), intent (in ) :: root_package
745
+
746
+ ! > Whether unused objects should be pruned
747
+ logical , intent (in ) :: prune_unused_objects
747
748
748
749
integer :: i, j, nexec
749
750
type (string_t), allocatable :: modules_used(:)
@@ -805,8 +806,8 @@ subroutine prune_build_targets(targets, root_package)
805
806
if (allocated (target % source)) then
806
807
if (target % source% unit_type == FPM_UNIT_MODULE) then
807
808
808
- exclude_target(i) = .true.
809
- target % skip = .true.
809
+ exclude_target(i) = prune_unused_objects
810
+ target % skip = prune_unused_objects
810
811
811
812
do j= 1 ,size (target % source% modules_provided)
812
813
@@ -822,8 +823,8 @@ subroutine prune_build_targets(targets, root_package)
822
823
elseif (target % source% unit_type == FPM_UNIT_SUBMODULE) then
823
824
! Remove submodules if their parents are not used
824
825
825
- exclude_target(i) = .true.
826
- target % skip = .true.
826
+ exclude_target(i) = prune_unused_objects
827
+ target % skip = prune_unused_objects
827
828
do j= 1 ,size (target % source% parent_modules)
828
829
829
830
if (target % source% parent_modules(j)% s .in . modules_used) then
@@ -858,27 +859,32 @@ subroutine prune_build_targets(targets, root_package)
858
859
859
860
targets = pack (targets,.not. exclude_target)
860
861
861
- ! Remove unused targets from archive dependency list
862
- if (targets(1 )% ptr% target_type == FPM_TARGET_ARCHIVE) then
863
- associate(archive= >targets(1 )% ptr)
862
+ ! Remove unused targets from library dependency list
863
+ do j= 1 ,size (targets)
864
+ associate(archive= >targets(j)% ptr)
865
+
866
+ if (any (archive% target_type==[FPM_TARGET_ARCHIVE,FPM_TARGET_OBJECT])) then
864
867
865
- allocate (exclude_from_archive(size (archive% dependencies)))
866
- exclude_from_archive(:) = .false.
868
+ allocate (exclude_from_archive(size (archive% dependencies)),source= .false. )
867
869
868
- do i= 1 ,size (archive% dependencies)
870
+ do i= 1 ,size (archive% dependencies)
869
871
870
- if (archive% dependencies(i)% ptr% skip) then
872
+ if (archive% dependencies(i)% ptr% skip) then
871
873
872
- exclude_from_archive(i) = .true.
874
+ exclude_from_archive(i) = .true.
873
875
874
- end if
876
+ end if
875
877
876
- end do
878
+ end do
877
879
878
- archive% dependencies = pack (archive% dependencies,.not. exclude_from_archive)
880
+ archive% dependencies = pack (archive% dependencies,.not. exclude_from_archive)
881
+
882
+ deallocate (exclude_from_archive)
883
+
884
+ endif
879
885
880
886
end associate
881
- end if
887
+ end do
882
888
883
889
contains
884
890
@@ -1106,8 +1112,8 @@ subroutine resolve_target_linking(targets, model, library, error)
1106
1112
has_self_lib = .false.
1107
1113
find_self: do j= 1 ,size (targets)
1108
1114
associate(target_loop= >targets(j)% ptr)
1109
- if (target_loop% target_type== FPM_TARGET_SHARED .and. &
1110
- target_loop% package_name== target % package_name) then
1115
+ if (any ( target_loop% target_type==[ FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE]) &
1116
+ .and. target_loop% package_name== target % package_name) then
1111
1117
has_self_lib = .true.
1112
1118
exit find_self
1113
1119
end if
0 commit comments