-- Copyright (C) 2002-2005 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. {-# LANGUAGE OverloadedStrings #-} module Darcs.UI.Commands.Unrecord ( unrecord , unpull , obliterate , getLastPatches , matchingHead ) where import Prelude () import Darcs.Prelude import Prelude hiding ( (^) ) import Control.Exception ( catch, IOException ) import Control.Monad ( when ) import Data.Maybe( isJust ) import Darcs.Util.Tree( Tree ) import System.Exit ( exitSuccess ) import Darcs.Patch ( IsRepoType, RepoPatch, invert, commute, effect ) import Darcs.Patch.Apply( ApplyState ) import Darcs.Patch.Bundle ( makeBundleN, contextPatches, minContext ) import Darcs.Patch.Depends ( findCommonWithThem, patchSetUnion ) import Darcs.Patch.Match ( firstMatch, matchFirstPatchset, matchAPatch, MatchFlag ) import Darcs.Patch.PatchInfoAnd ( hopefully, patchDesc ) import Darcs.Patch.Set ( PatchSet(..), Tagged(..), appendPSFL, Origin, SealedPatchSet ) import Darcs.Patch.Witnesses.Sealed ( Sealed(..), seal ) import Darcs.Patch.Witnesses.Ordered ( RL(..), (:>)(..), (+<+), mapFL_FL, nullFL, reverseRL, mapRL, FL(..) ) import Darcs.Util.Path( useAbsoluteOrStd, AbsolutePath, toFilePath, doesPathExist ) import Darcs.Util.SignalHandler ( catchInterrupt ) import Darcs.Repository ( PatchInfoAnd, withRepoLock, RepoJob(..), Repository, tentativelyRemovePatches, finalizeRepositoryChanges, tentativelyAddToPending, applyToWorking, readRepo, invalidateIndex, unrecordedChanges, identifyRepositoryFor ) import Darcs.Repository.Flags( UseIndex(..), ScanKnown(..), UpdateWorking(..), DryRun(NoDryRun) ) import Darcs.Util.Lock( writeDocBinFile ) import Darcs.Repository.Prefs ( getDefaultRepoPath ) import Darcs.UI.Commands ( DarcsCommand(..), withStdOpts, nodefaults, commandAlias , putVerbose , setEnvDarcsPatches, amInHashedRepository , putInfo ) import Darcs.UI.Commands.Util ( getUniqueDPatchName, printDryRunMessageAndExit ) import Darcs.UI.Completion ( noArgs ) import Darcs.UI.Flags ( DarcsFlag, changesReverse, compress, verbosity, getOutput , useCache, dryRun, umask, minimize , diffAlgorithm, xmlOutput, isInteractive, selectDeps ) import Darcs.UI.Options ( (^), odesc, ocheck, onormalise, defaultFlags, parseFlags, (?) ) import Darcs.UI.Options.All ( notInRemoteFlagName ) import qualified Darcs.UI.Options.All as O import Darcs.UI.SelectChanges ( WhichChanges(..), selectionContext, runSelection ) import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions (..) ) import Darcs.Util.English ( presentParticiple ) import Darcs.Util.Printer ( text, putDoc, vcat, (<+>), ($$) ) import Darcs.Util.Progress ( debugMessage ) unrecordDescription :: String unrecordDescription = "Remove recorded patches without changing the working tree." unrecordHelp :: String unrecordHelp = unlines [ "Unrecord does the opposite of record: it deletes patches from" , "the repository, without changing the working tree." , "Deleting patches from the repository makes active changes again" , "which you may record or revert later." , "Beware that you should not use this command if there is a" , "possibility that another user may have already pulled the patch." ] unrecord :: DarcsCommand [DarcsFlag] unrecord = DarcsCommand { commandProgramName = "darcs" , commandName = "unrecord" , commandHelp = unrecordHelp , commandDescription = unrecordDescription , commandExtraArgs = 0 , commandExtraArgHelp = [] , commandCommand = unrecordCmd , commandPrereq = amInHashedRepository , commandCompleteArgs = noArgs , commandArgdefaults = nodefaults , commandAdvancedOptions = odesc unrecordAdvancedOpts , commandBasicOptions = odesc unrecordBasicOpts , commandDefaults = defaultFlags unrecordOpts , commandCheckOptions = ocheck unrecordOpts , commandParseOptions = onormalise unrecordOpts } where unrecordBasicOpts = O.notInRemote ^ O.matchSeveralOrLast ^ O.selectDeps ^ O.interactive -- True ^ O.repoDir unrecordAdvancedOpts = O.compress ^ O.umask ^ O.changesReverse unrecordOpts = unrecordBasicOpts `withStdOpts` unrecordAdvancedOpts unrecordCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO () unrecordCmd _ opts _ = withRepoLock NoDryRun (useCache ? opts) YesUpdateWorking (umask ? opts) $ RepoJob $ \repository -> do (_ :> removal_candidates) <- preselectPatches opts repository let direction = if changesReverse ? opts then Last else LastReversed context = selectionContext direction "unrecord" (patchSelOpts opts) Nothing Nothing (_ :> to_unrecord) <- runSelection removal_candidates context when (nullFL to_unrecord) $ do putInfo opts "No patches selected!" exitSuccess putVerbose opts $ text "About to write out (potentially) modified patches..." setEnvDarcsPatches to_unrecord invalidateIndex repository _ <- tentativelyRemovePatches repository (compress ? opts) YesUpdateWorking to_unrecord finalizeRepositoryChanges repository YesUpdateWorking (compress ? opts) putInfo opts "Finished unrecording." getLastPatches :: (IsRepoType rt, RepoPatch p) => [MatchFlag] -> PatchSet rt p Origin wR -> (PatchSet rt p :> FL (PatchInfoAnd rt p)) Origin wR getLastPatches matchFlags ps = case matchFirstPatchset matchFlags ps of Sealed p1s -> findCommonWithThem ps p1s unpullDescription :: String unpullDescription = "Opposite of pull; unsafe if patch is not in remote repository." unpullHelp :: String unpullHelp = unlines [ "Unpull completely removes recorded patches from your local repository." , "The changes will be undone in your working tree and the patches" , "will not be shown in your changes list anymore. Beware that if the" , "patches are not still present in another repository you will lose" , "precious code by unpulling!" , "" , "One way to save unpulled patches is to use the -O flag. A patch" , "bundle will be created locally, that you will be able to apply" , "later to your repository with `darcs apply`." ] unpull :: DarcsCommand [DarcsFlag] unpull = (commandAlias "unpull" Nothing obliterate) { commandHelp = unpullHelp , commandDescription = unpullDescription , commandCommand = unpullCmd } unpullCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO () unpullCmd = genericObliterateCmd "unpull" obliterateDescription :: String obliterateDescription = "Delete selected patches from the repository." obliterateHelp :: String obliterateHelp = unlines [ "Obliterate completely removes recorded patches from your local" , "repository. The changes will be undone in your working tree and the" , "patches will not be shown in your changes list anymore. Beware that" , "you can lose precious code by obliterating!" , "" , "One way to save obliterated patches is to use the -O flag. A patch" , "bundle will be created locally, that you will be able to apply" , "later to your repository with `darcs apply`." ] obliterate :: DarcsCommand [DarcsFlag] obliterate = DarcsCommand { commandProgramName = "darcs" , commandName = "obliterate" , commandHelp = obliterateHelp , commandDescription = obliterateDescription , commandExtraArgs = 0 , commandExtraArgHelp = [] , commandCommand = obliterateCmd , commandPrereq = amInHashedRepository , commandCompleteArgs = noArgs , commandArgdefaults = nodefaults , commandAdvancedOptions = odesc obliterateAdvancedOpts , commandBasicOptions = odesc obliterateBasicOpts , commandDefaults = defaultFlags obliterateOpts , commandCheckOptions = ocheck obliterateOpts , commandParseOptions = onormalise obliterateOpts } where obliterateBasicOpts = O.notInRemote ^ O.matchSeveralOrLast ^ O.selectDeps ^ O.interactive ^ O.repoDir ^ O.summary ^ O.output ^ O.minimize ^ O.diffAlgorithm ^ O.dryRunXml obliterateAdvancedOpts = O.compress ^ O.useIndex ^ O.umask ^ O.changesReverse obliterateOpts = obliterateBasicOpts `withStdOpts` obliterateAdvancedOpts obliterateCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO () obliterateCmd = genericObliterateCmd "obliterate" -- | genericObliterateCmd is the function that executes the "obliterate" and -- "unpull" commands. The first argument is the name under which the command is -- invoked (@unpull@ or @obliterate@). genericObliterateCmd :: String -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO () genericObliterateCmd cmdname _ opts _ = let cacheOpt = useCache ? opts verbOpt = verbosity ? opts in withRepoLock (dryRun ? opts) cacheOpt YesUpdateWorking (umask ? opts) $ RepoJob $ \repository -> do -- FIXME we may need to honour --ignore-times here, although this -- command does not take that option (yet) pend <- unrecordedChanges (UseIndex, ScanKnown, diffAlgorithm ? opts) O.NoLookForMoves O.NoLookForReplaces repository Nothing (auto_kept :> removal_candidates) <- preselectPatches opts repository let direction = if changesReverse ? opts then Last else LastReversed context = selectionContext direction cmdname (patchSelOpts opts) Nothing Nothing (kept :> removed) <- runSelection removal_candidates context when (nullFL removed) $ do putInfo opts "No patches selected!" exitSuccess case commute (effect removed :> pend) of Nothing -> fail $ "Can't " ++ cmdname ++ " patch without reverting some " ++ "unrecorded change." Just (_ :> p_after_pending) -> do printDryRunMessageAndExit "obliterate" verbOpt (O.summary ? opts) (dryRun ? opts) (xmlOutput ? opts) (isInteractive True opts) removed setEnvDarcsPatches removed when (isJust $ getOutput opts "") $ savetoBundle opts (auto_kept `appendPSFL` kept) removed invalidateIndex repository _ <- tentativelyRemovePatches repository (compress ? opts) YesUpdateWorking removed tentativelyAddToPending repository YesUpdateWorking $ invert $ effect removed finalizeRepositoryChanges repository YesUpdateWorking (compress ? opts) debugMessage "Applying patches to working directory..." _ <- applyToWorking repository verbOpt (invert p_after_pending) `catch` \(e :: IOException) -> fail $ "Couldn't undo patch in working dir.\n" ++ show e putInfo opts $ "Finished" <+> text (presentParticiple cmdname) <> "." -- | Get the union of the set of patches in each specified location remotePatches :: (IsRepoType rt, RepoPatch p) => [DarcsFlag] -> Repository rt p wX wU wT -> [O.NotInRemote] -> IO (SealedPatchSet rt p Origin) remotePatches opts repository nirs = do nirsPaths <- mapM getNotInRemotePath nirs putInfo opts $ "Determining patches not in" <+> pluralExtra nirsPaths $$ itemize nirsPaths patchSetUnion `fmap` mapM readNir nirsPaths where pluralExtra names = if length names > 1 then "any of" else mempty itemize = vcat . map (text . (" - " ++)) readNir n = do r <- identifyRepositoryFor repository (useCache ? opts) n rps <- readRepo r return $ seal rps getNotInRemotePath :: O.NotInRemote -> IO String getNotInRemotePath (O.NotInRemotePath p) = return p getNotInRemotePath O.NotInDefaultRepo = do defaultRepo <- getDefaultRepoPath let err = fail $ "No default push/pull repo configured, please pass a " ++ "repo name to --" ++ notInRemoteFlagName maybe err return defaultRepo -- | matchingHead returns the repository up to some tag. The tag t is the last -- tag such that there is a patch after t that is matched by the user's query. matchingHead :: forall rt p wR . (IsRepoType rt, RepoPatch p) => [MatchFlag] -> PatchSet rt p Origin wR -> (PatchSet rt p :> FL (PatchInfoAnd rt p)) Origin wR matchingHead matchFlags set = case mh set of (start :> patches) -> start :> reverseRL patches where mh :: forall wX . PatchSet rt p Origin wX -> (PatchSet rt p :> RL (PatchInfoAnd rt p)) Origin wX mh s@(PatchSet _ x) | or (mapRL (matchAPatch matchFlags) x) = contextPatches s mh (PatchSet (ts :<: Tagged t _ ps) x) = case mh (PatchSet ts (ps :<: t)) of (start :> patches) -> start :> patches +<+ x mh ps = ps :> NilRL savetoBundle :: (RepoPatch p, ApplyState p ~ Tree) => [DarcsFlag] -> PatchSet rt p Origin wZ -> FL (PatchInfoAnd rt p) wZ wT -> IO () savetoBundle opts kept removed@(x :>: _) = do let genFullBundle = makeBundleN Nothing kept (mapFL_FL hopefully removed) bundle <- if not (minimize ? opts) then genFullBundle else do putInfo opts "Minimizing context, to generate bundle with full context hit ctrl-C..." ( case minContext kept removed of Sealed (kept' :> removed') -> makeBundleN Nothing kept' (mapFL_FL hopefully removed') ) `catchInterrupt` genFullBundle filename <- getUniqueDPatchName (patchDesc x) let Just outname = getOutput opts filename exists <- useAbsoluteOrStd (doesPathExist . toFilePath) (return False) outname when exists $ fail $ "Directory or file named '" ++ (show outname) ++ "' already exists." useAbsoluteOrStd writeDocBinFile putDoc outname bundle savetoBundle _ _ NilFL = return () preselectPatches :: (IsRepoType rt, RepoPatch p) => [DarcsFlag] -> Repository rt p wR wU wT -> IO ((PatchSet rt p :> FL (PatchInfoAnd rt p)) Origin wR) preselectPatches opts repo = do allpatches <- readRepo repo let matchFlags = parseFlags O.matchSeveralOrLast opts case O.notInRemote ? opts of [] -> do return $ if firstMatch matchFlags then getLastPatches matchFlags allpatches else matchingHead matchFlags allpatches -- FIXME what about match options when we have --not-in-remote? -- It looks like they are simply ignored. nirs -> do (Sealed thems) <- remotePatches opts repo nirs return $ findCommonWithThem allpatches thems patchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions patchSelOpts flags = S.PatchSelectionOptions { S.verbosity = verbosity ? flags , S.matchFlags = parseFlags O.matchSeveralOrLast flags , S.interactive = isInteractive True flags , S.selectDeps = selectDeps ? flags , S.summary = O.summary ? flags , S.withContext = O.NoContext }