{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Darcs.Patch.Prim.V1.Mangle () where
import Darcs.Prelude
import qualified Data.ByteString.Char8 as BC (pack, last)
import qualified Data.ByteString as B (null, ByteString)
import Data.Maybe ( isJust, listToMaybe )
import Data.List ( sort, intercalate, nub )
import Darcs.Patch.FileHunk ( FileHunk(..), IsHunk(..) )
import Darcs.Patch.Inspect ( PatchInspect(listTouchedFiles) )
import Darcs.Patch.Invert ( Invert(..) )
import Darcs.Patch.Prim.Class
( PrimConstruct(primFromHunk)
, PrimMangleUnravelled(..)
)
import Darcs.Patch.Prim.V1.Core ( Prim )
import Darcs.Patch.Witnesses.Ordered ( FL(..), (+>+), mapFL_FL_M )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..), mapSeal, unseal )
import Darcs.Util.Path ( AnchoredPath )
newtype FileState wX = FileState { content :: [Maybe B.ByteString] }
unknownFileState :: FileState wX
unknownFileState = FileState (repeat Nothing)
applyHunk :: FileHunk wX wY -> FileState wX -> FileState wY
applyHunk (FileHunk _ line old new) = FileState . go . content
where
go mls =
case splitAt (line - 1) mls of
(before, rest) ->
concat [before, map Just new, drop (length old) rest]
applyHunks :: FL FileHunk wX wY -> FileState wX -> FileState wY
applyHunks NilFL = id
applyHunks (p:>:ps) = applyHunks ps . applyHunk p
instance PrimMangleUnravelled Prim where
mangleUnravelled pss = do
hunks <- onlyHunks pss
filename <- listToMaybe (filenames pss)
return $ mapSeal ((:>: NilFL) . primFromHunk) $ mangleHunks filename hunks
where
filenames = nub . concatMap (unseal listTouchedFiles)
onlyHunks :: forall prim wX. IsHunk prim
=> [Sealed (FL prim wX)]
-> Maybe [Sealed (FL FileHunk wX)]
onlyHunks = mapM toHunk where
toHunk :: Sealed (FL prim wA) -> Maybe (Sealed (FL FileHunk wA))
toHunk (Sealed ps) = fmap Sealed $ mapFL_FL_M isHunk ps
mangleHunks :: AnchoredPath -> [Sealed (FL FileHunk wX)] -> Sealed (FileHunk wX)
mangleHunks _ [] = error "mangleHunks called with empty list of alternatives"
mangleHunks path ps = Sealed (FileHunk path l old new)
where
oldf = foldl oldFileState unknownFileState ps
newfs = map (newFileState oldf) ps
l = getHunkline (Sealed oldf : newfs)
nchs = sort (map (makeChunk l) newfs)
old = makeChunk l (Sealed oldf)
new = [top] ++ old ++ [initial] ++ intercalate [middle] nchs ++ [bottom]
top = BC.pack ("v v v v v v v" ++ eol_c)
initial = BC.pack ("=============" ++ eol_c)
middle = BC.pack ("*************" ++ eol_c)
bottom = BC.pack ("^ ^ ^ ^ ^ ^ ^" ++ eol_c)
eol_c =
if any (\line -> not (B.null line) && BC.last line == '\r') old
then "\r"
else ""
oldFileState :: FileState wX -> Sealed (FL FileHunk wX) -> FileState wX
oldFileState mls (Sealed ps) = applyHunks (ps +>+ invert ps) mls
newFileState :: FileState wX -> Sealed (FL FileHunk wX) -> Sealed FileState
newFileState mls (Sealed ps) = Sealed (applyHunks ps mls)
getHunkline :: [Sealed FileState] -> Int
getHunkline = go 1 . map (unseal content)
where
go n pps =
if any (isJust . head) pps
then n
else go (n + 1) $ map tail pps
makeChunk :: Int -> Sealed FileState -> [B.ByteString]
makeChunk n = takeWhileJust . drop (n - 1) . unseal content
where
takeWhileJust = foldr (\x acc -> maybe [] (:acc) x) []