@@ -136,6 +136,8 @@ subroutine targets_from_sources(targets,model,error)
136
136
call resolve_module_dependencies(targets,model% external_modules,error)
137
137
if (allocated (error)) return
138
138
139
+ call prune_build_targets(targets)
140
+
139
141
call resolve_target_linking(targets,model)
140
142
141
143
end subroutine targets_from_sources
@@ -453,6 +455,119 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
453
455
end function find_module_dependency
454
456
455
457
458
+ ! > Perform tree-shaking to remove unused module targets
459
+ subroutine prune_build_targets (targets )
460
+ type (build_target_ptr), intent (inout ), allocatable :: targets(:)
461
+
462
+ integer :: i, j, nexec
463
+ type (string_t), allocatable :: modules_used(:)
464
+ logical :: exclude_target(size (targets))
465
+ logical , allocatable :: exclude_from_archive(:)
466
+
467
+ nexec = 0
468
+ allocate (modules_used(0 ))
469
+
470
+ ! Enumerate modules used by executables and their dependencies
471
+ do i= 1 ,size (targets)
472
+
473
+ if (targets(i)% ptr% target_type == FPM_TARGET_EXECUTABLE) then
474
+
475
+ nexec = nexec + 1
476
+ call collect_used_modules(targets(i)% ptr)
477
+
478
+ end if
479
+
480
+ end do
481
+
482
+ ! Can't prune targets without executables
483
+ ! (everything will be built)
484
+ if (nexec < 1 ) then
485
+ return
486
+ end if
487
+
488
+ exclude_target(:) = .false.
489
+
490
+ ! Exclude purely module targets if they are not used anywhere
491
+ do i= 1 ,size (targets)
492
+ associate(target = >targets(i)% ptr)
493
+
494
+ if (allocated (target % source)) then
495
+ if (target % source% unit_type == FPM_UNIT_MODULE) then
496
+
497
+ exclude_target(i) = .true.
498
+ target % skip = .true.
499
+
500
+ do j= 1 ,size (target % source% modules_provided)
501
+
502
+ if (target % source% modules_provided(j)% s .in . modules_used) then
503
+
504
+ exclude_target(i) = .false.
505
+ target % skip = .false.
506
+
507
+ end if
508
+
509
+ end do
510
+
511
+ end if
512
+ end if
513
+
514
+ end associate
515
+ end do
516
+
517
+ targets = pack (targets,.not. exclude_target)
518
+
519
+ ! Remove unused targets from archive dependency list
520
+ if (targets(1 )% ptr% target_type == FPM_TARGET_ARCHIVE) then
521
+ associate(archive= >targets(1 )% ptr)
522
+
523
+ allocate (exclude_from_archive(size (archive% dependencies)))
524
+ exclude_from_archive(:) = .false.
525
+
526
+ do i= 1 ,size (archive% dependencies)
527
+
528
+ if (archive% dependencies(i)% ptr% skip) then
529
+
530
+ exclude_from_archive(i) = .true.
531
+
532
+ end if
533
+
534
+ end do
535
+
536
+ archive% dependencies = pack (archive% dependencies,.not. exclude_from_archive)
537
+
538
+ end associate
539
+ end if
540
+
541
+ contains
542
+
543
+ recursive subroutine collect_used_modules (target )
544
+ type (build_target_t), intent (in ) :: target
545
+
546
+ integer :: j
547
+
548
+ if (allocated (target % source)) then
549
+ do j= 1 ,size (target % source% modules_used)
550
+
551
+ if (.not. (target % source% modules_used(j)% s .in . modules_used)) then
552
+
553
+ modules_used = [modules_used, target % source% modules_used(j)]
554
+
555
+ end if
556
+
557
+ end do
558
+ end if
559
+
560
+ do j= 1 ,size (target % dependencies)
561
+
562
+ call collect_used_modules(target % dependencies(j)% ptr)
563
+
564
+ end do
565
+
566
+ end subroutine collect_used_modules
567
+
568
+ end subroutine prune_build_targets
569
+
570
+
456
571
! > Construct the linker flags string for each target
457
572
! > `target%link_flags` includes non-library objects and library flags
458
573
! >
0 commit comments