Skip to content

Commit d00e314

Browse files
committed
add test: enforce dependency ID on pruned empty targets
1 parent 494564a commit d00e314

File tree

5 files changed

+150
-52
lines changed

5 files changed

+150
-52
lines changed

ci/run_tests.sh

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -321,6 +321,18 @@ pushd shared_lib_extra
321321
test $EXIT_CODE -eq 0
322322
popd
323323

324+
pushd shared_lib_empty
325+
"$fpm" build
326+
"$fpm" run
327+
"$fpm" test
328+
popd
329+
330+
pushd static_lib_empty
331+
"$fpm" build
332+
"$fpm" run
333+
"$fpm" test
334+
popd
335+
324336
pushd shared_app_only
325337
"$fpm" test || EXIT_CODE=$?
326338
test $EXIT_CODE -eq 0

example_packages/static_app_only/fpm.toml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
# App only, use shared lib from other folder
1+
# App only, use shared libs from other folder, no provided sources
22
name = "static_app_only"
33
library.type="static"
44
install.library=true
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
name = "static_lib_empty"
2+
library.type="static"
3+
[dependencies]
4+
shared_lib = { path = "../shared_lib" }
5+
shared_app_only = { path = "../shared_app_only" }

src/fpm_model.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1156,7 +1156,7 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
11561156
integer :: id,ndep,i
11571157
logical :: no_root
11581158
integer, allocatable :: sorted_package_IDs(:)
1159-
logical, allocatable :: empty_package(:)
1159+
logical, allocatable :: has_lib(:)
11601160
type(string_t), allocatable :: package_deps(:)
11611161

11621162
! Get dependency ID of this target
@@ -1189,10 +1189,10 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
11891189
endif
11901190

11911191
! Exclusion of package IDs marked "empty" (i.e. they contain no sources)
1192-
empty_package = .not.model%packages%has_library()
1192+
has_lib = model%packages%has_library()
11931193

1194-
if (any(empty_package)) then
1195-
sorted_package_IDs = pack(sorted_package_IDs, .not.empty_package(sorted_package_IDs))
1194+
if (any(has_lib)) then
1195+
sorted_package_IDs = pack(sorted_package_IDs, has_lib(sorted_package_IDs))
11961196
ndep = size(sorted_package_IDs)
11971197
end if
11981198

src/fpm_targets.f90

Lines changed: 128 additions & 47 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ module fpm_targets
4545
FPM_TARGET_SHARED, FPM_TARGET_NAME
4646
public build_target_t, build_target_ptr
4747
public targets_from_sources, resolve_module_dependencies
48-
public add_target, add_dependency, get_library_dirs
48+
public add_target, new_target, add_dependency, get_library_dirs
4949
public filter_library_targets, filter_executable_targets, filter_modules
5050

5151

@@ -148,6 +148,11 @@ module fpm_targets
148148

149149
end type build_target_t
150150

151+
interface add_target
152+
module procedure add_new_target
153+
module procedure add_old_target
154+
module procedure add_old_targets
155+
end interface
151156

152157
contains
153158

@@ -269,8 +274,8 @@ subroutine targets_from_sources(targets,model,prune,library,error)
269274
! all sources to be distributable
270275
should_prune = prune
271276
if (present(library)) should_prune = should_prune .and. library%monolithic()
272-
273-
call prune_build_targets(targets,model%package_name,should_prune)
277+
278+
call prune_build_targets(targets,model%packages(1),should_prune)
274279

275280
call resolve_target_linking(targets,model,library,error)
276281
if (allocated(error)) return
@@ -345,17 +350,20 @@ subroutine build_target_list(targets,model,library)
345350
type = FPM_TARGET_ARCHIVE,output_name = lib_name)
346351

347352
elseif (shared_lib .or. static_lib) then
348-
! Package libraries go to the same path as the `.mod` files (consistent linking directories)
353+
354+
! Individual package libraries are built.
355+
! Create as many targets as the packages in the dependency tree
349356
do j=1,size(model%packages)
350357

351358
lib_name = library_filename(model%packages(j)%name,shared_lib,.false.,get_os_type())
352359

353360
call add_target(targets,package=model%packages(j)%name, &
354-
type = merge(FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE,shared_lib),output_name = lib_name)
361+
type=merge(FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE,shared_lib), &
362+
output_name=lib_name)
355363
end do
356364

357365
endif
358-
366+
359367
do j=1,size(model%packages)
360368

361369
associate(sources=>model%packages(j)%sources)
@@ -553,9 +561,43 @@ subroutine collect_exe_link_dependencies(targets)
553561

554562
end subroutine collect_exe_link_dependencies
555563

564+
!> Allocate a new target
565+
type(build_target_ptr) function new_target(package, type, output_name, source, link_libraries, &
566+
& features, preprocess, version, output_dir)
567+
character(*), intent(in) :: package
568+
integer, intent(in) :: type
569+
character(*), intent(in) :: output_name
570+
type(srcfile_t), intent(in), optional :: source
571+
type(string_t), intent(in), optional :: link_libraries(:)
572+
type(fortran_features_t), intent(in), optional :: features
573+
type(preprocess_config_t), intent(in), optional :: preprocess
574+
character(*), intent(in), optional :: version
575+
character(*), intent(in), optional :: output_dir
576+
577+
allocate(new_target%ptr)
578+
579+
associate(target=>new_target%ptr)
580+
581+
target%target_type = type
582+
target%output_name = output_name
583+
target%package_name = package
584+
if (present(source)) target%source = source
585+
if (present(link_libraries)) target%link_libraries = link_libraries
586+
if (present(features)) target%features = features
587+
if (present(preprocess)) then
588+
if (allocated(preprocess%macros)) target%macros = preprocess%macros
589+
endif
590+
if (present(version)) target%version = version
591+
allocate(target%dependencies(0))
592+
593+
call target%set_output_dir(output_dir)
594+
595+
endassociate
596+
597+
end function new_target
556598

557599
!> Allocate a new target and append to target list
558-
subroutine add_target(targets, package, type, output_name, source, link_libraries, &
600+
subroutine add_new_target(targets, package, type, output_name, source, link_libraries, &
559601
& features, preprocess, version, output_dir)
560602
type(build_target_ptr), allocatable, intent(inout) :: targets(:)
561603
character(*), intent(in) :: package
@@ -568,45 +610,55 @@ subroutine add_target(targets, package, type, output_name, source, link_librarie
568610
character(*), intent(in), optional :: version
569611
character(*), intent(in), optional :: output_dir
570612

571-
integer :: i
572-
type(build_target_t), pointer :: new_target
613+
type(build_target_ptr) :: added
573614

574615
if (.not.allocated(targets)) allocate(targets(0))
616+
617+
! Create new target
618+
added = new_target(package,type,output_name,source,link_libraries,features,preprocess,&
619+
version,output_dir)
620+
621+
call add_old_target(targets, added)
622+
623+
end subroutine add_new_target
575624

625+
subroutine add_old_targets(targets, add_targets)
626+
type(build_target_ptr), allocatable, intent(inout) :: targets(:)
627+
type(build_target_ptr), intent(in) :: add_targets(:)
628+
629+
integer :: i,j
630+
631+
if (.not.allocated(targets)) allocate(targets(0))
632+
576633
! Check for duplicate outputs
577-
do i=1,size(targets)
634+
do j=1,size(add_targets)
635+
associate(added=>add_targets(j)%ptr)
578636

579-
if (targets(i)%ptr%output_name == output_name) then
637+
do i=1,size(targets)
580638

581-
write(*,*) 'Error while building target list: duplicate output object "',&
582-
output_name,'"'
583-
if (present(source)) write(*,*) ' Source file: "',source%file_name,'"'
584-
call fpm_stop(1,' ')
639+
if (targets(i)%ptr%output_name == added%output_name) then
585640

586-
end if
641+
write(*,*) 'Error while building target list: duplicate output object "',&
642+
added%output_name,'"'
643+
if (allocated(added%source)) write(*,*) ' Source file: "',added%source%file_name,'"'
644+
call fpm_stop(1,' ')
587645

588-
end do
646+
end if
589647

590-
allocate(new_target)
591-
new_target%target_type = type
592-
new_target%output_name = output_name
593-
new_target%package_name = package
594-
if (present(source)) new_target%source = source
595-
if (present(link_libraries)) new_target%link_libraries = link_libraries
596-
if (present(features)) new_target%features = features
597-
if (present(preprocess)) then
598-
if (allocated(preprocess%macros)) new_target%macros = preprocess%macros
599-
endif
600-
if (present(version)) new_target%version = version
601-
allocate(new_target%dependencies(0))
602-
603-
call new_target%set_output_dir(output_dir)
648+
end do
649+
650+
endassociate
651+
end do
604652

653+
targets = [targets, add_targets ]
605654

606-
targets = [targets, build_target_ptr(new_target)]
607-
608-
end subroutine add_target
655+
end subroutine add_old_targets
609656

657+
subroutine add_old_target(targets, add_target)
658+
type(build_target_ptr), allocatable, intent(inout) :: targets(:)
659+
type(build_target_ptr), intent(in) :: add_target
660+
call add_old_targets(targets, [add_target])
661+
end subroutine add_old_target
610662

611663
!> Add pointer to dependeny in target%dependencies
612664
subroutine add_dependency(target, dependency)
@@ -740,8 +792,8 @@ subroutine prune_build_targets(targets, root_package, prune_unused_objects)
740792
!> Build target list to prune
741793
type(build_target_ptr), intent(inout), allocatable :: targets(:)
742794

743-
!> Name of root package
744-
character(*), intent(in) :: root_package
795+
!> Root package
796+
type(package_t), intent(in) :: root_package
745797

746798
!> Whether unused objects should be pruned
747799
logical, intent(in) :: prune_unused_objects
@@ -784,7 +836,7 @@ subroutine prune_build_targets(targets, root_package, prune_unused_objects)
784836

785837
do i=1,size(targets)
786838

787-
if (targets(i)%ptr%package_name == root_package .and. &
839+
if (targets(i)%ptr%package_name == root_package%name .and. &
788840
all(targets(i)%ptr%target_type /= [FPM_TARGET_ARCHIVE,FPM_TARGET_SHARED])) then
789841

790842
call collect_used_modules(targets(i)%ptr)
@@ -848,10 +900,11 @@ subroutine prune_build_targets(targets, root_package, prune_unused_objects)
848900

849901
end if
850902

851-
! (If there aren't any executables then we only prune modules from dependencies)
852-
if (nexec < 1 .and. target%package_name == root_package) then
853-
exclude_target(i) = .false.
854-
target%skip = .false.
903+
! (If there aren't any executables then we only prune modules from dependencies,
904+
! unless the root package is also empty)
905+
if (nexec < 1 .and. target%package_name == root_package%name) then
906+
exclude_target(i) = .not.root_package%has_library()
907+
target%skip = exclude_target(i)
855908
end if
856909

857910
end associate
@@ -964,7 +1017,7 @@ subroutine resolve_target_linking(targets, model, library, error)
9641017

9651018
integer :: i,j
9661019
logical :: shared,static,monolithic,has_self_lib
967-
integer, allocatable :: package_deps(:)
1020+
integer, allocatable :: package_deps(:),dep_target_ID(:)
9681021
character(:), allocatable :: global_link_flags, local_link_flags
9691022
character(:), allocatable :: global_include_flags, shared_lib_paths
9701023

@@ -1027,16 +1080,14 @@ subroutine resolve_target_linking(targets, model, library, error)
10271080

10281081
call target%set_output_dir(get_output_dir(model%build_prefix, target%compile_flags))
10291082

1030-
! Check shared build
1031-
if (target%target_type==FPM_TARGET_SHARED) shared = .true.
1032-
10331083
end associate
10341084

10351085
end do
10361086

10371087
call add_include_build_dirs(model, targets)
10381088
call add_library_link_dirs(model, targets, shared_lib_paths)
1039-
1089+
call library_targets_to_deps(model, targets, dep_target_ID)
1090+
10401091
do i=1,size(targets)
10411092

10421093
associate(target => targets(i)%ptr)
@@ -1074,7 +1125,8 @@ subroutine resolve_target_linking(targets, model, library, error)
10741125
! Now that they're available, add these dependencies to the targets
10751126
if (size(package_deps)>0) then
10761127
do j=1,size(package_deps)
1077-
call add_dependency(target, targets(package_deps(j))%ptr)
1128+
if (dep_target_ID(package_deps(j))<=0) cycle
1129+
call add_dependency(target, targets(dep_target_ID(package_deps(j)))%ptr)
10781130
end do
10791131
end if
10801132

@@ -1388,5 +1440,34 @@ subroutine set_output_dir(self, output_dir)
13881440

13891441
end subroutine set_output_dir
13901442

1443+
!> Build a lookup table mapping each package dependency to its corresponding
1444+
!> shared or archive build target in the targets list.
1445+
!>
1446+
!> This mapping is essential when model%deps%dep(i) indices do not match
1447+
!> the pruned or reordered targets(:) array.
1448+
subroutine library_targets_to_deps(model, targets, target_ID)
1449+
class(fpm_model_t), intent(in) :: model
1450+
type(build_target_ptr), intent(in) :: targets(:)
1451+
1452+
!> For each package (by dependency index), gives the index of the corresponding target
1453+
integer, allocatable, intent(out) :: target_ID(:)
1454+
1455+
integer :: it, ip, n
1456+
1457+
n = size(model%deps%dep)
1458+
allocate(target_ID(n), source=0)
1459+
1460+
do it = 1, size(targets)
1461+
associate(target => targets(it)%ptr)
1462+
! Only shared libraries and archives are mapped
1463+
if (all(target%target_type /= [FPM_TARGET_ARCHIVE, FPM_TARGET_SHARED])) cycle
1464+
1465+
! Get the dependency graph index of this package
1466+
ip = model%deps%find(target%package_name)
1467+
if (ip > 0) target_ID(ip) = it
1468+
end associate
1469+
end do
1470+
1471+
end subroutine library_targets_to_deps
13911472

13921473
end module fpm_targets

0 commit comments

Comments
 (0)