cmd_clean Subroutine

public subroutine cmd_clean(settings)

Delete the build directory including or excluding dependencies. Can be used to clear the registry cache.

Arguments

Type IntentOptional Attributes Name
class(fpm_clean_settings), intent(in) :: settings

Settings for the clean command.


Source Code

subroutine cmd_clean(settings)
    !> Settings for the clean command.
    class(fpm_clean_settings), intent(in) :: settings

    character :: user_response
    type(fpm_global_settings) :: global_settings
    type(error_t), allocatable :: error

    ! Clear registry cache
    if (settings%registry_cache) then
        call get_global_settings(global_settings, error) 
        if (allocated(error)) return

        call os_delete_dir(os_is_unix(), global_settings%registry_settings%cache_path)
    end if

    if (is_dir('build')) then
        ! Remove the entire build directory
        if (settings%clean_all) then
            call os_delete_dir(os_is_unix(), 'build'); return
        ! Remove the build directory but skip dependencies
        else if (settings%clean_skip) then
            call delete_skip(os_is_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)') user_response
        if (lower(user_response) == 'y') call delete_skip(os_is_unix())
    else
        write (stdout, '(A)') "fpm: No build directory found."
    end if
end subroutine cmd_clean