module Darcs.Repository.Resolution
( standardResolution
, externalResolution
, patchsetConflictResolutions
) where
import Prelude ()
import Darcs.Prelude
import System.FilePath.Posix ( (</>) )
import System.Exit ( ExitCode( ExitSuccess ) )
import System.Directory ( setCurrentDirectory, getCurrentDirectory )
import Data.List ( zip4 )
import Control.Monad ( when )
import Darcs.Repository.Diff( treeDiff )
import Darcs.Patch ( PrimOf, PrimPatch, RepoPatch, resolveConflicts,
effectOnFilePaths,
invert, listConflictedFiles, commute, applyToTree, fromPrim )
import Darcs.Patch.Apply( ApplyState )
import Darcs.Patch.Conflict ( Conflict, CommuteNoConflicts )
import Darcs.Patch.Named.Wrapped ( activecontents )
import Darcs.Patch.Prim ( PrimPatchBase )
import Darcs.Util.Path ( toFilePath, filterFilePaths )
import Darcs.Patch.Witnesses.Ordered
( FL(..), RL(..), (:>)(..), (+>+),
mapFL_FL, concatFL, reverseRL )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..), unFreeLeft )
import Darcs.Util.CommandLine ( parseCmd )
import Darcs.Patch.PatchInfoAnd ( hopefully )
import Darcs.Util.Prompt ( askEnter )
import Darcs.Patch.Set ( PatchSet(..), Origin )
import Darcs.Repository.Prefs ( filetypeFunction )
import Darcs.Util.Exec ( exec, Redirect(..) )
import Darcs.Util.Lock ( withTempDir )
import Darcs.Util.External ( cloneTree )
import Darcs.Repository.Flags ( WantGuiPause(..), DiffAlgorithm(..) )
import qualified Darcs.Util.Tree as Tree
import Darcs.Util.Tree.Plain ( writePlainTree, readPlainTree )
standardResolution :: (PrimPatchBase p, Conflict p, CommuteNoConflicts p)
=> FL p wX wY -> Sealed (FL (PrimOf p) wY)
standardResolution = mergeList . map head . resolveConflicts
mergeList :: forall prim wX . PrimPatch prim => [Sealed (FL prim wX)] -> Sealed (FL prim wX)
mergeList = doml NilFL
where doml :: FL prim wX wY -> [Sealed (FL prim wX)] -> Sealed (FL prim wX)
doml mp (Sealed p:ps) =
case commute (invert p :> mp) of
Just (mp' :> _) -> doml (p +>+ mp') ps
Nothing -> doml mp ps
doml mp [] = Sealed mp
externalResolution :: forall p wX wY wZ wA. (RepoPatch p, ApplyState p ~ Tree.Tree)
=> DiffAlgorithm
-> Tree.Tree IO
-> String
-> WantGuiPause
-> FL (PrimOf p) wX wY
-> FL (PrimOf p) wX wZ
-> FL p wY wA
-> IO (Sealed (FL (PrimOf p) wA))
externalResolution diffa s1 c wantGuiPause p1_prim p2_prim pmerged = do
let p1 :: FL p wX wY = mapFL_FL fromPrim p1_prim
p2 :: FL p wX wZ = mapFL_FL fromPrim p2_prim
sa <- applyToTree (invert p1) s1
sm <- applyToTree pmerged s1
s2 <- applyToTree p2 sa
let nms = listConflictedFiles pmerged
nas = effectOnFilePaths (invert pmerged) nms
n1s = effectOnFilePaths p1 nas
n2s = effectOnFilePaths p2 nas
ns = zip4 nas n1s n2s nms
write_files tree fs = writePlainTree (Tree.filter (filterFilePaths fs) tree) "."
in do
former_dir <- getCurrentDirectory
withTempDir "version1" $ \absd1 -> do
let d1 = toFilePath absd1
write_files s1 n1s
setCurrentDirectory former_dir
withTempDir "ancestor" $ \absda -> do
let da = toFilePath absda
write_files sa nas
setCurrentDirectory former_dir
withTempDir "merged" $ \absdm -> do
let dm = toFilePath absdm
write_files sm nms
setCurrentDirectory former_dir
withTempDir "cleanmerged" $ \absdc -> do
let dc = toFilePath absdc
cloneTree dm "."
setCurrentDirectory former_dir
withTempDir "version2" $ \absd2 -> do
let d2 = toFilePath absd2
write_files s2 n2s
mapM_ (externallyResolveFile c wantGuiPause da d1 d2 dm) ns
sc <- readPlainTree dc
sfixed <- readPlainTree dm
ftf <- filetypeFunction
unFreeLeft `fmap` treeDiff diffa ftf sc sfixed
externallyResolveFile :: String
-> WantGuiPause
-> String
-> String
-> String
-> String
-> (FilePath, FilePath, FilePath, FilePath)
-> IO ()
externallyResolveFile c wantGuiPause da d1 d2 dm (fa, f1, f2, fm) = do
putStrLn $ "Merging file "++fm++" by hand."
ec <- run c [('1', d1</>f1), ('2', d2</>f2), ('a', da</>fa), ('o', dm</>fm), ('%', "%")]
when (ec /= ExitSuccess) $
putStrLn $ "External merge command exited with " ++ show ec
when (wantGuiPause == YesWantGuiPause) $
askEnter "Hit return to move on, ^C to abort the whole operation..."
run :: String -> [(Char,String)] -> IO ExitCode
run c replacements =
case parseCmd replacements c of
Left err -> fail $ show err
Right (c2,_) -> rr c2
where rr (command:args) = do putStrLn $ "Running command '" ++
unwords (command:args) ++ "'"
exec command args (Null,Null,Null)
rr [] = return ExitSuccess
patchsetConflictResolutions :: RepoPatch p => PatchSet rt p Origin wX -> Sealed (FL (PrimOf p) wX)
patchsetConflictResolutions (PatchSet _ NilRL) = Sealed NilFL
patchsetConflictResolutions (PatchSet _ xs)
=
standardResolution $ concatFL $
mapFL_FL (activecontents . hopefully) $ reverseRL xs