Skip to content

Commit

Permalink
Merge pull request #665 from freevryheid/main
Browse files Browse the repository at this point in the history
add clean command
  • Loading branch information
LKedward authored Apr 21, 2022
2 parents 67132c4 + c5b95d5 commit 95dbca1
Show file tree
Hide file tree
Showing 8 changed files with 283 additions and 34 deletions.
5 changes: 4 additions & 1 deletion app/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,11 @@ program main
fpm_test_settings, &
fpm_install_settings, &
fpm_update_settings, &
fpm_clean_settings, &
get_command_line_settings
use fpm_error, only: error_t
use fpm_filesystem, only: exists, parent_dir, join_path
use fpm, only: cmd_build, cmd_run
use fpm, only: cmd_build, cmd_run, cmd_clean
use fpm_cmd_install, only: cmd_install
use fpm_cmd_new, only: cmd_new
use fpm_cmd_update, only : cmd_update
Expand Down Expand Up @@ -73,6 +74,8 @@ program main
call cmd_install(settings)
type is (fpm_update_settings)
call cmd_update(settings)
type is (fpm_clean_settings)
call cmd_clean(settings)
end select

if (allocated(project_root)) then
Expand Down
52 changes: 48 additions & 4 deletions src/fpm.f90
Original file line number Diff line number Diff line change
@@ -1,12 +1,14 @@
module fpm
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, fnv_1a
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, fnv_1a, &
lower, str_ends_with
use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
fpm_run_settings, fpm_install_settings, fpm_test_settings, &
fpm_clean_settings
use fpm_dependency, only : new_dependency_tree
use fpm_environment, only: get_env
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, &
basename, filewrite, mkdir, run
basename, filewrite, mkdir, run, os_delete_dir
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
Expand All @@ -22,9 +24,10 @@ module fpm
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
implicit none
private
public :: cmd_build, cmd_run
public :: cmd_build, cmd_run, cmd_clean
public :: build_model, check_modules_for_duplicates

contains
Expand Down Expand Up @@ -502,4 +505,45 @@ end subroutine compact_list

end subroutine cmd_run

subroutine delete_skip(unix)
!> delete directories in the build folder, skipping dependencies
logical, intent(in) :: unix
character(len=:), allocatable :: dir
type(string_t), allocatable :: files(:)
integer :: i
call list_files('build', files, .false.)
do i = 1, size(files)
if (is_dir(files(i)%s)) then
dir = files(i)%s
if (.not.str_ends_with(dir,'dependencies')) call os_delete_dir(unix, dir)
end if
end do
end subroutine delete_skip

subroutine cmd_clean(settings)
!> fpm clean called
class(fpm_clean_settings), intent(in) :: settings
! character(len=:), allocatable :: dir
! type(string_t), allocatable :: files(:)
character(len=1) :: response
if (is_dir('build')) then
! remove the entire build directory
if (settings%clean_call) then
call os_delete_dir(settings%unix, 'build')
return
end if
! remove the build directory but skip dependencies
if (settings%clean_skip) then
call delete_skip(settings%unix)
return
end if
! 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%unix)
else
write (stdout, '(A)') "fpm: No build directory found."
end if
end subroutine cmd_clean

end module fpm
30 changes: 28 additions & 2 deletions src/fpm/installer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,8 @@ module fpm_installer
integer :: verbosity = 1
!> Command to copy objects into the installation prefix
character(len=:), allocatable :: copy
!> Command to move objects into the installation prefix
character(len=:), allocatable :: move
!> Cached operating system
integer :: os
contains
Expand Down Expand Up @@ -69,11 +71,18 @@ module fpm_installer
!> Copy command on Windows platforms
character(len=*), parameter :: default_copy_win = "copy"

!> Move command on Unix platforms
character(len=*), parameter :: default_move_unix = "mv"

!> Move command on Windows platforms
character(len=*), parameter :: default_move_win = "move"


contains

!> Create a new instance of an installer
subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
copy)
copy, move)
!> Instance of the installer
type(installer_t), intent(out) :: self
!> Path to installation directory
Expand All @@ -88,6 +97,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
integer, intent(in), optional :: verbosity
!> Copy command
character(len=*), intent(in), optional :: copy
!> Move command
character(len=*), intent(in), optional :: move

self%os = get_os_type()

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

if (present(move)) then
self%move = move
else
if (os_is_unix(self%os)) then
self%move = default_move_unix
else
self%move = default_move_win
end if
end if

if (present(includedir)) then
self%includedir = includedir
else
Expand Down Expand Up @@ -238,7 +259,12 @@ subroutine install(self, source, destination, error)
end if
end if

call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error)
! move instead of copy if already installed
if (exists(install_dest)) then
call self%run(self%move//' "'//source//'" "'//install_dest//'"', error)
else
call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error)
end if
if (allocated(error)) return

end subroutine install
Expand Down
80 changes: 67 additions & 13 deletions src/fpm_command_line.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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, &
use fpm_environment, only : get_os_type, get_env, os_is_unix, &
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
Expand All @@ -47,6 +47,7 @@ module fpm_command_line
fpm_run_settings, &
fpm_test_settings, &
fpm_update_settings, &
fpm_clean_settings, &
get_command_line_settings

type, abstract :: fpm_cmd_settings
Expand Down Expand Up @@ -104,6 +105,13 @@ module fpm_command_line
logical :: clean
end type

type, extends(fpm_cmd_settings) :: fpm_clean_settings
logical :: unix
character(len=:), allocatable :: calling_dir ! directory clean called from
logical :: clean_skip=.false.
logical :: clean_call=.false.
end type

character(len=:),allocatable :: name
character(len=:),allocatable :: os_type
character(len=ibug),allocatable :: names(:)
Expand All @@ -113,9 +121,10 @@ module fpm_command_line
character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), &
& help_test(:), help_build(:), help_usage(:), help_runner(:), &
& help_text(:), help_install(:), help_help(:), help_update(:), &
& help_list(:), help_list_dash(:), help_list_nodash(:)
& help_list(:), help_list_dash(:), help_list_nodash(:), &
& help_clean(:)
character(len=20),parameter :: manual(*)=[ character(len=20) ::&
& ' ', 'fpm', 'new', 'build', 'run', &
& ' ', 'fpm', 'new', 'build', 'run', 'clean', &
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]

character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_ldflag, &
Expand Down Expand Up @@ -174,6 +183,8 @@ subroutine get_command_line_settings(cmd_settings)
character(len=4096) :: cmdarg
integer :: i
integer :: widest
integer :: os
logical :: unix
type(fpm_install_settings), allocatable :: install_settings
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
& c_compiler, archiver
Expand All @@ -184,8 +195,9 @@ subroutine get_command_line_settings(cmd_settings)
type(error_t), allocatable :: error

call set_help()
os = get_os_type()
! text for --version switch,
select case (get_os_type())
select case (os)
case (OS_LINUX); os_type = "OS Type: Linux"
case (OS_MACOS); os_type = "OS Type: macOS"
case (OS_WINDOWS); os_type = "OS Type: Windows"
Expand All @@ -196,6 +208,7 @@ subroutine get_command_line_settings(cmd_settings)
case (OS_UNKNOWN); os_type = "OS Type: Unknown"
case default ; os_type = "OS Type: UNKNOWN"
end select
unix = os_is_unix(os)
version_text = [character(len=80) :: &
& 'Version: 0.5.0, alpha', &
& 'Program: fpm(1)', &
Expand Down Expand Up @@ -321,7 +334,7 @@ subroutine get_command_line_settings(cmd_settings)
select case(size(unnamed))
case(1)
if(lget('backfill'))then
name='.'
name='.'
else
write(stderr,'(*(7x,g0,/))') &
& '<USAGE> fpm new NAME [[--lib|--src] [--app] [--test] [--example]]|[--full|--bare] [--backfill]'
Expand Down Expand Up @@ -424,6 +437,8 @@ subroutine get_command_line_settings(cmd_settings)
help_text=[character(len=widest) :: help_text, help_help]
case('version' )
help_text=[character(len=widest) :: help_text, version_text]
case('clean' )
help_text=[character(len=widest) :: help_text, help_clean]
case default
help_text=[character(len=widest) :: help_text, &
& '<ERROR> unknown help topic "'//trim(unnamed(i))//'"']
Expand Down Expand Up @@ -469,6 +484,7 @@ subroutine get_command_line_settings(cmd_settings)
if(lget('list'))then
call printhelp(help_list_dash)
endif

case('test')
call set_args(common_args // compiler_args // run_args // ' --', &
help_test,version_text)
Expand Down Expand Up @@ -528,6 +544,19 @@ subroutine get_command_line_settings(cmd_settings)
fetch_only=lget('fetch-only'), verbose=lget('verbose'), &
clean=lget('clean'))

case('clean')
call set_args(common_args // &
& ' --skip' // &
& ' --all', &
help_clean, version_text)
allocate(fpm_clean_settings :: cmd_settings)
call get_current_directory(working_dir, error)
cmd_settings=fpm_clean_settings( &
& unix=unix, &
& calling_dir=working_dir, &
& clean_skip=lget('skip'), &
clean_call=lget('all'))

case default

if(which('fpm-'//cmdarg).ne.'')then
Expand Down Expand Up @@ -607,6 +636,7 @@ subroutine set_help()
' test Run the test programs ', &
' update Update and manage project dependencies ', &
' install Install project ', &
' clean Delete the build ', &
' ', &
' Enter "fpm --list" for a brief list of subcommand options. Enter ', &
' "fpm --help" or "fpm SUBCOMMAND --help" for detailed descriptions. ', &
Expand All @@ -626,6 +656,7 @@ subroutine set_help()
' [--list] [--compiler COMPILER_NAME] [-- ARGS] ', &
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
' [options] ', &
' clean [--skip] [--all] ', &
' ']
help_usage=[character(len=80) :: &
'' ]
Expand Down Expand Up @@ -722,12 +753,14 @@ subroutine set_help()
' + build Compile the packages into the "build/" directory. ', &
' + new Create a new Fortran package directory with sample files. ', &
' + update Update the project dependencies. ', &
' + run Run the local package binaries. defaults to all binaries ', &
' + run Run the local package binaries. Defaults to all binaries ', &
' for that release. ', &
' + test Run the tests. ', &
' + help Alternate to the --help switch for displaying help text. ', &
' + list Display brief descriptions of all subcommands. ', &
' + install Install project ', &
' + install Install project. ', &
' + clean Delete directories in the "build/" directory, except ', &
' dependencies. Prompts for confirmation to delete. ', &
' ', &
' Their syntax is ', &
' ', &
Expand All @@ -743,7 +776,8 @@ subroutine set_help()
' help [NAME(s)] ', &
' list [--list] ', &
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
' [options] ', &
' [options] ', &
' clean [--skip] [--all] ', &
' ', &
'SUBCOMMAND OPTIONS ', &
' -C, --directory PATH', &
Expand All @@ -759,6 +793,10 @@ subroutine set_help()
' the fpm(1) command this shows a brief list of subcommands.', &
' --runner CMD Provides a command to prefix program execution paths. ', &
' -- ARGS Arguments to pass to executables. ', &
' --skip Delete directories in the build/ directory without ', &
' prompting, but skip dependencies. ', &
' --all Delete directories in the build/ directory without ', &
' prompting, including dependencies. ', &
' ', &
'VALID FOR ALL SUBCOMMANDS ', &
' --help Show help text and exit ', &
Expand Down Expand Up @@ -788,8 +826,8 @@ subroutine set_help()
' # my build options ', &
' options build ', &
' options --compiler gfortran ', &
' options --flag "-pg -static -pthread -Wunreachable-code -Wunused \', &
' -Wuninitialized -g -O -fbacktrace -fdump-core -fno-underscoring \', &
' options --flag "-pg -static -pthread -Wunreachable-code -Wunused ', &
' -Wuninitialized -g -O -fbacktrace -fdump-core -fno-underscoring ', &
' -frecord-marker=4 -L/usr/X11R6/lib -L/usr/X11R6/lib64 -lX11" ', &
' ', &
' Note --flag would have to be on one line as response files do not ', &
Expand All @@ -809,6 +847,7 @@ subroutine set_help()
' fpm new --help ', &
' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title" ', &
' fpm install --prefix ~/.local ', &
' fpm clean --all ', &
' ', &
'SEE ALSO ', &
' ', &
Expand Down Expand Up @@ -998,8 +1037,8 @@ subroutine set_help()
'NAME ', &
' new(1) - the fpm(1) subcommand to initialize a new project ', &
'SYNOPSIS ', &
' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' fpm new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' fpm new --help|--version ', &
' ', &
'DESCRIPTION ', &
Expand Down Expand Up @@ -1219,7 +1258,22 @@ subroutine set_help()
'', &
' fpm install --prefix $PWD --bindir exe', &
'' ]
end subroutine set_help
help_clean=[character(len=80) :: &
'NAME', &
' clean(1) - delete the build', &
'', &
'SYNOPSIS', &
' fpm clean', &
'', &
'DESCRIPTION', &
' Prompts the user to confirm deletion of the build. If affirmative,', &
' directories in the build/ directory are deleted, except dependencies.', &
'', &
'OPTIONS', &
' --skip delete the build without prompting but skip dependencies.', &
' --all delete the build without prompting including dependencies.', &
'' ]
end subroutine set_help

subroutine get_char_arg(var, arg)
character(len=:), allocatable, intent(out) :: var
Expand Down
Loading

0 comments on commit 95dbca1

Please sign in to comment.