module Darcs.UI.Commands.Unrevert ( unrevert, writeUnrevert ) where
import Prelude ()
import Darcs.Prelude
import Control.Exception ( catch, IOException )
import System.Exit ( exitSuccess )
import Darcs.Util.Tree( Tree )
import Darcs.UI.Commands ( DarcsCommand(..), withStdOpts, nodefaults, amInHashedRepository )
import Darcs.UI.Completion ( noArgs )
import Darcs.UI.Flags
( diffingOpts, verbosity, useCache, umask, compress, diffAlgorithm
, isInteractive, withContext )
import Darcs.Repository.Flags
( UseIndex(..), ScanKnown (..), Reorder(..), AllowConflicts(..), ExternalMerge(..)
, WantGuiPause(..), UpdateWorking(..), DryRun(NoDryRun) )
import Darcs.UI.Flags ( DarcsFlag )
import Darcs.UI.Options ( (^), odesc, ocheck, onormalise, defaultFlags, (?) )
import qualified Darcs.UI.Options.All as O
import Darcs.Repository ( SealedPatchSet, Repository, withRepoLock, RepoJob(..),
unrevertUrl, considerMergeToWorking,
tentativelyAddToPending, finalizeRepositoryChanges,
readRepo,
readRecorded,
applyToWorking, unrecordedChanges )
import Darcs.Patch ( IsRepoType, RepoPatch, PrimOf, commute, fromPrims )
import Darcs.Patch.Apply( ApplyState )
import Darcs.Patch.Named.Wrapped ( namepatch )
import Darcs.Patch.Rebase ( dropAnyRebase )
import Darcs.Patch.Set ( Origin )
import Darcs.Patch.Witnesses.Sealed ( Sealed(Sealed) )
import Darcs.Patch.Witnesses.Ordered ( FL(..), (:>)(..), (+>+) )
import Darcs.UI.SelectChanges
( WhichChanges(First)
, runSelection
, selectionContextPrim
)
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions (..) )
import qualified Data.ByteString as B
import Darcs.Util.Lock ( writeDocBinFile, removeFileMayNotExist )
import Darcs.Patch.Depends ( mergeThem )
import Darcs.UI.External ( catchall )
import Darcs.Util.Prompt ( askUser )
import Darcs.Patch.Bundle ( scanBundle, makeBundleN )
import Darcs.Util.IsoDate ( getIsoDateTime )
import Darcs.Util.SignalHandler ( withSignalsBlocked )
import Darcs.Util.Progress ( debugMessage )
import Darcs.Util.Path ( AbsolutePath )
unrevertDescription :: String
unrevertDescription =
"Undo the last revert."
unrevertHelp :: String
unrevertHelp =
"Unrevert is a rescue command in case you accidentally reverted\n" ++
"something you wanted to keep (for example, typing `darcs rev -a`\n" ++
"instead of `darcs rec -a`).\n" ++
"\n" ++
"This command may fail if the repository has changed since the revert\n" ++
"took place. Darcs will ask for confirmation before executing an\n" ++
"interactive command that will DEFINITELY prevent unreversion.\n"
patchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
patchSelOpts flags = S.PatchSelectionOptions
{ S.verbosity = verbosity ? flags
, S.matchFlags = []
, S.interactive = isInteractive True flags
, S.selectDeps = O.PromptDeps
, S.summary = O.NoSummary
, S.withContext = withContext ? flags
}
unrevert :: DarcsCommand [DarcsFlag]
unrevert = DarcsCommand
{ commandProgramName = "darcs"
, commandName = "unrevert"
, commandHelp = unrevertHelp
, commandDescription = unrevertDescription
, commandExtraArgs = 0
, commandExtraArgHelp = []
, commandCommand = unrevertCmd
, commandPrereq = amInHashedRepository
, commandCompleteArgs = noArgs
, commandArgdefaults = nodefaults
, commandAdvancedOptions = odesc unrevertAdvancedOpts
, commandBasicOptions = odesc unrevertBasicOpts
, commandDefaults = defaultFlags unrevertOpts
, commandCheckOptions = ocheck unrevertOpts
, commandParseOptions = onormalise unrevertOpts
}
where
unrevertBasicOpts
= O.useIndex
^ O.interactive
^ O.repoDir
^ O.withContext
^ O.diffAlgorithm
unrevertAdvancedOpts = O.umask
unrevertOpts = unrevertBasicOpts `withStdOpts` unrevertAdvancedOpts
unrevertCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
unrevertCmd _ opts [] =
withRepoLock NoDryRun (useCache ? opts) YesUpdateWorking (umask ? opts) $ RepoJob $ \repository -> do
us <- readRepo repository
Sealed them <- unrevertPatchBundle repository
recorded <- readRecorded repository
unrecorded <- unrecordedChanges (diffingOpts opts )
O.NoLookForMoves O.NoLookForReplaces repository Nothing
Sealed h_them <- return $ mergeThem us them
Sealed pw <- considerMergeToWorking repository "unrevert"
YesAllowConflictsAndMark YesUpdateWorking
NoExternalMerge NoWantGuiPause
(compress ? opts) (verbosity ? opts) NoReorder
( UseIndex, ScanKnown, diffAlgorithm ? opts )
NilFL h_them
let context = selectionContextPrim First "unrevert" (patchSelOpts opts) Nothing Nothing (Just recorded)
(p :> skipped) <- runSelection pw context
tentativelyAddToPending repository YesUpdateWorking p
withSignalsBlocked $
do finalizeRepositoryChanges repository YesUpdateWorking (compress ? opts)
_ <- applyToWorking repository (verbosity ? opts) p `catch` \(e :: IOException) ->
fail ("Error applying unrevert to working directory...\n"
++ show e)
debugMessage "I'm about to writeUnrevert."
writeUnrevert repository skipped recorded (unrecorded+>+p)
debugMessage "Finished unreverting."
unrevertCmd _ _ _ = impossible
writeUnrevert :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
=> Repository rt p wR wU wT -> FL (PrimOf p) wX wY
-> Tree IO -> FL (PrimOf p) wR wX -> IO ()
writeUnrevert repository NilFL _ _ = removeFileMayNotExist $ unrevertUrl repository
writeUnrevert repository ps recorded pend =
case commute (pend :> ps) of
Nothing -> do really <- askUser "You will not be able to unrevert this operation! Proceed? "
case really of ('y':_) -> return ()
_ -> exitSuccess
writeUnrevert repository NilFL recorded pend
Just (p' :> _) -> do
rep <- dropAnyRebase <$> readRepo repository
date <- getIsoDateTime
np <- namepatch date "unrevert" "anon" [] (fromRepoPrims repository p')
bundle <- makeBundleN (Just recorded) rep (np :>: NilFL)
writeDocBinFile (unrevertUrl repository) bundle
where fromRepoPrims :: RepoPatch p => Repository rt p wR wU wT -> FL (PrimOf p) wR wY -> FL p wR wY
fromRepoPrims _ = fromPrims
unrevertPatchBundle :: RepoPatch p => Repository rt p wR wU wT -> IO (SealedPatchSet rt p Origin)
unrevertPatchBundle repository = do
pf <- B.readFile (unrevertUrl repository)
`catchall` fail "There's nothing to unrevert!"
case scanBundle pf of
Right ps -> return ps
Left err -> fail $ "Couldn't parse unrevert patch:\n" ++ err