Skip to content

Commit 494564a

Browse files
committed
new test: package depends on empty library
1 parent f434cb0 commit 494564a

File tree

4 files changed

+60
-24
lines changed

4 files changed

+60
-24
lines changed
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
name = "shared_lib_empty"
2+
library.type="shared"
3+
[dependencies]
4+
shared_lib = { path = "../shared_lib" }
5+
shared_app_only = { path = "../shared_app_only" }

example_packages/static_app_only/fpm.toml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
# App only, use shared lib from other folder
2-
name = "shared_app_only"
2+
name = "static_app_only"
33
library.type="static"
44
install.library=true
55
[dependencies]

src/fpm_model.f90

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -174,6 +174,9 @@ module fpm_model
174174

175175
contains
176176

177+
!> Check if a package will create a library
178+
procedure :: has_library => package_has_library
179+
177180
!> Serialization interface
178181
procedure :: serializable_is_same => package_is_same
179182
procedure :: dump_to_toml => package_dump_to_toml
@@ -1153,6 +1156,7 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
11531156
integer :: id,ndep,i
11541157
logical :: no_root
11551158
integer, allocatable :: sorted_package_IDs(:)
1159+
logical, allocatable :: empty_package(:)
11561160
type(string_t), allocatable :: package_deps(:)
11571161

11581162
! Get dependency ID of this target
@@ -1184,6 +1188,14 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
11841188
ndep = size(sorted_package_IDs)
11851189
endif
11861190

1191+
! Exclusion of package IDs marked "empty" (i.e. they contain no sources)
1192+
empty_package = .not.model%packages%has_library()
1193+
1194+
if (any(empty_package)) then
1195+
sorted_package_IDs = pack(sorted_package_IDs, .not.empty_package(sorted_package_IDs))
1196+
ndep = size(sorted_package_IDs)
1197+
end if
1198+
11871199
package_deps = [(string_t(model%deps%dep(sorted_package_IDs(i))%name),i=1,ndep)]
11881200

11891201
r = model%compiler%enumerate_libraries(prefix, package_deps)
@@ -1193,4 +1205,17 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
11931205

11941206
end function get_package_libraries_link
11951207

1208+
!> Check whether a package has an object library
1209+
elemental logical function package_has_library(self) result(has_library)
1210+
class(package_t), intent(in) :: self
1211+
1212+
if (allocated(self%sources)) then
1213+
has_library = any(self%sources%unit_scope==FPM_SCOPE_LIB)
1214+
else
1215+
has_library = .false.
1216+
end if
1217+
1218+
end function package_has_library
1219+
1220+
11961221
end module fpm_model

src/fpm_targets.f90

Lines changed: 29 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -270,7 +270,7 @@ subroutine targets_from_sources(targets,model,prune,library,error)
270270
should_prune = prune
271271
if (present(library)) should_prune = should_prune .and. library%monolithic()
272272

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)
274274

275275
call resolve_target_linking(targets,model,library,error)
276276
if (allocated(error)) return
@@ -321,9 +321,7 @@ subroutine build_target_list(targets,model,library)
321321

322322
if (n_source < 1) return
323323

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())
327325

328326
if (with_lib .and. present(library)) then
329327
shared_lib = library%shared()
@@ -737,13 +735,16 @@ end function find_module_dependency
737735

738736

739737
!> 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)
741739

742740
!> Build target list to prune
743741
type(build_target_ptr), intent(inout), allocatable :: targets(:)
744742

745743
!> Name of root package
746744
character(*), intent(in) :: root_package
745+
746+
!> Whether unused objects should be pruned
747+
logical, intent(in) :: prune_unused_objects
747748

748749
integer :: i, j, nexec
749750
type(string_t), allocatable :: modules_used(:)
@@ -805,8 +806,8 @@ subroutine prune_build_targets(targets, root_package)
805806
if (allocated(target%source)) then
806807
if (target%source%unit_type == FPM_UNIT_MODULE) then
807808

808-
exclude_target(i) = .true.
809-
target%skip = .true.
809+
exclude_target(i) = prune_unused_objects
810+
target%skip = prune_unused_objects
810811

811812
do j=1,size(target%source%modules_provided)
812813

@@ -822,8 +823,8 @@ subroutine prune_build_targets(targets, root_package)
822823
elseif (target%source%unit_type == FPM_UNIT_SUBMODULE) then
823824
! Remove submodules if their parents are not used
824825

825-
exclude_target(i) = .true.
826-
target%skip = .true.
826+
exclude_target(i) = prune_unused_objects
827+
target%skip = prune_unused_objects
827828
do j=1,size(target%source%parent_modules)
828829

829830
if (target%source%parent_modules(j)%s .in. modules_used) then
@@ -858,27 +859,32 @@ subroutine prune_build_targets(targets, root_package)
858859

859860
targets = pack(targets,.not.exclude_target)
860861

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
864867

865-
allocate(exclude_from_archive(size(archive%dependencies)))
866-
exclude_from_archive(:) = .false.
868+
allocate(exclude_from_archive(size(archive%dependencies)),source=.false.)
867869

868-
do i=1,size(archive%dependencies)
870+
do i=1,size(archive%dependencies)
869871

870-
if (archive%dependencies(i)%ptr%skip) then
872+
if (archive%dependencies(i)%ptr%skip) then
871873

872-
exclude_from_archive(i) = .true.
874+
exclude_from_archive(i) = .true.
873875

874-
end if
876+
end if
875877

876-
end do
878+
end do
877879

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
879885

880886
end associate
881-
end if
887+
end do
882888

883889
contains
884890

@@ -1106,8 +1112,8 @@ subroutine resolve_target_linking(targets, model, library, error)
11061112
has_self_lib = .false.
11071113
find_self: do j=1,size(targets)
11081114
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
11111117
has_self_lib = .true.
11121118
exit find_self
11131119
end if

0 commit comments

Comments
 (0)