Skip to content

Commit 95dbca1

Browse files
authored
Merge pull request #665 from freevryheid/main
add clean command
2 parents 67132c4 + c5b95d5 commit 95dbca1

File tree

8 files changed

+283
-34
lines changed

8 files changed

+283
-34
lines changed

app/main.f90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,11 @@ program main
88
fpm_test_settings, &
99
fpm_install_settings, &
1010
fpm_update_settings, &
11+
fpm_clean_settings, &
1112
get_command_line_settings
1213
use fpm_error, only: error_t
1314
use fpm_filesystem, only: exists, parent_dir, join_path
14-
use fpm, only: cmd_build, cmd_run
15+
use fpm, only: cmd_build, cmd_run, cmd_clean
1516
use fpm_cmd_install, only: cmd_install
1617
use fpm_cmd_new, only: cmd_new
1718
use fpm_cmd_update, only : cmd_update
@@ -73,6 +74,8 @@ program main
7374
call cmd_install(settings)
7475
type is (fpm_update_settings)
7576
call cmd_update(settings)
77+
type is (fpm_clean_settings)
78+
call cmd_clean(settings)
7679
end select
7780

7881
if (allocated(project_root)) then

src/fpm.f90

Lines changed: 48 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,14 @@
11
module fpm
2-
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, fnv_1a
2+
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, fnv_1a, &
3+
lower, str_ends_with
34
use fpm_backend, only: build_package
45
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
5-
fpm_run_settings, fpm_install_settings, fpm_test_settings
6+
fpm_run_settings, fpm_install_settings, fpm_test_settings, &
7+
fpm_clean_settings
68
use fpm_dependency, only : new_dependency_tree
79
use fpm_environment, only: get_env
810
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, &
9-
basename, filewrite, mkdir, run
11+
basename, filewrite, mkdir, run, os_delete_dir
1012
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1113
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1214
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
@@ -22,9 +24,10 @@ module fpm
2224
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
2325
& stdout=>output_unit, &
2426
& stderr=>error_unit
27+
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
2528
implicit none
2629
private
27-
public :: cmd_build, cmd_run
30+
public :: cmd_build, cmd_run, cmd_clean
2831
public :: build_model, check_modules_for_duplicates
2932

3033
contains
@@ -502,4 +505,45 @@ end subroutine compact_list
502505

503506
end subroutine cmd_run
504507

508+
subroutine delete_skip(unix)
509+
!> delete directories in the build folder, skipping dependencies
510+
logical, intent(in) :: unix
511+
character(len=:), allocatable :: dir
512+
type(string_t), allocatable :: files(:)
513+
integer :: i
514+
call list_files('build', files, .false.)
515+
do i = 1, size(files)
516+
if (is_dir(files(i)%s)) then
517+
dir = files(i)%s
518+
if (.not.str_ends_with(dir,'dependencies')) call os_delete_dir(unix, dir)
519+
end if
520+
end do
521+
end subroutine delete_skip
522+
523+
subroutine cmd_clean(settings)
524+
!> fpm clean called
525+
class(fpm_clean_settings), intent(in) :: settings
526+
! character(len=:), allocatable :: dir
527+
! type(string_t), allocatable :: files(:)
528+
character(len=1) :: response
529+
if (is_dir('build')) then
530+
! remove the entire build directory
531+
if (settings%clean_call) then
532+
call os_delete_dir(settings%unix, 'build')
533+
return
534+
end if
535+
! remove the build directory but skip dependencies
536+
if (settings%clean_skip) then
537+
call delete_skip(settings%unix)
538+
return
539+
end if
540+
! prompt to remove the build directory but skip dependencies
541+
write(stdout, '(A)', advance='no') "Delete build, excluding dependencies (y/n)? "
542+
read(stdin, '(A1)') response
543+
if (lower(response) == 'y') call delete_skip(settings%unix)
544+
else
545+
write (stdout, '(A)') "fpm: No build directory found."
546+
end if
547+
end subroutine cmd_clean
548+
505549
end module fpm

src/fpm/installer.f90

Lines changed: 28 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,8 @@ module fpm_installer
3131
integer :: verbosity = 1
3232
!> Command to copy objects into the installation prefix
3333
character(len=:), allocatable :: copy
34+
!> Command to move objects into the installation prefix
35+
character(len=:), allocatable :: move
3436
!> Cached operating system
3537
integer :: os
3638
contains
@@ -69,11 +71,18 @@ module fpm_installer
6971
!> Copy command on Windows platforms
7072
character(len=*), parameter :: default_copy_win = "copy"
7173

74+
!> Move command on Unix platforms
75+
character(len=*), parameter :: default_move_unix = "mv"
76+
77+
!> Move command on Windows platforms
78+
character(len=*), parameter :: default_move_win = "move"
79+
80+
7281
contains
7382

7483
!> Create a new instance of an installer
7584
subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
76-
copy)
85+
copy, move)
7786
!> Instance of the installer
7887
type(installer_t), intent(out) :: self
7988
!> Path to installation directory
@@ -88,6 +97,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
8897
integer, intent(in), optional :: verbosity
8998
!> Copy command
9099
character(len=*), intent(in), optional :: copy
100+
!> Move command
101+
character(len=*), intent(in), optional :: move
91102

92103
self%os = get_os_type()
93104

@@ -101,6 +112,16 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
101112
end if
102113
end if
103114

115+
if (present(move)) then
116+
self%move = move
117+
else
118+
if (os_is_unix(self%os)) then
119+
self%move = default_move_unix
120+
else
121+
self%move = default_move_win
122+
end if
123+
end if
124+
104125
if (present(includedir)) then
105126
self%includedir = includedir
106127
else
@@ -238,7 +259,12 @@ subroutine install(self, source, destination, error)
238259
end if
239260
end if
240261

241-
call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error)
262+
! move instead of copy if already installed
263+
if (exists(install_dest)) then
264+
call self%run(self%move//' "'//source//'" "'//install_dest//'"', error)
265+
else
266+
call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error)
267+
end if
242268
if (allocated(error)) return
243269

244270
end subroutine install

src/fpm_command_line.f90

Lines changed: 67 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@
2323
!> ``fpm-help`` and ``fpm --list`` help pages below to make sure the help output
2424
!> is complete and consistent as well.
2525
module fpm_command_line
26-
use fpm_environment, only : get_os_type, get_env, &
26+
use fpm_environment, only : get_os_type, get_env, os_is_unix, &
2727
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
2828
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
@@ -47,6 +47,7 @@ module fpm_command_line
4747
fpm_run_settings, &
4848
fpm_test_settings, &
4949
fpm_update_settings, &
50+
fpm_clean_settings, &
5051
get_command_line_settings
5152

5253
type, abstract :: fpm_cmd_settings
@@ -104,6 +105,13 @@ module fpm_command_line
104105
logical :: clean
105106
end type
106107

108+
type, extends(fpm_cmd_settings) :: fpm_clean_settings
109+
logical :: unix
110+
character(len=:), allocatable :: calling_dir ! directory clean called from
111+
logical :: clean_skip=.false.
112+
logical :: clean_call=.false.
113+
end type
114+
107115
character(len=:),allocatable :: name
108116
character(len=:),allocatable :: os_type
109117
character(len=ibug),allocatable :: names(:)
@@ -113,9 +121,10 @@ module fpm_command_line
113121
character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), &
114122
& help_test(:), help_build(:), help_usage(:), help_runner(:), &
115123
& help_text(:), help_install(:), help_help(:), help_update(:), &
116-
& help_list(:), help_list_dash(:), help_list_nodash(:)
124+
& help_list(:), help_list_dash(:), help_list_nodash(:), &
125+
& help_clean(:)
117126
character(len=20),parameter :: manual(*)=[ character(len=20) ::&
118-
& ' ', 'fpm', 'new', 'build', 'run', &
127+
& ' ', 'fpm', 'new', 'build', 'run', 'clean', &
119128
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
120129

121130
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_ldflag, &
@@ -174,6 +183,8 @@ subroutine get_command_line_settings(cmd_settings)
174183
character(len=4096) :: cmdarg
175184
integer :: i
176185
integer :: widest
186+
integer :: os
187+
logical :: unix
177188
type(fpm_install_settings), allocatable :: install_settings
178189
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
179190
& c_compiler, archiver
@@ -184,8 +195,9 @@ subroutine get_command_line_settings(cmd_settings)
184195
type(error_t), allocatable :: error
185196

186197
call set_help()
198+
os = get_os_type()
187199
! text for --version switch,
188-
select case (get_os_type())
200+
select case (os)
189201
case (OS_LINUX); os_type = "OS Type: Linux"
190202
case (OS_MACOS); os_type = "OS Type: macOS"
191203
case (OS_WINDOWS); os_type = "OS Type: Windows"
@@ -196,6 +208,7 @@ subroutine get_command_line_settings(cmd_settings)
196208
case (OS_UNKNOWN); os_type = "OS Type: Unknown"
197209
case default ; os_type = "OS Type: UNKNOWN"
198210
end select
211+
unix = os_is_unix(os)
199212
version_text = [character(len=80) :: &
200213
& 'Version: 0.5.0, alpha', &
201214
& 'Program: fpm(1)', &
@@ -321,7 +334,7 @@ subroutine get_command_line_settings(cmd_settings)
321334
select case(size(unnamed))
322335
case(1)
323336
if(lget('backfill'))then
324-
name='.'
337+
name='.'
325338
else
326339
write(stderr,'(*(7x,g0,/))') &
327340
& '<USAGE> fpm new NAME [[--lib|--src] [--app] [--test] [--example]]|[--full|--bare] [--backfill]'
@@ -424,6 +437,8 @@ subroutine get_command_line_settings(cmd_settings)
424437
help_text=[character(len=widest) :: help_text, help_help]
425438
case('version' )
426439
help_text=[character(len=widest) :: help_text, version_text]
440+
case('clean' )
441+
help_text=[character(len=widest) :: help_text, help_clean]
427442
case default
428443
help_text=[character(len=widest) :: help_text, &
429444
& '<ERROR> unknown help topic "'//trim(unnamed(i))//'"']
@@ -469,6 +484,7 @@ subroutine get_command_line_settings(cmd_settings)
469484
if(lget('list'))then
470485
call printhelp(help_list_dash)
471486
endif
487+
472488
case('test')
473489
call set_args(common_args // compiler_args // run_args // ' --', &
474490
help_test,version_text)
@@ -528,6 +544,19 @@ subroutine get_command_line_settings(cmd_settings)
528544
fetch_only=lget('fetch-only'), verbose=lget('verbose'), &
529545
clean=lget('clean'))
530546

547+
case('clean')
548+
call set_args(common_args // &
549+
& ' --skip' // &
550+
& ' --all', &
551+
help_clean, version_text)
552+
allocate(fpm_clean_settings :: cmd_settings)
553+
call get_current_directory(working_dir, error)
554+
cmd_settings=fpm_clean_settings( &
555+
& unix=unix, &
556+
& calling_dir=working_dir, &
557+
& clean_skip=lget('skip'), &
558+
clean_call=lget('all'))
559+
531560
case default
532561

533562
if(which('fpm-'//cmdarg).ne.'')then
@@ -607,6 +636,7 @@ subroutine set_help()
607636
' test Run the test programs ', &
608637
' update Update and manage project dependencies ', &
609638
' install Install project ', &
639+
' clean Delete the build ', &
610640
' ', &
611641
' Enter "fpm --list" for a brief list of subcommand options. Enter ', &
612642
' "fpm --help" or "fpm SUBCOMMAND --help" for detailed descriptions. ', &
@@ -626,6 +656,7 @@ subroutine set_help()
626656
' [--list] [--compiler COMPILER_NAME] [-- ARGS] ', &
627657
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
628658
' [options] ', &
659+
' clean [--skip] [--all] ', &
629660
' ']
630661
help_usage=[character(len=80) :: &
631662
'' ]
@@ -722,12 +753,14 @@ subroutine set_help()
722753
' + build Compile the packages into the "build/" directory. ', &
723754
' + new Create a new Fortran package directory with sample files. ', &
724755
' + update Update the project dependencies. ', &
725-
' + run Run the local package binaries. defaults to all binaries ', &
756+
' + run Run the local package binaries. Defaults to all binaries ', &
726757
' for that release. ', &
727758
' + test Run the tests. ', &
728759
' + help Alternate to the --help switch for displaying help text. ', &
729760
' + list Display brief descriptions of all subcommands. ', &
730-
' + install Install project ', &
761+
' + install Install project. ', &
762+
' + clean Delete directories in the "build/" directory, except ', &
763+
' dependencies. Prompts for confirmation to delete. ', &
731764
' ', &
732765
' Their syntax is ', &
733766
' ', &
@@ -743,7 +776,8 @@ subroutine set_help()
743776
' help [NAME(s)] ', &
744777
' list [--list] ', &
745778
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
746-
' [options] ', &
779+
' [options] ', &
780+
' clean [--skip] [--all] ', &
747781
' ', &
748782
'SUBCOMMAND OPTIONS ', &
749783
' -C, --directory PATH', &
@@ -759,6 +793,10 @@ subroutine set_help()
759793
' the fpm(1) command this shows a brief list of subcommands.', &
760794
' --runner CMD Provides a command to prefix program execution paths. ', &
761795
' -- 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. ', &
762800
' ', &
763801
'VALID FOR ALL SUBCOMMANDS ', &
764802
' --help Show help text and exit ', &
@@ -788,8 +826,8 @@ subroutine set_help()
788826
' # my build options ', &
789827
' options build ', &
790828
' options --compiler gfortran ', &
791-
' options --flag "-pg -static -pthread -Wunreachable-code -Wunused \', &
792-
' -Wuninitialized -g -O -fbacktrace -fdump-core -fno-underscoring \', &
829+
' options --flag "-pg -static -pthread -Wunreachable-code -Wunused ', &
830+
' -Wuninitialized -g -O -fbacktrace -fdump-core -fno-underscoring ', &
793831
' -frecord-marker=4 -L/usr/X11R6/lib -L/usr/X11R6/lib64 -lX11" ', &
794832
' ', &
795833
' Note --flag would have to be on one line as response files do not ', &
@@ -809,6 +847,7 @@ subroutine set_help()
809847
' fpm new --help ', &
810848
' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title" ', &
811849
' fpm install --prefix ~/.local ', &
850+
' fpm clean --all ', &
812851
' ', &
813852
'SEE ALSO ', &
814853
' ', &
@@ -998,8 +1037,8 @@ subroutine set_help()
9981037
'NAME ', &
9991038
' new(1) - the fpm(1) subcommand to initialize a new project ', &
10001039
'SYNOPSIS ', &
1001-
' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
1002-
' [--full|--bare][--backfill] ', &
1040+
' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
1041+
' [--full|--bare][--backfill] ', &
10031042
' fpm new --help|--version ', &
10041043
' ', &
10051044
'DESCRIPTION ', &
@@ -1219,7 +1258,22 @@ subroutine set_help()
12191258
'', &
12201259
' fpm install --prefix $PWD --bindir exe', &
12211260
'' ]
1222-
end subroutine set_help
1261+
help_clean=[character(len=80) :: &
1262+
'NAME', &
1263+
' clean(1) - delete the build', &
1264+
'', &
1265+
'SYNOPSIS', &
1266+
' fpm clean', &
1267+
'', &
1268+
'DESCRIPTION', &
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.', &
1275+
'' ]
1276+
end subroutine set_help
12231277

12241278
subroutine get_char_arg(var, arg)
12251279
character(len=:), allocatable, intent(out) :: var

0 commit comments

Comments
 (0)