module Darcs.Repository.Merge
( tentativelyMergePatches
, considerMergeToWorking
) where
import Darcs.Prelude
import Control.Monad ( when, unless )
import System.Exit ( exitSuccess )
import System.IO.Error
( catchIOError
, ioeGetErrorType
, isIllegalOperationErrorType
)
import Darcs.Util.Tree( Tree )
import Darcs.Util.External ( backupByCopying )
import Darcs.Patch
( RepoPatch, IsRepoType, PrimOf, merge
, effect
, listConflictedFiles )
import Darcs.Patch.Apply ( ApplyState )
import Darcs.Patch.Ident ( merge2FL )
import Darcs.Patch.Named ( patchcontents, anonymous )
import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, n2pia, hopefully )
import Darcs.Patch.Progress( progressFL )
import Darcs.Patch.Set ( PatchSet, Origin, patchSet2RL )
import Darcs.Patch.Witnesses.Ordered
( FL(..), RL(..), Fork(..), (:\/:)(..), (:/\:)(..), (+>+), (+<<+)
, mapFL_FL, concatFL, reverseFL )
import Darcs.Patch.Witnesses.Sealed ( Sealed(Sealed), seal )
import Darcs.Repository.Flags
( UseIndex
, ScanKnown
, AllowConflicts (..)
, Reorder (..)
, UpdatePending (..)
, ExternalMerge (..)
, Verbosity (..)
, Compression (..)
, WantGuiPause (..)
, DiffAlgorithm (..)
, LookForMoves(..)
, LookForReplaces(..)
)
import Darcs.Repository.Hashed
( tentativelyAddPatches_
, tentativelyRemovePatches_
, UpdatePristine(..)
)
import Darcs.Repository.Pristine
( applyToTentativePristine
, ApplyDir(..)
)
import Darcs.Repository.InternalTypes ( Repository, repoLocation )
import Darcs.Repository.Pending ( setTentativePending )
import Darcs.Repository.Resolution
( externalResolution
, standardResolution
, StandardResolution(..)
, announceConflicts
)
import Darcs.Repository.State ( unrecordedChanges, readUnrecorded )
import Darcs.Util.Prompt ( promptYorn )
import Darcs.Util.Path ( anchorPath, displayPath )
import Darcs.Util.Progress( debugMessage )
import Darcs.Util.Printer.Color ( ePutDocLn )
import Darcs.Util.Printer ( redText, vcat )
data MakeChanges = MakeChanges | DontMakeChanges deriving ( Eq )
tentativelyMergePatches_ :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
=> MakeChanges
-> Repository rt p wR wU wR -> String
-> AllowConflicts
-> ExternalMerge -> WantGuiPause
-> Compression -> Verbosity -> Reorder
-> ( UseIndex, ScanKnown, DiffAlgorithm )
-> Fork (PatchSet rt p)
(FL (PatchInfoAnd rt p))
(FL (PatchInfoAnd rt p)) Origin wR wY
-> IO (Sealed (FL (PrimOf p) wU))
tentativelyMergePatches_ mc _repo cmd allowConflicts externalMerge wantGuiPause
compression verbosity reorder diffingOpts@(useidx, _, dflag) (Fork context us them) = do
(them' :/\: us')
<- return $ merge2FL (progressFL "Merging us" us)
(progressFL "Merging them" them)
pw <- unrecordedChanges diffingOpts NoLookForMoves NoLookForReplaces _repo Nothing
anonpw <- n2pia `fmap` anonymous pw
pw' :/\: them'' <- return $ merge (them' :\/: anonpw :>: NilFL)
let them''content = concatFL $ progressFL "Examining patches for conflicts" $
mapFL_FL (patchcontents . hopefully) them''
let conflicts =
standardResolution
(patchSet2RL context +<<+ us :<: anonpw)
(reverseFL them'')
let standard_resolution = mangled conflicts
debugMessage "Checking for conflicts..."
when (allowConflicts == YesAllowConflictsAndMark) $
mapM_ backupByCopying $
map (anchorPath (repoLocation _repo)) $
conflictedPaths conflicts
debugMessage "Announcing conflicts..."
have_conflicts <-
announceConflicts cmd allowConflicts externalMerge conflicts
debugMessage "Checking for unrecorded conflicts..."
let pw'content = concatFL $ progressFL "Examining patches for conflicts" $
mapFL_FL (patchcontents . hopefully) pw'
case listConflictedFiles pw'content of
[] -> return ()
fs -> do
ePutDocLn $ vcat $ map redText $
"You have conflicting unrecorded changes to:" : map displayPath fs
confirmed <- promptYorn "Proceed?" `catchIOError` (\e ->
if isIllegalOperationErrorType (ioeGetErrorType e)
then return True
else ioError e)
unless confirmed $ do
putStrLn "Cancelled."
exitSuccess
debugMessage "Reading working tree..."
working <- readUnrecorded _repo useidx Nothing
debugMessage "Working out conflict markup..."
Sealed resolution <-
case (externalMerge , have_conflicts) of
(NoExternalMerge, _) -> return $ if allowConflicts == YesAllowConflicts
then seal NilFL
else standard_resolution
(_, False) -> return $ standard_resolution
(YesExternalMerge c, True) -> externalResolution dflag working c wantGuiPause
(effect us +>+ pw) (effect them) them''content
debugMessage "Adding patches to the inventory and writing new pending..."
when (mc == MakeChanges) $ do
applyToTentativePristine _repo ApplyNormal verbosity them'
_repo <- case reorder of
NoReorder -> do
tentativelyAddPatches_ DontUpdatePristine _repo
compression verbosity NoUpdatePending them'
Reorder -> do
r1 <- tentativelyRemovePatches_ DontUpdatePristineNorRevert _repo
compression NoUpdatePending us
r2 <- tentativelyAddPatches_ DontUpdatePristine r1
compression verbosity NoUpdatePending them
tentativelyAddPatches_ DontUpdatePristine r2
compression verbosity NoUpdatePending us'
setTentativePending _repo (effect pw' +>+ resolution)
return $ seal (effect them''content +>+ resolution)
tentativelyMergePatches :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
=> Repository rt p wR wU wR -> String
-> AllowConflicts
-> ExternalMerge -> WantGuiPause
-> Compression -> Verbosity -> Reorder
-> ( UseIndex, ScanKnown, DiffAlgorithm )
-> Fork (PatchSet rt p)
(FL (PatchInfoAnd rt p))
(FL (PatchInfoAnd rt p)) Origin wR wY
-> IO (Sealed (FL (PrimOf p) wU))
tentativelyMergePatches = tentativelyMergePatches_ MakeChanges
considerMergeToWorking :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
=> Repository rt p wR wU wR -> String
-> AllowConflicts
-> ExternalMerge -> WantGuiPause
-> Compression -> Verbosity -> Reorder
-> ( UseIndex, ScanKnown, DiffAlgorithm )
-> Fork (PatchSet rt p)
(FL (PatchInfoAnd rt p))
(FL (PatchInfoAnd rt p)) Origin wR wY
-> IO (Sealed (FL (PrimOf p) wU))
considerMergeToWorking = tentativelyMergePatches_ DontMakeChanges