patch-0.0.8.4: Data structures for describing changes to other data structures.
Safe HaskellNone
LanguageHaskell2010

Data.Patch

Description

 
Synopsis

Documentation

class (Semigroup q, Monoid q) => Group q where Source #

A Group is a Monoid where every element has an inverse.

Minimal complete definition

negateG

Methods

negateG :: q -> q Source #

(~~) :: q -> q -> q Source #

Instances

Instances details
Group () Source #

Trivial group.

Instance details

Defined in Data.Patch

Methods

negateG :: () -> () Source #

(~~) :: () -> () -> () Source #

Group a => Group (Identity a) Source #

Identity lifts groups pointwise (at only one point)

Instance details

Defined in Data.Patch

Group (Proxy x) Source #

Trivial group, Functor style

Instance details

Defined in Data.Patch

Methods

negateG :: Proxy x -> Proxy x Source #

(~~) :: Proxy x -> Proxy x -> Proxy x Source #

(Ord k, Group q) => Group (MonoidalMap k q) Source # 
Instance details

Defined in Data.Patch

(Group a, Group b) => Group (a, b) Source #

Product group. A Pair of groups gives rise to a group

Instance details

Defined in Data.Patch

Methods

negateG :: (a, b) -> (a, b) Source #

(~~) :: (a, b) -> (a, b) -> (a, b) Source #

Group b => Group (a -> b) Source #

Functions lift groups pointwise.

Instance details

Defined in Data.Patch

Methods

negateG :: (a -> b) -> a -> b Source #

(~~) :: (a -> b) -> (a -> b) -> a -> b Source #

Group a => Group (Const a x) Source #

Const lifts groups into a functor.

Instance details

Defined in Data.Patch

Methods

negateG :: Const a x -> Const a x Source #

(~~) :: Const a x -> Const a x -> Const a x Source #

(Group (f a), Group (g a)) => Group ((f :*: g) a) Source #

Product of groups, Functor style.

Instance details

Defined in Data.Patch

Methods

negateG :: (f :*: g) a -> (f :*: g) a Source #

(~~) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

Group (f (g a)) => Group ((f :.: g) a) Source # 
Instance details

Defined in Data.Patch

Methods

negateG :: (f :.: g) a -> (f :.: g) a Source #

(~~) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

newtype AdditivePatch p Source #

The elements of an Commutative Semigroup can be considered as patches of their own type.

Constructors

AdditivePatch 

Fields

Instances

Instances details
Commutative p => Patch (AdditivePatch p) Source # 
Instance details

Defined in Data.Patch

Associated Types

type PatchTarget (AdditivePatch p) 
Instance details

Defined in Data.Patch

type PatchTarget (AdditivePatch p) Source # 
Instance details

Defined in Data.Patch

data PatchDMapWithMove (k1 :: k -> Type) (v :: k -> Type) Source #

Like PatchMapWithMove, but for DMap. Each key carries a NodeInfo which describes how it will be changed by the patch and connects move sources and destinations.

Invariants:

  • A key should not move to itself.
  • A move should always be represented with both the destination key (as a From_Move) and the source key (as a ComposeMaybe (Just destination))

Instances

Instances details
GCompare k2 => Monoid (PatchDMapWithMove k2 v) Source #

Compose patches having the same effect as applying the patches in turn: applyAlways (p <> q) == applyAlways p . applyAlways q

Instance details

Defined in Data.Patch.DMapWithMove

GCompare k2 => Semigroup (PatchDMapWithMove k2 v) Source #

Compose patches having the same effect as applying the patches in turn: applyAlways (p <> q) == applyAlways p . applyAlways q

Instance details

Defined in Data.Patch.DMapWithMove

(GEq k2, Has' Eq k2 (NodeInfo k2 v)) => Eq (PatchDMapWithMove k2 v) Source #

Test whether two PatchDMapWithMove k v contain the same patch operations.

Instance details

Defined in Data.Patch.DMapWithMove

GCompare k2 => DecidablyEmpty (PatchDMapWithMove k2 v) Source # 
Instance details

Defined in Data.Patch.DMapWithMove

GCompare k2 => Patch (PatchDMapWithMove k2 v) Source #

Apply the insertions, deletions, and moves to a given DMap.

Instance details

Defined in Data.Patch.DMapWithMove

Associated Types

type PatchTarget (PatchDMapWithMove k2 v) 
Instance details

Defined in Data.Patch.DMapWithMove

type PatchTarget (PatchDMapWithMove k2 v) Source # 
Instance details

Defined in Data.Patch.DMapWithMove

const2PatchDMapWithMoveWith :: forall {k1} k2 v v' (a :: k1). (v -> v' a) -> PatchMapWithMove k2 v -> PatchDMapWithMove (Const2 k2 a) v' Source #

Strengthen a PatchMapWithMove k v into a 'PatchDMapWithMove (Const2 k a); that is, turn a non-dependently-typed patch into a dependently typed one but which always has a constant key type represented by Const2. Apply the given function to each v to produce a v' a. Completemented by patchDMapWithMoveToPatchMapWithMoveWith

mapPatchDMapWithMove :: forall {k1} (k2 :: k1 -> Type) v v'. (forall (a :: k1). v a -> v' a) -> PatchDMapWithMove k2 v -> PatchDMapWithMove k2 v' Source #

Map a natural transform v -> v' over the given patch, transforming PatchDMapWithMove k v into PatchDMapWithMove k v'.

patchDMapWithMoveToPatchMapWithMoveWith :: forall {k1} k2 v v' (a :: k1). (v a -> v') -> PatchDMapWithMove (Const2 k2 a) v -> PatchMapWithMove k2 v' Source #

Weaken a PatchDMapWithMove (Const2 k a) v to a PatchMapWithMove k v'. Weaken is in scare quotes because the Const2 has already disabled any dependency in the typing and all points are already a, hence the function to map each value to v' is not higher rank.

traversePatchDMapWithMoveWithKey :: forall {k1} m k2 v v'. Applicative m => (forall (a :: k1). k2 a -> v a -> m (v' a)) -> PatchDMapWithMove k2 v -> m (PatchDMapWithMove k2 v') Source #

Map an effectful function forall a. k a -> v a -> m (v ' a) over the given patch, transforming PatchDMapWithMove k v into m (PatchDMapWithMove k v').

unPatchDMapWithMove :: forall {k1} (k2 :: k1 -> Type) (v :: k1 -> Type). PatchDMapWithMove k2 v -> DMap k2 (NodeInfo k2 v) Source #

Extract the DMap representing the patch changes from the PatchDMapWithMove.

unsafePatchDMapWithMove :: forall {k1} (k2 :: k1 -> Type) (v :: k1 -> Type). DMap k2 (NodeInfo k2 v) -> PatchDMapWithMove k2 v Source #

Wrap a DMap representing patch changes into a PatchDMapWithMove, without checking any invariants.

Warning: when using this function, you must ensure that the invariants of PatchDMapWithMove are preserved; they will not be checked.

weakenPatchDMapWithMoveWith :: forall {k1} (k2 :: k1 -> Type) v v'. (forall (a :: k1). v a -> v') -> PatchDMapWithMove k2 v -> PatchMapWithMove (Some k2) v' Source #

Weaken a PatchDMapWithMove to a PatchMapWithMove by weakening the keys from k a to Some k and applying a given weakening function v a -> v' to values.

data PatchMapWithMove k v Source #

Patch a Map with additions, deletions, and moves. Invariant: If key k1 is coming from From_Move k2, then key k2 should be going to Just k1, and vice versa. There should never be any unpaired From/To keys.

Instances

Instances details
FoldableWithIndex k (PatchMapWithMove k) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Methods

ifoldMap :: Monoid m => (k -> a -> m) -> PatchMapWithMove k a -> m #

ifoldMap' :: Monoid m => (k -> a -> m) -> PatchMapWithMove k a -> m #

ifoldr :: (k -> a -> b -> b) -> b -> PatchMapWithMove k a -> b #

ifoldl :: (k -> b -> a -> b) -> b -> PatchMapWithMove k a -> b #

ifoldr' :: (k -> a -> b -> b) -> b -> PatchMapWithMove k a -> b #

ifoldl' :: (k -> b -> a -> b) -> b -> PatchMapWithMove k a -> b #

FunctorWithIndex k (PatchMapWithMove k) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Methods

imap :: (k -> a -> b) -> PatchMapWithMove k a -> PatchMapWithMove k b #

TraversableWithIndex k (PatchMapWithMove k) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Methods

itraverse :: Applicative f => (k -> a -> f b) -> PatchMapWithMove k a -> f (PatchMapWithMove k b) #

Functor (PatchMapWithMove k) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Methods

fmap :: (a -> b) -> PatchMapWithMove k a -> PatchMapWithMove k b #

(<$) :: a -> PatchMapWithMove k b -> PatchMapWithMove k a #

Foldable (PatchMapWithMove k) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Methods

fold :: Monoid m => PatchMapWithMove k m -> m #

foldMap :: Monoid m => (a -> m) -> PatchMapWithMove k a -> m #

foldMap' :: Monoid m => (a -> m) -> PatchMapWithMove k a -> m #

foldr :: (a -> b -> b) -> b -> PatchMapWithMove k a -> b #

foldr' :: (a -> b -> b) -> b -> PatchMapWithMove k a -> b #

foldl :: (b -> a -> b) -> b -> PatchMapWithMove k a -> b #

foldl' :: (b -> a -> b) -> b -> PatchMapWithMove k a -> b #

foldr1 :: (a -> a -> a) -> PatchMapWithMove k a -> a #

foldl1 :: (a -> a -> a) -> PatchMapWithMove k a -> a #

toList :: PatchMapWithMove k a -> [a] #

null :: PatchMapWithMove k a -> Bool #

length :: PatchMapWithMove k a -> Int #

elem :: Eq a => a -> PatchMapWithMove k a -> Bool #

maximum :: Ord a => PatchMapWithMove k a -> a #

minimum :: Ord a => PatchMapWithMove k a -> a #

sum :: Num a => PatchMapWithMove k a -> a #

product :: Num a => PatchMapWithMove k a -> a #

Traversable (PatchMapWithMove k) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Methods

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

sequenceA :: Applicative f => PatchMapWithMove k (f a) -> f (PatchMapWithMove k a) #

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

sequence :: Monad m => PatchMapWithMove k (m a) -> m (PatchMapWithMove k a) #

Ord k => Monoid (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Ord k => Semigroup (PatchMapWithMove k v) Source #

Compose patches having the same effect as applying the patches in turn: applyAlways (p <> q) == applyAlways p . applyAlways q

Instance details

Defined in Data.Patch.MapWithMove

(Ord k, Read k, Read v) => Read (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

(Show k, Show v) => Show (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

(Eq k, Eq v) => Eq (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

(Ord k, Ord v) => Ord (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Wrapped (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

Associated Types

type Unwrapped (PatchMapWithMove k v) 
Instance details

Defined in Data.Patch.MapWithMove

Ord k => Patch (PatchMapWithMove k v) Source #

Apply the insertions, deletions, and moves to a given Map

Instance details

Defined in Data.Patch.MapWithMove

Associated Types

type PatchTarget (PatchMapWithMove k v) 
Instance details

Defined in Data.Patch.MapWithMove

PatchMapWithMove k1 v1 ~ t => Rewrapped (PatchMapWithMove k2 v2) t Source # 
Instance details

Defined in Data.Patch.MapWithMove

type Unwrapped (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

type PatchTarget (PatchMapWithMove k v) Source # 
Instance details

Defined in Data.Patch.MapWithMove

patchMapWithMoveNewElements :: PatchMapWithMove k v -> [v] Source #

Returns all the new elements that will be added to the Map.

patchMapWithMoveNewElementsMap :: PatchMapWithMove k v -> Map k v Source #

Return a Map k v with all the inserts/updates from the given PatchMapWithMove k v.

unsafePatchMapWithMove :: Map k (NodeInfo k v) -> PatchMapWithMove k v Source #

Wrap a Map k (NodeInfo k v) representing patch changes into a PatchMapWithMove k v, without checking any invariants.

Warning: when using this function, you must ensure that the invariants of PatchMapWithMove are preserved; they will not be checked.

newtype PatchIntMap a Source #

Patch for IntMap which represents insertion or deletion of keys in the mapping. Internally represented by 'IntMap (Maybe a)', where Just means insert/update and Nothing means delete.

Constructors

PatchIntMap 

Fields

Instances

Instances details
Functor PatchIntMap Source # 
Instance details

Defined in Data.Patch.IntMap

Methods

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

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

Foldable PatchIntMap Source # 
Instance details

Defined in Data.Patch.IntMap

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> PatchIntMap a -> m #

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

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

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

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

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

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

toList :: PatchIntMap a -> [a] #

null :: PatchIntMap a -> Bool #

length :: PatchIntMap a -> Int #

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

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

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

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

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

Traversable PatchIntMap Source # 
Instance details

Defined in Data.Patch.IntMap

Methods

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

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

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

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

FoldableWithIndex Int PatchIntMap Source # 
Instance details

Defined in Data.Patch.IntMap

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> PatchIntMap a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> PatchIntMap a -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> PatchIntMap a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> PatchIntMap a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> PatchIntMap a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> PatchIntMap a -> b #

FunctorWithIndex Int PatchIntMap Source # 
Instance details

Defined in Data.Patch.IntMap

Methods

imap :: (Int -> a -> b) -> PatchIntMap a -> PatchIntMap b #

TraversableWithIndex Int PatchIntMap Source # 
Instance details

Defined in Data.Patch.IntMap

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b) #

Monoid (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Semigroup (PatchIntMap v) Source #

a <> b will apply the changes of b and then apply the changes of a. If the same key is modified by both patches, the one on the left will take precedence.

Instance details

Defined in Data.Patch.IntMap

Read a => Read (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

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

Defined in Data.Patch.IntMap

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

Defined in Data.Patch.IntMap

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

Defined in Data.Patch.IntMap

Wrapped (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Associated Types

type Unwrapped (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

DecidablyEmpty (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Patch (PatchIntMap a) Source #

Apply the insertions or deletions to a given IntMap.

Instance details

Defined in Data.Patch.IntMap

Associated Types

type PatchTarget (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

PatchIntMap a1 ~ t => Rewrapped (PatchIntMap a2) t Source # 
Instance details

Defined in Data.Patch.IntMap

type Unwrapped (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

type PatchTarget (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

mapIntMapPatchWithKey :: (Int -> a -> b) -> PatchIntMap a -> PatchIntMap b Source #

Map a function Int -> a -> b over all as in the given PatchIntMap a (that is, all inserts/updates), producing a PatchIntMap b.

traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b) Source #

Map an effectful function Int -> a -> f b over all as in the given PatchIntMap a (that is, all inserts/updates), producing a f (PatchIntMap b).

patchIntMapNewElements :: PatchIntMap a -> [a] Source #

Extract all as inserted/updated by the given PatchIntMap a.

patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a Source #

Convert the given PatchIntMap a into an IntMap a with all the inserts/updates in the given patch.

newtype PatchDMap (k1 :: k -> Type) (v :: k -> Type) Source #

A set of changes to a DMap. Any element may be inserted/updated or deleted. Insertions are represented as ComposeMaybe (Just value), while deletions are represented as ComposeMaybe Nothing.

Constructors

PatchDMap 

Fields

Instances

Instances details
GCompare k2 => Monoid (PatchDMap k2 v) Source # 
Instance details

Defined in Data.Patch.DMap

Methods

mempty :: PatchDMap k2 v #

mappend :: PatchDMap k2 v -> PatchDMap k2 v -> PatchDMap k2 v #

mconcat :: [PatchDMap k2 v] -> PatchDMap k2 v #

GCompare k2 => Semigroup (PatchDMap k2 v) Source # 
Instance details

Defined in Data.Patch.DMap

Methods

(<>) :: PatchDMap k2 v -> PatchDMap k2 v -> PatchDMap k2 v #

sconcat :: NonEmpty (PatchDMap k2 v) -> PatchDMap k2 v #

stimes :: Integral b => b -> PatchDMap k2 v -> PatchDMap k2 v #

GCompare k2 => DecidablyEmpty (PatchDMap k2 v) Source # 
Instance details

Defined in Data.Patch.DMap

Methods

isEmpty :: PatchDMap k2 v -> Bool Source #

GCompare k2 => Patch (PatchDMap k2 v) Source #

Apply the insertions or deletions to a given DMap.

Instance details

Defined in Data.Patch.DMap

Associated Types

type PatchTarget (PatchDMap k2 v) 
Instance details

Defined in Data.Patch.DMap

type PatchTarget (PatchDMap k2 v) = DMap k2 v

Methods

apply :: PatchDMap k2 v -> PatchTarget (PatchDMap k2 v) -> Maybe (PatchTarget (PatchDMap k2 v)) Source #

type PatchTarget (PatchDMap k2 v) Source # 
Instance details

Defined in Data.Patch.DMap

type PatchTarget (PatchDMap k2 v) = DMap k2 v

mapPatchDMap :: forall {k1} v v' (k2 :: k1 -> Type). (forall (a :: k1). v a -> v' a) -> PatchDMap k2 v -> PatchDMap k2 v' Source #

Map a function v a -> v' a over any inserts/updates in the given PatchDMap k v to produce a PatchDMap k v'.

traversePatchDMap :: forall {k1} f v v' (k2 :: k1 -> Type). Applicative f => (forall (a :: k1). v a -> f (v' a)) -> PatchDMap k2 v -> f (PatchDMap k2 v') Source #

Map an effectful function v a -> f (v' a) over any inserts/updates in the given PatchDMap k v to produce a PatchDMap k v'.

traversePatchDMapWithKey :: forall {k1} m k2 v v'. Applicative m => (forall (a :: k1). k2 a -> v a -> m (v' a)) -> PatchDMap k2 v -> m (PatchDMap k2 v') Source #

Map an effectful function k a -> v a -> f (v' a) over any inserts/updates in the given PatchDMap k v to produce a PatchDMap k v'.

weakenPatchDMapWith :: forall {k1} v v' (k2 :: k1 -> Type). (forall (a :: k1). v a -> v') -> PatchDMap k2 v -> PatchMap (Some k2) v' Source #

Weaken a PatchDMap k v to a PatchMap (Some k) v' using a function v a -> v' to weaken each value contained in the patch.

patchDMapToPatchMapWith :: forall {k1} v (a :: k1) v' k2. (v a -> v') -> PatchDMap (Const2 k2 a) v -> PatchMap k2 v' Source #

Convert a weak PatchDMap (Const2 k a) v where the a is known by way of the Const2 into a PatchMap k v' using a rank 1 function v a -> v'.

const2PatchDMapWith :: forall {k1} k2 v v' (a :: k1). (v -> v' a) -> PatchMap k2 v -> PatchDMap (Const2 k2 a) v' Source #

Convert a PatchMap k v into a PatchDMap (Const2 k a) v' using a function v -> v' a.

const2IntPatchDMapWith :: forall {k} v f (a :: k). (v -> f a) -> PatchIntMap v -> PatchDMap (Const2 Key a) f Source #

Convert a PatchIntMap v into a PatchDMap (Const2 Int a) v' using a function v -> v' a.