Skip to content

Commit f87fac1

Browse files
committed
Clean up clean command
1 parent 33adb0e commit f87fac1

File tree

2 files changed

+24
-27
lines changed

2 files changed

+24
-27
lines changed

src/fpm.f90

Lines changed: 19 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -21,10 +21,12 @@ module fpm
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
24-
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
25-
& stdout=>output_unit, &
26-
& stderr=>error_unit
24+
use, intrinsic :: iso_fortran_env, only : stdin => input_unit, &
25+
& stdout => output_unit, &
26+
& stderr => error_unit
2727
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
28+
use fpm_environment, only: os_is_unix
29+
2830
implicit none
2931
private
3032
public :: cmd_build, cmd_run, cmd_clean
@@ -676,27 +678,28 @@ subroutine delete_skip(is_unix)
676678
end do
677679
end subroutine delete_skip
678680

681+
!> Delete the build directory including or excluding dependencies.
679682
subroutine cmd_clean(settings)
680-
!> fpm clean called
683+
!> Settings for the clean command.
681684
class(fpm_clean_settings), intent(in) :: settings
682-
! character(len=:), allocatable :: dir
683-
! type(string_t), allocatable :: files(:)
684-
character(len=1) :: response
685+
686+
character :: user_response
687+
685688
if (is_dir('build')) then
686-
! remove the entire build directory
689+
! Remove the entire build directory
687690
if (settings%clean_call) then
688-
call os_delete_dir(settings%is_unix, 'build')
689-
return
691+
call os_delete_dir(os_is_unix(), 'build'); return
690692
end if
691-
! remove the build directory but skip dependencies
693+
694+
! Remove the build directory but skip dependencies
692695
if (settings%clean_skip) then
693-
call delete_skip(settings%is_unix)
694-
return
696+
call delete_skip(os_is_unix()); return
695697
end if
696-
! prompt to remove the build directory but skip dependencies
698+
699+
! Prompt to remove the build directory but skip dependencies
697700
write(stdout, '(A)', advance='no') "Delete build, excluding dependencies (y/n)? "
698-
read(stdin, '(A1)') response
699-
if (lower(response) == 'y') call delete_skip(settings%is_unix)
701+
read(stdin, '(A1)') user_response
702+
if (lower(user_response) == 'y') call delete_skip(os_is_unix())
700703
else
701704
write (stdout, '(A)') "fpm: No build directory found."
702705
end if

src/fpm_command_line.f90

Lines changed: 5 additions & 11 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, os_is_unix, &
26+
use fpm_environment, only : get_os_type, get_env, &
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
@@ -112,10 +112,8 @@ module fpm_command_line
112112
end type
113113

114114
type, extends(fpm_cmd_settings) :: fpm_clean_settings
115-
logical :: is_unix
116-
character(len=:), allocatable :: calling_dir ! directory clean called from
117-
logical :: clean_skip=.false.
118-
logical :: clean_call=.false.
115+
logical :: clean_skip = .false.
116+
logical :: clean_call = .false.
119117
end type
120118

121119
type, extends(fpm_build_settings) :: fpm_publish_settings
@@ -217,7 +215,6 @@ subroutine get_command_line_settings(cmd_settings)
217215
character(len=4096) :: cmdarg
218216
integer :: i
219217
integer :: os
220-
logical :: is_unix
221218
type(fpm_install_settings), allocatable :: install_settings
222219
type(version_t) :: version
223220
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
@@ -243,7 +240,6 @@ subroutine get_command_line_settings(cmd_settings)
243240
case (OS_UNKNOWN); os_type = "OS Type: Unknown"
244241
case default ; os_type = "OS Type: UNKNOWN"
245242
end select
246-
is_unix = os_is_unix(os)
247243

248244
! Get current release version
249245
version = fpm_version()
@@ -588,7 +584,7 @@ subroutine get_command_line_settings(cmd_settings)
588584
& build_tests=.true., &
589585
& name=names, &
590586
& runner=val_runner, &
591-
& verbose=lget('verbose') )
587+
& verbose=lget('verbose'))
592588

593589
case('update')
594590
call set_args(common_args // ' --fetch-only F --clean F', &
@@ -613,10 +609,8 @@ subroutine get_command_line_settings(cmd_settings)
613609
allocate(fpm_clean_settings :: cmd_settings)
614610
call get_current_directory(working_dir, error)
615611
cmd_settings=fpm_clean_settings( &
616-
& is_unix=is_unix, &
617-
& calling_dir=working_dir, &
618612
& clean_skip=lget('skip'), &
619-
clean_call=lget('all'))
613+
& clean_call=lget('all'))
620614

621615
case('publish')
622616
call set_args(common_args // compiler_args //'&

0 commit comments

Comments
 (0)