Skip to content

Commit e9f9476

Browse files
authored
feat: selective clean functionality (#1171)
2 parents 265cbee + 26c291f commit e9f9476

File tree

3 files changed

+271
-184
lines changed

3 files changed

+271
-184
lines changed

src/fpm.f90

Lines changed: 82 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module fpm
88
fpm_clean_settings
99
use fpm_dependency, only : new_dependency_tree
1010
use fpm_filesystem, only: is_dir, join_path, list_files, exists, &
11-
basename, filewrite, mkdir, run, os_delete_dir
11+
basename, filewrite, mkdir, run, os_delete_dir, delete_file
1212
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1313
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1414
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
@@ -17,7 +17,7 @@ module fpm
1717

1818
use fpm_sources, only: add_executable_sources, add_sources_from_dir
1919
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
2121
use fpm_manifest, only : get_package_data, package_config_t
2222
use fpm_meta, only : resolve_metapackages
2323
use fpm_error, only : error_t, fatal_error, fpm_stop
@@ -692,11 +692,76 @@ subroutine delete_skip(is_unix)
692692
end do
693693
end subroutine delete_skip
694694

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+
do i = 1, size(scope_targets)
708+
if (exists(scope_targets(i)%s)) then
709+
write(stdout, '(A,A,A,A)') "<INFO> Deleted ", scope_name, " target: ", basename(scope_targets(i)%s)
710+
call delete_file(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(inout) :: 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+
logical :: deleted_any
726+
727+
! Get package configuration
728+
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
729+
if (allocated(error)) return
730+
731+
! Build the model to understand targets
732+
call build_model(model, settings, package, error)
733+
if (allocated(error)) return
734+
735+
! Get the exact targets
736+
call targets_from_sources(targets, model, settings%prune, package%library, error)
737+
if (allocated(error)) return
738+
739+
deleted_any = .false.
740+
741+
! Delete targets by scope using the original approach
742+
if (settings%clean_test) then
743+
call delete_targets_by_scope(targets, FPM_SCOPE_TEST, "test", deleted_any)
744+
end if
745+
746+
if (settings%clean_apps) then
747+
call delete_targets_by_scope(targets, FPM_SCOPE_APP, "app", deleted_any)
748+
end if
749+
750+
if (settings%clean_examples) then
751+
call delete_targets_by_scope(targets, FPM_SCOPE_EXAMPLE, "example", deleted_any)
752+
end if
753+
754+
if (.not. deleted_any) then
755+
write(stdout, '(A)') "No matching build targets found to delete."
756+
end if
757+
758+
end subroutine delete_targets
759+
695760
!> Delete the build directory including or excluding dependencies. Can be used
696761
!> to clear the registry cache.
697762
subroutine cmd_clean(settings)
698763
!> Settings for the clean command.
699-
class(fpm_clean_settings), intent(in) :: settings
764+
class(fpm_clean_settings), intent(inout) :: settings
700765

701766
character :: user_response
702767
type(fpm_global_settings) :: global_settings
@@ -710,6 +775,20 @@ subroutine cmd_clean(settings)
710775
call os_delete_dir(os_is_unix(), global_settings%registry_settings%cache_path)
711776
end if
712777

778+
! Handle target-specific cleaning
779+
if (any([settings%clean_test, settings%clean_apps, settings%clean_examples])) then
780+
if (.not. is_dir('build')) then
781+
write (stdout, '(A)') "fpm: No build directory found."
782+
return
783+
end if
784+
call delete_targets(settings, error)
785+
if (allocated(error)) then
786+
write(stderr, '(A)') 'Error: ' // error%message
787+
return
788+
end if
789+
return
790+
end if
791+
713792
if (is_dir('build')) then
714793
! Remove the entire build directory
715794
if (settings%clean_all) then

0 commit comments

Comments
 (0)