Skip to content

Commit 1a9921d

Browse files
committed
implement clean --test --apps --examples
1 parent b9d11e6 commit 1a9921d

File tree

3 files changed

+127
-4
lines changed

3 files changed

+127
-4
lines changed

src/fpm.f90

Lines changed: 90 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -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,6 +692,81 @@ 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+
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+
695770
!> Delete the build directory including or excluding dependencies. Can be used
696771
!> to clear the registry cache.
697772
subroutine cmd_clean(settings)
@@ -710,6 +785,20 @@ subroutine cmd_clean(settings)
710785
call os_delete_dir(os_is_unix(), global_settings%registry_settings%cache_path)
711786
end if
712787

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+
713802
if (is_dir('build')) then
714803
! Remove the entire build directory
715804
if (settings%clean_all) then

src/fpm_command_line.f90

Lines changed: 26 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -132,6 +132,9 @@ module fpm_command_line
132132
type, extends(fpm_cmd_settings) :: fpm_clean_settings
133133
logical :: clean_skip = .false.
134134
logical :: clean_all = .false.
135+
logical :: clean_test = .false.
136+
logical :: clean_apps = .false.
137+
logical :: clean_examples = .false.
135138
logical :: registry_cache = .false.
136139
end type
137140

@@ -712,26 +715,42 @@ subroutine get_command_line_settings(cmd_settings)
712715
& ' --registry-cache' // &
713716
& ' --skip' // &
714717
& ' --all' // &
718+
& ' --test' // &
719+
& ' --apps' // &
720+
& ' --examples' // &
715721
& ' --config-file ""', help_clean, version_text)
716722

717723
block
718-
logical :: skip, clean_all
724+
logical :: skip, clean_all, clean_test, clean_apps, clean_examples
725+
logical :: target_specific
719726

720727
skip = lget('skip')
721728
clean_all = lget('all')
729+
clean_test = lget('test')
730+
clean_apps = lget('apps')
731+
clean_examples = lget('examples')
722732
config_file = sget('config-file')
723733

734+
target_specific = any([clean_test, clean_apps, clean_examples])
735+
724736
if (all([skip, clean_all])) then
725737
call fpm_stop(6, 'Do not specify both --skip and --all options on the clean subcommand.')
726738
end if
727739

740+
if (target_specific .and. any([skip, clean_all])) then
741+
call fpm_stop(6, 'Cannot combine target-specific flags (--test, --apps, --examples) with --skip or --all.')
742+
end if
743+
728744
allocate(fpm_clean_settings :: cmd_settings)
729745
call get_current_directory(working_dir, error)
730746
cmd_settings = fpm_clean_settings( &
731747
& working_dir=working_dir, &
732748
& clean_skip=skip, &
733749
& registry_cache=lget('registry-cache'), &
734750
& clean_all=clean_all, &
751+
& clean_test=clean_test, &
752+
& clean_apps=clean_apps, &
753+
& clean_examples=clean_examples, &
735754
& path_to_config=config_file)
736755
end block
737756

@@ -1501,16 +1520,21 @@ subroutine set_help()
15011520
' clean(1) - delete the build', &
15021521
'', &
15031522
'SYNOPSIS', &
1504-
' fpm clean', &
1523+
' fpm clean [--skip|--all]', &
1524+
' fpm clean [--test] [--apps] [--examples]', &
15051525
'', &
15061526
'DESCRIPTION', &
15071527
' Prompts the user to confirm deletion of the build. If affirmative,', &
15081528
' directories in the build/ directory are deleted, except dependencies.', &
15091529
' Use the --registry-cache option to delete the registry cache.', &
1530+
' Use target-specific flags to delete only certain build artifacts.', &
15101531
'', &
15111532
'OPTIONS', &
15121533
' --skip Delete the build without prompting but skip dependencies.', &
15131534
' --all Delete the build without prompting including dependencies.', &
1535+
' --test Delete only test executables.', &
1536+
' --apps Delete only application executables.', &
1537+
' --examples Delete only example executables.', &
15141538
' --config-file PATH Custom location of the global config file.', &
15151539
' --registry-cache Delete registry cache.', &
15161540
'' ]

test/cli_test/cli_test.f90

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,9 @@ program main
2929
logical :: w_t,act_w_t ; namelist/act_cli/act_w_t
3030
logical :: c_s,act_c_s ; namelist/act_cli/act_c_s
3131
logical :: c_a,act_c_a ; namelist/act_cli/act_c_a
32+
logical :: c_t,act_c_t ; namelist/act_cli/act_c_t
33+
logical :: c_apps,act_c_apps ; namelist/act_cli/act_c_apps
34+
logical :: c_ex,act_c_ex ; namelist/act_cli/act_c_ex
3235
logical :: reg_c,act_reg_c ; namelist/act_cli/act_reg_c
3336
logical :: show_v,act_show_v ; namelist/act_cli/act_show_v
3437
logical :: show_u_d,act_show_u_d; namelist/act_cli/act_show_u_d
@@ -37,7 +40,7 @@ program main
3740

3841
character(len=:), allocatable :: profile,act_profile ; namelist/act_cli/act_profile
3942
character(len=:), allocatable :: args,act_args ; namelist/act_cli/act_args
40-
namelist/expected/cmd,cstat,estat,w_e,w_t,c_s,c_a,reg_c,name,profile,args,show_v,show_u_d,dry_run,token
43+
namelist/expected/cmd,cstat,estat,w_e,w_t,c_s,c_a,c_t,c_apps,c_ex,reg_c,name,profile,args,show_v,show_u_d,dry_run,token
4144
integer :: lun
4245
logical,allocatable :: tally(:)
4346
logical,allocatable :: subtally(:)
@@ -76,6 +79,10 @@ program main
7679
'CMD="clean", NAME=, ARGS="",', &
7780
'CMD="clean --skip", C_S=T, NAME=, ARGS="",', &
7881
'CMD="clean --all", C_A=T, NAME=, ARGS="",', &
82+
'CMD="clean --test", C_T=T, NAME=, ARGS="",', &
83+
'CMD="clean --apps", C_APPS=T, NAME=, ARGS="",', &
84+
'CMD="clean --examples", C_EX=T, NAME=, ARGS="",', &
85+
'CMD="clean --test --apps", C_T=T, C_APPS=T, NAME=, ARGS="",', &
7986
'CMD="clean --registry-cache", REG_C=T, NAME=, ARGS="",', &
8087
'CMD="publish --token abc --show-package-version", SHOW_V=T, NAME=, token="abc",ARGS="",', &
8188
'CMD="publish --token abc --show-upload-data", SHOW_U_D=T, NAME=, token="abc",ARGS="",', &
@@ -273,6 +280,9 @@ subroutine parse()
273280
type is (fpm_clean_settings)
274281
act_c_s=settings%clean_skip
275282
act_c_a=settings%clean_all
283+
act_c_t=settings%clean_test
284+
act_c_apps=settings%clean_apps
285+
act_c_ex=settings%clean_examples
276286
act_reg_c=settings%registry_cache
277287
type is (fpm_install_settings)
278288
type is (fpm_publish_settings)

0 commit comments

Comments
 (0)