module Data.Algorithm.DiffContext
( getContextDiff
, prettyContextDiff
) where
import Data.Algorithm.Diff (Diff(..), getGroupedDiff)
import Data.List (groupBy)
import Data.Monoid (mappend)
import Text.PrettyPrint (Doc, text, empty, hcat)
type ContextDiff c = [[Diff [c]]]
getContextDiff :: Eq a => Int -> [a] -> [a] -> ContextDiff a
getContextDiff context a b =
group $ swap $ trimTail $ trimHead $ concatMap split $ getGroupedDiff a b
where
split (Both xs ys) =
case length xs of
n | n > (2 * context) -> [Both (take context xs) (take context ys), Both (drop (n context) xs) (drop (n context) ys)]
_ -> [Both xs ys]
split x = [x]
trimHead [] = []
trimHead [Both _ _] = []
trimHead [Both _ _, Both _ _] = []
trimHead (Both _ _ : x@(Both _ _) : more) = x : more
trimHead xs = trimTail xs
trimTail [x@(Both _ _), Both _ _] = [x]
trimTail (x : more) = x : trimTail more
trimTail [] = []
swap (x@(Second _) : y@(First _) : xs) = y : x : swap xs
swap (x : xs) = x : swap xs
swap [] = []
group xs =
groupBy (\ x y -> not (isBoth x && isBoth y)) xs
where
isBoth (Both _ _) = True
isBoth _ = False
prettyContextDiff ::
Doc
-> Doc
-> (c -> Doc)
-> ContextDiff c
-> Doc
prettyContextDiff _ _ _ [] = empty
prettyContextDiff old new prettyElem hunks =
hcat . map (`mappend` text "\n") $ (text "--- " `mappend` old :
text "+++ " `mappend` new :
concatMap prettyRun hunks)
where
prettyRun hunk =
text "@@" : concatMap prettyChange hunk
prettyChange (Both ts _) = map (\ l -> text " " `mappend` prettyElem l) ts
prettyChange (First ts) = map (\ l -> text "-" `mappend` prettyElem l) ts
prettyChange (Second ts) = map (\ l -> text "+" `mappend` prettyElem l) ts