@@ -78,6 +78,9 @@ module fpm_targets
78
78
! > File path of build log file relative to cwd
79
79
character (:), allocatable :: output_log_file
80
80
81
+ ! > Name of parent package
82
+ character (:), allocatable :: package_name
83
+
81
84
! > Primary source for this build target
82
85
type (srcfile_t), allocatable :: source
83
86
@@ -140,7 +143,7 @@ subroutine targets_from_sources(targets,model,prune,error)
140
143
if (allocated (error)) return
141
144
142
145
if (prune) then
143
- call prune_build_targets(targets)
146
+ call prune_build_targets(targets,root_package = model % package_name )
144
147
end if
145
148
146
149
call resolve_target_linking(targets,model)
@@ -198,7 +201,7 @@ subroutine build_target_list(targets,model)
198
201
i= 1 ,size (model% packages(j)% sources)), &
199
202
j= 1 ,size (model% packages))])
200
203
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,&
202
205
output_name = join_path(&
203
206
model% package_name,' lib' // model% package_name// ' .a' ))
204
207
@@ -215,7 +218,7 @@ subroutine build_target_list(targets,model)
215
218
select case (sources(i)% unit_type)
216
219
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
217
220
218
- call add_target(targets,source = sources(i), &
221
+ call add_target(targets,package = model % packages(j) % name, source = sources(i), &
219
222
type = merge (FPM_TARGET_C_OBJECT,FPM_TARGET_OBJECT,&
220
223
sources(i)% unit_type== FPM_UNIT_CSOURCE), &
221
224
output_name = get_object_name(sources(i)))
@@ -227,7 +230,7 @@ subroutine build_target_list(targets,model)
227
230
228
231
case (FPM_UNIT_PROGRAM)
229
232
230
- call add_target(targets,type = FPM_TARGET_OBJECT,&
233
+ call add_target(targets,package = model % packages(j) % name, type = FPM_TARGET_OBJECT,&
231
234
output_name = get_object_name(sources(i)), &
232
235
source = sources(i) &
233
236
)
@@ -246,7 +249,7 @@ subroutine build_target_list(targets,model)
246
249
247
250
end if
248
251
249
- call add_target(targets,type = FPM_TARGET_EXECUTABLE,&
252
+ call add_target(targets,package = model % packages(j) % name, type = FPM_TARGET_EXECUTABLE,&
250
253
link_libraries = sources(i)% link_libraries, &
251
254
output_name = join_path(exe_dir, &
252
255
sources(i)% exe_name// xsuffix))
@@ -296,8 +299,9 @@ end subroutine build_target_list
296
299
297
300
298
301
! > 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 )
300
303
type (build_target_ptr), allocatable , intent (inout ) :: targets(:)
304
+ character (* ), intent (in ) :: package
301
305
integer , intent (in ) :: type
302
306
character (* ), intent (in ) :: output_name
303
307
type (srcfile_t), intent (in ), optional :: source
@@ -325,6 +329,7 @@ subroutine add_target(targets,type,output_name,source,link_libraries)
325
329
allocate (new_target)
326
330
new_target% target_type = type
327
331
new_target% output_name = output_name
332
+ new_target% package_name = package
328
333
if (present (source)) new_target% source = source
329
334
if (present (link_libraries)) new_target% link_libraries = link_libraries
330
335
allocate (new_target% dependencies(0 ))
@@ -461,14 +466,23 @@ end function find_module_dependency
461
466
462
467
463
468
! > 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
465
472
type (build_target_ptr), intent (inout ), allocatable :: targets(:)
466
473
474
+ ! > Name of root package
475
+ character (* ), intent (in ) :: root_package
476
+
467
477
integer :: i, j, nexec
468
478
type (string_t), allocatable :: modules_used(:)
469
479
logical :: exclude_target(size (targets))
470
480
logical , allocatable :: exclude_from_archive(:)
471
481
482
+ if (size (targets) < 1 ) then
483
+ return
484
+ end if
485
+
472
486
nexec = 0
473
487
allocate (modules_used(0 ))
474
488
@@ -484,10 +498,21 @@ subroutine prune_build_targets(targets)
484
498
485
499
end do
486
500
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
489
503
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
+
491
516
end if
492
517
493
518
exclude_target(:) = .false.
@@ -532,6 +557,12 @@ subroutine prune_build_targets(targets)
532
557
end if
533
558
end if
534
559
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
+
535
566
end associate
536
567
end do
537
568
0 commit comments