From f87fac1d688a411936cf5cbc0eb0c4845056470b Mon Sep 17 00:00:00 2001 From: minhqdao Date: Thu, 22 Jun 2023 00:02:18 +0700 Subject: [PATCH] Clean up clean command --- src/fpm.f90 | 35 +++++++++++++++++++---------------- src/fpm_command_line.f90 | 16 +++++----------- 2 files changed, 24 insertions(+), 27 deletions(-) diff --git a/src/fpm.f90 b/src/fpm.f90 index 9e82b91d97..50d39a8842 100644 --- a/src/fpm.f90 +++ b/src/fpm.f90 @@ -21,10 +21,12 @@ module fpm use fpm_manifest, only : get_package_data, package_config_t use fpm_meta, only : resolve_metapackages use fpm_error, only : error_t, fatal_error, fpm_stop -use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & - & stdout=>output_unit, & - & stderr=>error_unit +use, intrinsic :: iso_fortran_env, only : stdin => input_unit, & + & stdout => output_unit, & + & stderr => error_unit use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer +use fpm_environment, only: os_is_unix + implicit none private public :: cmd_build, cmd_run, cmd_clean @@ -676,27 +678,28 @@ subroutine delete_skip(is_unix) end do end subroutine delete_skip +!> Delete the build directory including or excluding dependencies. subroutine cmd_clean(settings) - !> fpm clean called + !> Settings for the clean command. class(fpm_clean_settings), intent(in) :: settings - ! character(len=:), allocatable :: dir - ! type(string_t), allocatable :: files(:) - character(len=1) :: response + + character :: user_response + if (is_dir('build')) then - ! remove the entire build directory + ! Remove the entire build directory if (settings%clean_call) then - call os_delete_dir(settings%is_unix, 'build') - return + call os_delete_dir(os_is_unix(), 'build'); return end if - ! remove the build directory but skip dependencies + + ! Remove the build directory but skip dependencies if (settings%clean_skip) then - call delete_skip(settings%is_unix) - return + call delete_skip(os_is_unix()); return end if - ! prompt to remove the build directory but skip dependencies + + ! Prompt to remove the build directory but skip dependencies write(stdout, '(A)', advance='no') "Delete build, excluding dependencies (y/n)? " - read(stdin, '(A1)') response - if (lower(response) == 'y') call delete_skip(settings%is_unix) + read(stdin, '(A1)') user_response + if (lower(user_response) == 'y') call delete_skip(os_is_unix()) else write (stdout, '(A)') "fpm: No build directory found." end if diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90 index f1ced79308..306b79a535 100644 --- a/src/fpm_command_line.f90 +++ b/src/fpm_command_line.f90 @@ -23,7 +23,7 @@ !> ``fpm-help`` and ``fpm --list`` help pages below to make sure the help output !> is complete and consistent as well. module fpm_command_line -use fpm_environment, only : get_os_type, get_env, os_is_unix, & +use fpm_environment, only : get_os_type, get_env, & OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, & OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified @@ -112,10 +112,8 @@ module fpm_command_line end type type, extends(fpm_cmd_settings) :: fpm_clean_settings - logical :: is_unix - character(len=:), allocatable :: calling_dir ! directory clean called from - logical :: clean_skip=.false. - logical :: clean_call=.false. + logical :: clean_skip = .false. + logical :: clean_call = .false. end type type, extends(fpm_build_settings) :: fpm_publish_settings @@ -217,7 +215,6 @@ subroutine get_command_line_settings(cmd_settings) character(len=4096) :: cmdarg integer :: i integer :: os - logical :: is_unix type(fpm_install_settings), allocatable :: install_settings type(version_t) :: version character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, & @@ -243,7 +240,6 @@ subroutine get_command_line_settings(cmd_settings) case (OS_UNKNOWN); os_type = "OS Type: Unknown" case default ; os_type = "OS Type: UNKNOWN" end select - is_unix = os_is_unix(os) ! Get current release version version = fpm_version() @@ -588,7 +584,7 @@ subroutine get_command_line_settings(cmd_settings) & build_tests=.true., & & name=names, & & runner=val_runner, & - & verbose=lget('verbose') ) + & verbose=lget('verbose')) case('update') call set_args(common_args // ' --fetch-only F --clean F', & @@ -613,10 +609,8 @@ subroutine get_command_line_settings(cmd_settings) allocate(fpm_clean_settings :: cmd_settings) call get_current_directory(working_dir, error) cmd_settings=fpm_clean_settings( & - & is_unix=is_unix, & - & calling_dir=working_dir, & & clean_skip=lget('skip'), & - clean_call=lget('all')) + & clean_call=lget('all')) case('publish') call set_args(common_args // compiler_args //'&