{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ViewPatterns #-}
module Patience
(
diff
, Item(..), itemChar, itemValue
, longestIncreasing
) where
import Data.Data (Data)
import qualified Data.Foldable as F
import qualified Data.IntMap as IM
import Data.List
import qualified Data.Map as M
import qualified Data.Map.Strict as MS
import Data.Ord
import Data.Sequence ( (<|), (|>), (><), ViewL(..), ViewR(..) )
import qualified Data.Sequence as S
import Data.Typeable (Typeable)
adjMove :: (a -> a) -> Int -> Int -> IM.IntMap a -> IM.IntMap a
adjMove f !xi !xf m = case IM.updateLookupWithKey (\_ _ -> Nothing) xi m of
(Just v, mm) -> IM.insert xf (f v) mm
(Nothing, _) -> m
data Card a = Card {-# UNPACK #-} !Int a (Maybe (Card a))
longestIncreasing :: [(Int,a)] -> [(Int,a)]
longestIncreasing = extract . F.foldl' ins IM.empty where
ins m (x,a) =
let (lt, gt) = IM.split x m
prev = (head . fst) `fmap` IM.maxView lt
new = Card x a prev
in case IM.minViewWithKey gt of
Nothing -> IM.insert x [new] m
Just ((k,_),_) -> adjMove (new:) k x m
extract (IM.maxView -> Just (c,_)) = walk $ head c
extract _ = []
walk (Card x a c) = (x,a) : maybe [] walk c
unique :: (Ord t) => S.Seq (a,t) -> M.Map t a
unique = M.mapMaybe id . F.foldr ins M.empty where
ins (a,x) = MS.insertWith (\_ _ -> Nothing) x (Just a)
solveLCS :: (Ord t) => S.Seq (Int,t) -> S.Seq (Int,t) -> [(Int,Int)]
solveLCS ma mb =
let xs = M.elems $ M.intersectionWith (,) (unique ma) (unique mb)
in longestIncreasing $ sortBy (comparing snd) xs
data Piece a
= Match a a
| Diff (S.Seq a) (S.Seq a)
deriving (Show)
chop :: S.Seq t -> S.Seq t -> [(Int,Int)] -> [Piece t]
chop xs ys []
| S.null xs && S.null ys = []
| otherwise = [Diff xs ys]
chop xs ys (!(!nx,!ny):ns) =
let (xsr, S.viewl -> (x :< xse)) = S.splitAt nx xs
(ysr, S.viewl -> (y :< yse)) = S.splitAt ny ys
in Diff xse yse : Match x y : chop xsr ysr ns
zipLS :: [a] -> S.Seq b -> S.Seq (a, b)
#if MIN_VERSION_containers(0,3,0)
zipLS = S.zip . S.fromList
#else
zipLS xs = S.fromList . zip xs . F.toList
#endif
number :: S.Seq t -> S.Seq (Int,t)
number xs = zipLS [0..S.length xs - 1] xs
data Item t
= Old t
| New t
| Both t t
deriving (Eq, Ord, Show, Read, Typeable, Data)
instance Functor Item where
fmap f (Old x ) = Old (f x)
fmap f (New x ) = New (f x)
fmap f (Both x y) = Both (f x) (f y)
diff :: (Ord t) => [t] -> [t] -> [Item t]
diff xsl ysl = F.toList $ go (S.fromList xsl) (S.fromList ysl) where
go (S.viewl -> (x :< xs)) (S.viewl -> (y :< ys))
| x == y = Both x y <| go xs ys
go (S.viewr -> (xs :> x)) (S.viewr -> (ys :> y))
| x == y = go xs ys |> Both x y
go xs ys = case chop xs ys $ solveLCS (number xs) (number ys) of
[Diff _ _] -> fmap Old xs >< fmap New ys
ps -> recur ps
recur [] = S.empty
recur (Match x y : ps) = recur ps |> Both x y
recur (Diff xs ys : ps) = recur ps >< go xs ys
itemChar :: Item t -> Char
itemChar (Old _ ) = '-'
itemChar (New _ ) = '+'
itemChar (Both _ _) = ' '
itemValue :: Item t -> t
itemValue (Old x ) = x
itemValue (New x ) = x
itemValue (Both x _) = x