Skip to content

Commit 7c3c36f

Browse files
committed
update clean subcommand adding --skip and --all flags
1 parent 8185a8a commit 7c3c36f

File tree

3 files changed

+83
-34
lines changed

3 files changed

+83
-34
lines changed

src/fpm.f90

Lines changed: 34 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module fpm
77
use fpm_dependency, only : new_dependency_tree
88
use fpm_environment, only: get_env
99
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, &
10-
basename, filewrite, mkdir, run
10+
basename, filewrite, mkdir, run, os_delete_dir
1111
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1212
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1313
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
@@ -23,6 +23,7 @@ module fpm
2323
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
2424
& stdout=>output_unit, &
2525
& stderr=>error_unit
26+
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
2627
implicit none
2728
private
2829
public :: cmd_build, cmd_run, cmd_clean
@@ -503,22 +504,42 @@ end subroutine compact_list
503504

504505
end subroutine cmd_run
505506

507+
subroutine delete_skip(unix)
508+
!> delete directories in the build folder, skipping dependencies
509+
logical, intent(in) :: unix
510+
character(len=:), allocatable :: dir
511+
type(string_t), allocatable :: files(:)
512+
integer :: i
513+
call list_files('build', files, .false.)
514+
do i = 1, size(files)
515+
if (is_dir(files(i)%s)) then
516+
dir = files(i)%s
517+
if (dir /= 'build/dependencies') call os_delete_dir(unix, dir)
518+
end if
519+
end do
520+
end subroutine delete_skip
521+
506522
subroutine cmd_clean(settings)
523+
!> fpm clean called
507524
class(fpm_clean_settings), intent(in) :: settings
525+
! character(len=:), allocatable :: dir
526+
! type(string_t), allocatable :: files(:)
508527
character(len=1) :: response
509-
write(stdout, '(*(a))') "fpm: Clean calling directory '"//settings%calling_dir//"'"
510-
if (is_dir("build")) then
511-
write(stdout, '(A)', advance='no') "Delete the build directory (y/n)? "
512-
read(stdin, '(A1)') response
513-
if (lower(response) == 'y') then
514-
if(settings%unix) then
515-
call run('rm -rf build', .false.)
516-
else
517-
call run('rmdir /s/q build', .false.)
518-
end if
519-
else
520-
write (stdout, '(A)') "fpm: Build directory was not deleted."
528+
if (is_dir('build')) then
529+
! remove the entire build directory
530+
if (settings%clean_call) then
531+
call os_delete_dir(settings%unix, 'build')
532+
return
521533
end if
534+
! remove the build directory but skip dependencies
535+
if (settings%clean_skip) then
536+
call delete_skip(settings%unix)
537+
return
538+
end if
539+
! prompt to remove the build directory but skip dependencies
540+
write(stdout, '(A)', advance='no') "Delete build, excluding dependencies (y/n)? "
541+
read(stdin, '(A1)') response
542+
if (lower(response) == 'y') call delete_skip(settings%unix)
522543
else
523544
write (stdout, '(A)') "fpm: No build directory found."
524545
end if

src/fpm_command_line.f90

Lines changed: 34 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -105,9 +105,11 @@ module fpm_command_line
105105
logical :: clean
106106
end type
107107

108-
type, extends(fpm_cmd_settings) :: fpm_clean_settings
109-
logical :: unix ! is the system os unix?
108+
type, extends(fpm_cmd_settings) :: fpm_clean_settings
109+
logical :: unix
110110
character(len=:), allocatable :: calling_dir ! directory clean called from
111+
logical :: clean_skip=.false.
112+
logical :: clean_call=.false.
111113
end type
112114

113115
character(len=:),allocatable :: name
@@ -543,10 +545,17 @@ subroutine get_command_line_settings(cmd_settings)
543545
clean=lget('clean'))
544546

545547
case('clean')
546-
call set_args(common_args, help_clean)
548+
call set_args(common_args // &
549+
& ' --skip' // &
550+
& ' --all', &
551+
help_install, version_text)
547552
allocate(fpm_clean_settings :: cmd_settings)
548553
call get_current_directory(working_dir, error)
549-
cmd_settings=fpm_clean_settings(unix=unix, calling_dir=working_dir)
554+
cmd_settings=fpm_clean_settings( &
555+
& unix=unix, &
556+
& calling_dir=working_dir, &
557+
& clean_skip=lget('skip'), &
558+
clean_call=lget('all'))
550559

551560
case default
552561

@@ -627,7 +636,7 @@ subroutine set_help()
627636
' test Run the test programs ', &
628637
' update Update and manage project dependencies ', &
629638
' install Install project ', &
630-
' clean Delete the "build" directory ', &
639+
' clean Delete the build ', &
631640
' ', &
632641
' Enter "fpm --list" for a brief list of subcommand options. Enter ', &
633642
' "fpm --help" or "fpm SUBCOMMAND --help" for detailed descriptions. ', &
@@ -647,6 +656,7 @@ subroutine set_help()
647656
' [--list] [--compiler COMPILER_NAME] [-- ARGS] ', &
648657
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
649658
' [options] ', &
659+
' clean [--skip] [--all] ', &
650660
' ']
651661
help_usage=[character(len=80) :: &
652662
'' ]
@@ -743,13 +753,14 @@ subroutine set_help()
743753
' + build Compile the packages into the "build/" directory. ', &
744754
' + new Create a new Fortran package directory with sample files. ', &
745755
' + update Update the project dependencies. ', &
746-
' + run Run the local package binaries. defaults to all binaries ', &
756+
' + run Run the local package binaries. Defaults to all binaries ', &
747757
' for that release. ', &
748758
' + test Run the tests. ', &
749759
' + help Alternate to the --help switch for displaying help text. ', &
750760
' + list Display brief descriptions of all subcommands. ', &
751-
' + install Install project ', &
752-
' + clean Delete the "build" directory ', &
761+
' + install Install project. ', &
762+
' + clean Delete directories in the build/ directory, except ', &
763+
' dependencies. Prompts for confirmation to delete. ', &
753764
' ', &
754765
' Their syntax is ', &
755766
' ', &
@@ -766,7 +777,7 @@ subroutine set_help()
766777
' list [--list] ', &
767778
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
768779
' [options] ', &
769-
' clean ', &
780+
' clean [--skip] [-all] ', &
770781
' ', &
771782
'SUBCOMMAND OPTIONS ', &
772783
' -C, --directory PATH', &
@@ -782,6 +793,10 @@ subroutine set_help()
782793
' the fpm(1) command this shows a brief list of subcommands.', &
783794
' --runner CMD Provides a command to prefix program execution paths. ', &
784795
' -- ARGS Arguments to pass to executables. ', &
796+
' --skip Delete directories in the build/ directory without ', &
797+
' prompting, but skip dependencies. ', &
798+
' --all Delete directories in the build/ directory without ', &
799+
' prompting, including dependencies. ', &
785800
' ', &
786801
'VALID FOR ALL SUBCOMMANDS ', &
787802
' --help Show help text and exit ', &
@@ -832,7 +847,7 @@ subroutine set_help()
832847
' fpm new --help ', &
833848
' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title" ', &
834849
' fpm install --prefix ~/.local ', &
835-
' fpm clean ', &
850+
' fpm clean --all ', &
836851
' ', &
837852
'SEE ALSO ', &
838853
' ', &
@@ -1022,8 +1037,8 @@ subroutine set_help()
10221037
'NAME ', &
10231038
' new(1) - the fpm(1) subcommand to initialize a new project ', &
10241039
'SYNOPSIS ', &
1025-
' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
1026-
' [--full|--bare][--backfill] ', &
1040+
' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
1041+
' [--full|--bare][--backfill] ', &
10271042
' fpm new --help|--version ', &
10281043
' ', &
10291044
'DESCRIPTION ', &
@@ -1245,16 +1260,18 @@ subroutine set_help()
12451260
'' ]
12461261
help_clean=[character(len=80) :: &
12471262
'NAME', &
1248-
' clean(1) - delete the "build" directory', &
1263+
' clean(1) - delete the build', &
12491264
'', &
12501265
'SYNOPSIS', &
12511266
' fpm clean', &
12521267
'', &
12531268
'DESCRIPTION', &
1254-
' Prompts the user to confirm deletion of the "build" directory. If affirmative,', &
1255-
' the "build" directory in the project root is deleted using os system specific', &
1256-
' commands, forcing the recursive removal of all files and directories,', &
1257-
' including dependencies.', &
1269+
' Prompts the user to confirm deletion of the build. If affirmative,', &
1270+
' directories in the build/ directory are deleted, except dependencies.', &
1271+
'', &
1272+
'OPTIONS', &
1273+
' --skip delete the build without prompting but skip dependencies.', &
1274+
' --all delete the build without prompting including dependencies.', &
12581275
'' ]
12591276
end subroutine set_help
12601277

src/fpm_filesystem.F90

Lines changed: 15 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ module fpm_filesystem
1717
public :: is_hidden_file
1818
public :: read_lines, read_lines_expanded
1919
public :: which, run, LINE_BUFFER_LEN
20+
public :: os_delete_dir
2021

2122
integer, parameter :: LINE_BUFFER_LEN = 1000
2223

@@ -365,7 +366,7 @@ subroutine mkdir(dir, echo)
365366

366367
integer :: stat
367368
logical :: echo_local
368-
369+
369370
if(present(echo))then
370371
echo_local=echo
371372
else
@@ -384,7 +385,7 @@ subroutine mkdir(dir, echo)
384385

385386
case (OS_WINDOWS)
386387
call execute_command_line("mkdir " // windows_path(dir), exitstat=stat)
387-
388+
388389
if (echo_local) then
389390
write (*, '(" + ",2a)') 'mkdir ' // windows_path(dir)
390391
end if
@@ -885,7 +886,7 @@ subroutine run(cmd,echo,exitstat,verbose,redirect)
885886
else
886887
verbose_local=.true.
887888
end if
888-
889+
889890
if (present(redirect)) then
890891
redirect_str = ">"//redirect//" 2>&1"
891892
else
@@ -917,7 +918,7 @@ subroutine run(cmd,echo,exitstat,verbose,redirect)
917918
close(fh)
918919

919920
end if
920-
921+
921922
if (present(exitstat)) then
922923
exitstat = stat
923924
else
@@ -928,5 +929,15 @@ subroutine run(cmd,echo,exitstat,verbose,redirect)
928929

929930
end subroutine run
930931

932+
!> delete dir using system os remove directory commands
933+
subroutine os_delete_dir(unix, dir)
934+
logical, intent(in) :: unix
935+
character(len=*), intent(in) :: dir
936+
if (unix) then
937+
call run('rm -rf ' // dir, .false.)
938+
else
939+
call run('rmdir /s/q ' // dir, .false.)
940+
end if
941+
end subroutine os_delete_dir
931942

932943
end module fpm_filesystem

0 commit comments

Comments
 (0)