% Copyright (C) 2002-2004 David Roundy % % This program is free software; you can redistribute it and/or modify % it under the terms of the GNU General Public License as published by % the Free Software Foundation; either version 2, or (at your option) % any later version. % % This program is distributed in the hope that it will be useful, % but WITHOUT ANY WARRANTY; without even the implied warranty of % MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the % GNU General Public License for more details. % % You should have received a copy of the GNU General Public License % along with this program; see the file COPYING. If not, write to % the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, % Boston, MA 02110-1301, USA. \subsection{darcs remove} \begin{code} {-# OPTIONS_GHC -cpp #-} module Darcs.Commands.Remove ( remove, rm, unadd ) where import Darcs.Commands ( DarcsCommand(..), nodefaults, command_alias, command_stub, ) import Darcs.Arguments ( DarcsFlag, getRepoPaths, list_registered_files, working_repo_dir, umask_option ) import Darcs.RepoPath ( SubPath, toFilePath, sp2fn ) import Darcs.Repository ( Repository, withRepoLock, ($-), amInRepository, slurp_pending, slurp_recorded, get_unrecorded, add_to_pending ) import Darcs.Patch ( RepoPatch, Prim, apply_to_slurpy, adddir, rmdir, addfile, rmfile ) import Darcs.Patch.Ordered ( FL(..), (+>+) ) import Darcs.SlurpDirectory ( slurp_removedir, slurp_removefile ) import Darcs.Repository.Prefs ( filetype_function ) import Darcs.Diff ( smart_diff ) #include "impossible.h" \end{code} \begin{code} remove_description :: String remove_description = "Remove one or more files or directories from the repository." \end{code} \options{remove} \haskell{remove_help} \begin{code} remove_help :: String remove_help = "Remove should be called when you want to remove a file from your project,\n"++ "but don't actually want to delete the file. Otherwise just delete the\n"++ "file or directory, and darcs will notice that it has been removed.\n" ++ "Be aware that the file WILL be deleted from any other copy of the\n" ++ "repository to which you later apply the patch.\n" \end{code} \begin{code} remove :: DarcsCommand remove = DarcsCommand {command_name = "remove", command_help = remove_help, command_description = remove_description, command_extra_args = -1, command_extra_arg_help = [" ..."], command_command = remove_cmd, command_prereq = amInRepository, command_get_arg_possibilities = list_registered_files, command_argdefaults = nodefaults, command_advanced_options = [umask_option], command_basic_options = [working_repo_dir]} \end{code} \begin{code} remove_cmd :: [DarcsFlag] -> [String] -> IO () remove_cmd opts relargs = withRepoLock opts $- \repository -> do args <- getRepoPaths opts relargs p <- make_remove_patch repository args add_to_pending repository p make_remove_patch :: RepoPatch p => Repository p -> [SubPath] -> IO (FL Prim) make_remove_patch repository files = do s <- slurp_pending repository srecorded <- slurp_recorded repository pend <- get_unrecorded repository let sunrec = fromJust $ apply_to_slurpy pend srecorded wt <- filetype_function mrp wt s sunrec files where mrp wt s sunrec (f:fs) = case slurp_removedir fn s of Just s' -> case slurp_removedir fn sunrec of Just sunrec' -> do rest <- mrp wt s' sunrec' fs return $ rmdir f_fp :>: rest Nothing -> do rest <- mrp wt s' sunrec fs return $ adddir f_fp :>: rmdir f_fp :>: rest Nothing -> case slurp_removefile fn s of Nothing -> fail $ "Can't remove "++f_fp Just s' -> case slurp_removefile fn sunrec of Nothing -> do rest <- mrp wt s' sunrec fs return $ addfile f_fp :>: rmfile f_fp :>: rest Just sunrec' -> do rest <- mrp wt s' sunrec' fs let newp = smart_diff [] wt sunrec sunrec' return $ newp +>+ rest where fn = sp2fn f f_fp = toFilePath f mrp _ _ _ [] = return NilFL \end{code} % rm - Note: not a subsection because not to be documented. \begin{code} rm_description :: String rm_description = "Does not actually do anything, but offers advice on removing files" rm_help :: String rm_help = "This command does not do anything.\n"++ "If you want to remove a file AND delete it, just delete the file or directory,\n"++ "and darcs will notice that it has been removed.\n" ++ "If you want to remove a file WITHOUT deleting it, use the 'remove' command\n" rm :: DarcsCommand rm = command_stub "rm" rm_help rm_description remove \end{code} % unadd - Note: not a subsection because not to be documented. \begin{code} unadd :: DarcsCommand unadd = command_alias "unadd" remove \end{code}