@@ -17,7 +17,7 @@ module fpm
17
17
18
18
use fpm_sources, only: add_executable_sources, add_sources_from_dir
19
19
use fpm_targets, only: targets_from_sources, build_target_t, build_target_ptr, &
20
- FPM_TARGET_EXECUTABLE, get_library_dirs
20
+ FPM_TARGET_EXECUTABLE, get_library_dirs, filter_executable_targets
21
21
use fpm_manifest, only : get_package_data, package_config_t
22
22
use fpm_meta, only : resolve_metapackages
23
23
use fpm_error, only : error_t, fatal_error, fpm_stop
@@ -692,6 +692,81 @@ subroutine delete_skip(is_unix)
692
692
end do
693
693
end subroutine delete_skip
694
694
695
+ ! > Delete targets of a specific scope with given description
696
+ subroutine delete_targets_by_scope (targets , scope , scope_name , deleted_any )
697
+ type (build_target_ptr), intent (in ) :: targets(:)
698
+ integer , intent (in ) :: scope
699
+ character (len=* ), intent (in ) :: scope_name
700
+ logical , intent (inout ) :: deleted_any
701
+
702
+ type (string_t), allocatable :: scope_targets(:)
703
+ integer :: i
704
+
705
+ call filter_executable_targets(targets, scope, scope_targets)
706
+ if (size (scope_targets) > 0 ) then
707
+ write (stdout, ' (A,I0,A,A,A)' ) " Deleting " , size (scope_targets), " " , scope_name, " targets"
708
+ do i = 1 , size (scope_targets)
709
+ if (exists(scope_targets(i)% s)) then
710
+ call run(' rm -f "' // scope_targets(i)% s// ' "' )
711
+ deleted_any = .true.
712
+ end if
713
+ end do
714
+ end if
715
+ end subroutine delete_targets_by_scope
716
+
717
+ ! > Delete build artifacts for specific target types (test, apps, examples)
718
+ subroutine delete_targets (settings , error )
719
+ class(fpm_clean_settings), intent (in ) :: settings
720
+ type (error_t), allocatable , intent (out ) :: error
721
+
722
+ type (package_config_t) :: package
723
+ type (fpm_model_t) :: model
724
+ type (build_target_ptr), allocatable :: targets(:)
725
+ type (fpm_build_settings) :: build_settings
726
+ logical :: deleted_any
727
+
728
+ ! Get package configuration
729
+ call get_package_data(package, settings% working_dir, error)
730
+ if (allocated (error)) return
731
+
732
+ ! Create minimal build settings to build the model
733
+ build_settings% working_dir = settings% working_dir
734
+ build_settings% path_to_config = settings% path_to_config
735
+ build_settings% build_tests = .true.
736
+ build_settings% prune = .true.
737
+ if (allocated (build_settings% profile)) deallocate (build_settings% profile)
738
+ allocate (character (len= 5 ) :: build_settings% profile)
739
+ build_settings% profile = " debug"
740
+
741
+ ! Build the model to understand targets
742
+ call build_model(model, build_settings, package, error)
743
+ if (allocated (error)) return
744
+
745
+ ! Get build targets
746
+ call targets_from_sources(targets, model, build_settings% prune, error= error)
747
+ if (allocated (error)) return
748
+
749
+ deleted_any = .false.
750
+
751
+ ! Delete targets by scope
752
+ if (settings% clean_test) then
753
+ call delete_targets_by_scope(targets, FPM_SCOPE_TEST, " test" , deleted_any)
754
+ end if
755
+
756
+ if (settings% clean_apps) then
757
+ call delete_targets_by_scope(targets, FPM_SCOPE_APP, " app" , deleted_any)
758
+ end if
759
+
760
+ if (settings% clean_examples) then
761
+ call delete_targets_by_scope(targets, FPM_SCOPE_EXAMPLE, " example" , deleted_any)
762
+ end if
763
+
764
+ if (.not. deleted_any) then
765
+ write (stdout, ' (A)' ) " No matching build targets found to delete."
766
+ end if
767
+
768
+ end subroutine delete_targets
769
+
695
770
! > Delete the build directory including or excluding dependencies. Can be used
696
771
! > to clear the registry cache.
697
772
subroutine cmd_clean (settings )
@@ -710,6 +785,20 @@ subroutine cmd_clean(settings)
710
785
call os_delete_dir(os_is_unix(), global_settings% registry_settings% cache_path)
711
786
end if
712
787
788
+ ! Handle target-specific cleaning
789
+ if (any ([settings% clean_test, settings% clean_apps, settings% clean_examples])) then
790
+ if (.not. is_dir(' build' )) then
791
+ write (stdout, ' (A)' ) " fpm: No build directory found."
792
+ return
793
+ end if
794
+ call delete_targets(settings, error)
795
+ if (allocated (error)) then
796
+ write (stderr, ' (A)' ) ' Error: ' // error% message
797
+ return
798
+ end if
799
+ return
800
+ end if
801
+
713
802
if (is_dir(' build' )) then
714
803
! Remove the entire build directory
715
804
if (settings% clean_all) then
0 commit comments