patience-0.3: Patience diff and longest increasing subsequence

Safe HaskellSafe
LanguageHaskell2010

Patience.Map

Contents

Description

This module provides a lossless way to do diffing between two Maps, and ways to manipulate the diffs.

Synopsis

Types

data Delta a Source #

The result of a diff of an entry within two Maps.

In two Maps m1 and m2, when performing a diff, this type encodes the following situations:

Same key, different values: Stores the two values in the Delta constructor.

Same key, same values: Stores the value in the Same constructor.

Key exists in m1 but not m2: Stores the value in the Old constructor.

Key exists in m2 but not m1: Stores the value in the New constructor.

This behaviour ensures that we don't lose any information, meaning we can reconstruct either of the original Map k a from a Map k (Delta a). (Note that this slightly differs from diff, which does not care about the possibility of reconstruction).

Constructors

Delta !a !a 
Same !a 
Old !a 
New !a 
Instances
Functor Delta Source # 
Instance details

Defined in Patience.Map

Methods

fmap :: (a -> b) -> Delta a -> Delta b #

(<$) :: a -> Delta b -> Delta a #

Foldable Delta Source # 
Instance details

Defined in Patience.Map

Methods

fold :: Monoid m => Delta m -> m #

foldMap :: Monoid m => (a -> m) -> Delta a -> m #

foldr :: (a -> b -> b) -> b -> Delta a -> b #

foldr' :: (a -> b -> b) -> b -> Delta a -> b #

foldl :: (b -> a -> b) -> b -> Delta a -> b #

foldl' :: (b -> a -> b) -> b -> Delta a -> b #

foldr1 :: (a -> a -> a) -> Delta a -> a #

foldl1 :: (a -> a -> a) -> Delta a -> a #

toList :: Delta a -> [a] #

null :: Delta a -> Bool #

length :: Delta a -> Int #

elem :: Eq a => a -> Delta a -> Bool #

maximum :: Ord a => Delta a -> a #

minimum :: Ord a => Delta a -> a #

sum :: Num a => Delta a -> a #

product :: Num a => Delta a -> a #

Traversable Delta Source # 
Instance details

Defined in Patience.Map

Methods

traverse :: Applicative f => (a -> f b) -> Delta a -> f (Delta b) #

sequenceA :: Applicative f => Delta (f a) -> f (Delta a) #

mapM :: Monad m => (a -> m b) -> Delta a -> m (Delta b) #

sequence :: Monad m => Delta (m a) -> m (Delta a) #

Eq a => Eq (Delta a) Source # 
Instance details

Defined in Patience.Map

Methods

(==) :: Delta a -> Delta a -> Bool #

(/=) :: Delta a -> Delta a -> Bool #

Ord a => Ord (Delta a) Source # 
Instance details

Defined in Patience.Map

Methods

compare :: Delta a -> Delta a -> Ordering #

(<) :: Delta a -> Delta a -> Bool #

(<=) :: Delta a -> Delta a -> Bool #

(>) :: Delta a -> Delta a -> Bool #

(>=) :: Delta a -> Delta a -> Bool #

max :: Delta a -> Delta a -> Delta a #

min :: Delta a -> Delta a -> Delta a #

Show a => Show (Delta a) Source # 
Instance details

Defined in Patience.Map

Methods

showsPrec :: Int -> Delta a -> ShowS #

show :: Delta a -> String #

showList :: [Delta a] -> ShowS #

Generic (Delta a) Source # 
Instance details

Defined in Patience.Map

Associated Types

type Rep (Delta a) :: Type -> Type #

Methods

from :: Delta a -> Rep (Delta a) x #

to :: Rep (Delta a) x -> Delta a #

Generic1 Delta Source # 
Instance details

Defined in Patience.Map

Associated Types

type Rep1 Delta :: k -> Type #

Methods

from1 :: Delta a -> Rep1 Delta a #

to1 :: Rep1 Delta a -> Delta a #

type Rep (Delta a) Source # 
Instance details

Defined in Patience.Map

type Rep1 Delta Source # 
Instance details

Defined in Patience.Map

Diffing

diff Source #

Arguments

:: (Eq a, Ord k) 
=> Map k a

first, old Map

-> Map k a

second, new Map

-> Map k (Delta a)

Map encoding the diff

Takes two Maps and returns a Map from the same key type to Delta a, where Delta a encodes differences between entries.

Case analysis on Delta

getSame :: Eq a => Delta a -> Maybe a Source #

Potentially get the Same value out of a Delta.

getOld :: Delta a -> Maybe a Source #

Potentially get the Old value out of a Delta.

getNew :: Delta a -> Maybe a Source #

Potentially get the New value out of a Delta.

getDelta :: Delta a -> Maybe (a, a) Source #

Potentially get the Changed value out of a Delta.

getOriginals :: Delta a -> (Maybe a, Maybe a) Source #

Get the original values out of the Delta.

isSame :: Eq a => Delta a -> Bool Source #

Is the Delta an encoding of same values?

isOld :: Delta a -> Bool Source #

Is the Delta an encoding of old values?

isNew :: Delta a -> Bool Source #

Is the Delta an encoding of new values?

isDelta :: Delta a -> Bool Source #

Is the Delta an encoding of changed values?

Construction of special maps from a diff

toSame :: Eq a => Map k (Delta a) -> Map k a Source #

Retrieve the Same values out of the diff map.

toOld :: Map k (Delta a) -> Map k a Source #

Retrieve only the Old values out of the diff map.

toNew :: Map k (Delta a) -> Map k a Source #

Retrieve only the New values out of the diff map.

toDelta :: Map k (Delta a) -> Map k (a, a) Source #

Retrieve only the DeltaUnit values out of the diff map.

toOriginals :: Map k (Delta a) -> (Map k a, Map k a) Source #

Reconstruct both original Maps.

Mapping

mapSame :: Eq a => (a -> b) -> Map k (Delta a) -> Map k b Source #

Map over all Same values, returning a map of just the transformed values. This can be more efficient than calling toSame and then Data.Map's map.

mapOld :: (a -> b) -> Map k (Delta a) -> Map k b Source #

Map over all Old values, returning a map of just the transformed values. This can be more efficient than calling toOld and then Data.Map's map.

mapNew :: (a -> b) -> Map k (Delta a) -> Map k b Source #

Map over all New values, returning a map of just the transformed values. This can be more efficient than calling toNew and then Data.Map's map.

mapSame' :: Eq a => (a -> a) -> Map k (Delta a) -> Map k (Delta a) Source #

Map over all the Same values, preserving the remaining values in the map.

mapOld' :: (a -> a) -> Map k (Delta a) -> Map k (Delta a) Source #

Map over all the Old values, preserving the remaining values in the map.

mapNew' :: (a -> a) -> Map k (Delta a) -> Map k (Delta a) Source #

Map over all the New values, preserving the remaining values in the map.