@@ -8,7 +8,7 @@ module fpm
8
8
fpm_clean_settings
9
9
use fpm_dependency, only : new_dependency_tree
10
10
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
12
12
use fpm_model, only: fpm_model_t, srcfile_t, show_model, fortran_features_t, &
13
13
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
14
14
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
@@ -704,10 +704,10 @@ subroutine delete_targets_by_scope(targets, scope, scope_name, deleted_any)
704
704
705
705
call filter_executable_targets(targets, scope, scope_targets)
706
706
if (size (scope_targets) > 0 ) then
707
- write (stdout, ' (A,I0,A,A,A)' ) " Deleting " , size (scope_targets), " " , scope_name, " targets"
708
707
do i = 1 , size (scope_targets)
709
708
if (exists(scope_targets(i)% s)) then
710
- call run(' rm -f "' // scope_targets(i)% s// ' "' )
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
711
deleted_any = .true.
712
712
end if
713
713
end do
@@ -716,39 +716,32 @@ end subroutine delete_targets_by_scope
716
716
717
717
! > Delete build artifacts for specific target types (test, apps, examples)
718
718
subroutine delete_targets (settings , error )
719
- class(fpm_clean_settings), intent (in ) :: settings
719
+ class(fpm_clean_settings), intent (inout ) :: settings
720
720
type (error_t), allocatable , intent (out ) :: error
721
721
722
722
type (package_config_t) :: package
723
723
type (fpm_model_t) :: model
724
724
type (build_target_ptr), allocatable :: targets(:)
725
- type (fpm_build_settings) :: build_settings
726
725
logical :: deleted_any
727
726
728
727
! Get package configuration
729
- call get_package_data(package, settings % working_dir , error)
728
+ call get_package_data(package, " fpm.toml " , error, apply_defaults = .true. )
730
729
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"
730
+
731
+ ! Ensure tests will be modeled
732
+ if (settings% clean_test) settings% build_tests = .true.
740
733
741
734
! Build the model to understand targets
742
- call build_model(model, build_settings , package, error)
735
+ call build_model(model, settings , package, error)
743
736
if (allocated (error)) return
744
737
745
- ! Get build targets
746
- call targets_from_sources(targets, model, build_settings % prune, error = error)
738
+ ! Get the exact targets
739
+ call targets_from_sources(targets, model, settings % prune, package % library, error)
747
740
if (allocated (error)) return
748
741
749
742
deleted_any = .false.
750
743
751
- ! Delete targets by scope
744
+ ! Delete targets by scope using the original approach
752
745
if (settings% clean_test) then
753
746
call delete_targets_by_scope(targets, FPM_SCOPE_TEST, " test" , deleted_any)
754
747
end if
@@ -771,7 +764,7 @@ end subroutine delete_targets
771
764
! > to clear the registry cache.
772
765
subroutine cmd_clean (settings )
773
766
! > Settings for the clean command.
774
- class(fpm_clean_settings), intent (in ) :: settings
767
+ class(fpm_clean_settings), intent (inout ) :: settings
775
768
776
769
character :: user_response
777
770
type (fpm_global_settings) :: global_settings
0 commit comments