Skip to content

Commit 28dcdc4

Browse files
committed
Update: to allow pruning based on root package modules
when there are no top-level executables to prune from.
1 parent e515796 commit 28dcdc4

File tree

2 files changed

+45
-14
lines changed

2 files changed

+45
-14
lines changed

src/fpm_targets.f90

+41-10
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,9 @@ module fpm_targets
7878
!> File path of build log file relative to cwd
7979
character(:), allocatable :: output_log_file
8080

81+
!> Name of parent package
82+
character(:), allocatable :: package_name
83+
8184
!> Primary source for this build target
8285
type(srcfile_t), allocatable :: source
8386

@@ -140,7 +143,7 @@ subroutine targets_from_sources(targets,model,prune,error)
140143
if (allocated(error)) return
141144

142145
if (prune) then
143-
call prune_build_targets(targets)
146+
call prune_build_targets(targets,root_package=model%package_name)
144147
end if
145148

146149
call resolve_target_linking(targets,model)
@@ -198,7 +201,7 @@ subroutine build_target_list(targets,model)
198201
i=1,size(model%packages(j)%sources)), &
199202
j=1,size(model%packages))])
200203

201-
if (with_lib) call add_target(targets,type = FPM_TARGET_ARCHIVE,&
204+
if (with_lib) call add_target(targets,package=model%package_name,type = FPM_TARGET_ARCHIVE,&
202205
output_name = join_path(&
203206
model%package_name,'lib'//model%package_name//'.a'))
204207

@@ -215,7 +218,7 @@ subroutine build_target_list(targets,model)
215218
select case (sources(i)%unit_type)
216219
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
217220

218-
call add_target(targets,source = sources(i), &
221+
call add_target(targets,package=model%packages(j)%name,source = sources(i), &
219222
type = merge(FPM_TARGET_C_OBJECT,FPM_TARGET_OBJECT,&
220223
sources(i)%unit_type==FPM_UNIT_CSOURCE), &
221224
output_name = get_object_name(sources(i)))
@@ -227,7 +230,7 @@ subroutine build_target_list(targets,model)
227230

228231
case (FPM_UNIT_PROGRAM)
229232

230-
call add_target(targets,type = FPM_TARGET_OBJECT,&
233+
call add_target(targets,package=model%packages(j)%name,type = FPM_TARGET_OBJECT,&
231234
output_name = get_object_name(sources(i)), &
232235
source = sources(i) &
233236
)
@@ -246,7 +249,7 @@ subroutine build_target_list(targets,model)
246249

247250
end if
248251

249-
call add_target(targets,type = FPM_TARGET_EXECUTABLE,&
252+
call add_target(targets,package=model%packages(j)%name,type = FPM_TARGET_EXECUTABLE,&
250253
link_libraries = sources(i)%link_libraries, &
251254
output_name = join_path(exe_dir, &
252255
sources(i)%exe_name//xsuffix))
@@ -296,8 +299,9 @@ end subroutine build_target_list
296299

297300

298301
!> Allocate a new target and append to target list
299-
subroutine add_target(targets,type,output_name,source,link_libraries)
302+
subroutine add_target(targets,package,type,output_name,source,link_libraries)
300303
type(build_target_ptr), allocatable, intent(inout) :: targets(:)
304+
character(*), intent(in) :: package
301305
integer, intent(in) :: type
302306
character(*), intent(in) :: output_name
303307
type(srcfile_t), intent(in), optional :: source
@@ -325,6 +329,7 @@ subroutine add_target(targets,type,output_name,source,link_libraries)
325329
allocate(new_target)
326330
new_target%target_type = type
327331
new_target%output_name = output_name
332+
new_target%package_name = package
328333
if (present(source)) new_target%source = source
329334
if (present(link_libraries)) new_target%link_libraries = link_libraries
330335
allocate(new_target%dependencies(0))
@@ -461,14 +466,23 @@ end function find_module_dependency
461466

462467

463468
!> Perform tree-shaking to remove unused module targets
464-
subroutine prune_build_targets(targets)
469+
subroutine prune_build_targets(targets, root_package)
470+
471+
!> Build target list to prune
465472
type(build_target_ptr), intent(inout), allocatable :: targets(:)
466473

474+
!> Name of root package
475+
character(*), intent(in) :: root_package
476+
467477
integer :: i, j, nexec
468478
type(string_t), allocatable :: modules_used(:)
469479
logical :: exclude_target(size(targets))
470480
logical, allocatable :: exclude_from_archive(:)
471481

482+
if (size(targets) < 1) then
483+
return
484+
end if
485+
472486
nexec = 0
473487
allocate(modules_used(0))
474488

@@ -484,10 +498,21 @@ subroutine prune_build_targets(targets)
484498

485499
end do
486500

487-
! Can't prune targets without executables
488-
! (everything will be built)
501+
! If there aren't any executables, then prune
502+
! based on modules used in root package
489503
if (nexec < 1) then
490-
return
504+
505+
do i=1,size(targets)
506+
507+
if (targets(i)%ptr%package_name == root_package .and. &
508+
targets(i)%ptr%target_type /= FPM_TARGET_ARCHIVE) then
509+
510+
call collect_used_modules(targets(i)%ptr)
511+
512+
end if
513+
514+
end do
515+
491516
end if
492517

493518
exclude_target(:) = .false.
@@ -532,6 +557,12 @@ subroutine prune_build_targets(targets)
532557
end if
533558
end if
534559

560+
! (If there aren't any executables then we only prune modules from dependencies)
561+
if (nexec < 1 .and. target%package_name == root_package) then
562+
exclude_target(i) = .false.
563+
target%skip = .false.
564+
end if
565+
535566
end associate
536567
end do
537568

test/fpm_test/test_backend.f90

+4-4
Original file line numberDiff line numberDiff line change
@@ -330,13 +330,13 @@ function new_test_package() result(targets)
330330
type(build_target_ptr), allocatable :: targets(:)
331331
integer :: i
332332

333-
call add_target(targets,FPM_TARGET_ARCHIVE,get_temp_filename())
333+
call add_target(targets,'test-package',FPM_TARGET_ARCHIVE,get_temp_filename())
334334

335-
call add_target(targets,FPM_TARGET_OBJECT,get_temp_filename())
335+
call add_target(targets,'test-package',FPM_TARGET_OBJECT,get_temp_filename())
336336

337-
call add_target(targets,FPM_TARGET_OBJECT,get_temp_filename())
337+
call add_target(targets,'test-package',FPM_TARGET_OBJECT,get_temp_filename())
338338

339-
call add_target(targets,FPM_TARGET_OBJECT,get_temp_filename())
339+
call add_target(targets,'test-package',FPM_TARGET_OBJECT,get_temp_filename())
340340

341341
! Library depends on all objects
342342
call add_dependency(targets(1)%ptr,targets(2)%ptr)

0 commit comments

Comments
 (0)