patch-0.0.3.1: Infrastructure for writing patches which act on other types.

Safe HaskellNone
LanguageHaskell98

Data.Patch.MapWithPatchingMove

Description

Patches on Map that can insert, delete, and move values from one key to another

Synopsis

Documentation

newtype PatchMapWithPatchingMove k p 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.

Constructors

PatchMapWithPatchingMove 

Fields

Instances
(Eq k, Eq p, Eq (PatchTarget p)) => Eq (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

(Ord k, Ord p, Ord (PatchTarget p)) => Ord (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

(Ord k, Read k, Read p, Read (PatchTarget p)) => Read (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

(Show k, Show p, Show (PatchTarget p)) => Show (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

(Ord k, DecidablyEmpty p, Patch p) => Semigroup (PatchMapWithPatchingMove k p) 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.MapWithPatchingMove

(Ord k, DecidablyEmpty p, Patch p) => Monoid (PatchMapWithPatchingMove k p) 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.MapWithPatchingMove

Wrapped (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Associated Types

type Unwrapped (PatchMapWithPatchingMove k p) :: Type #

(Ord k, DecidablyEmpty p, Patch p) => DecidablyEmpty (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

(Ord k, Patch p) => Patch (PatchMapWithPatchingMove k p) Source #

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

Instance details

Defined in Data.Patch.MapWithPatchingMove

Associated Types

type PatchTarget (PatchMapWithPatchingMove k p) :: Type Source #

PatchMapWithPatchingMove k1 p1 ~ t => Rewrapped (PatchMapWithPatchingMove k2 p2) t Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

type Unwrapped (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

type PatchTarget (PatchMapWithPatchingMove k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

data NodeInfo k p Source #

Holds the information about each key: where its new value should come from, and where its old value should go to

Constructors

NodeInfo 

Fields

  • _nodeInfo_from :: !(From k p)

    Where do we get the new value for this key?

  • _nodeInfo_to :: !(To k)

    If the old value is being kept (i.e. moved rather than deleted or replaced), where is it going?

Instances
(Eq k, Eq p, Eq (PatchTarget p)) => Eq (NodeInfo k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Methods

(==) :: NodeInfo k p -> NodeInfo k p -> Bool #

(/=) :: NodeInfo k p -> NodeInfo k p -> Bool #

(Ord k, Ord p, Ord (PatchTarget p)) => Ord (NodeInfo k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Methods

compare :: NodeInfo k p -> NodeInfo k p -> Ordering #

(<) :: NodeInfo k p -> NodeInfo k p -> Bool #

(<=) :: NodeInfo k p -> NodeInfo k p -> Bool #

(>) :: NodeInfo k p -> NodeInfo k p -> Bool #

(>=) :: NodeInfo k p -> NodeInfo k p -> Bool #

max :: NodeInfo k p -> NodeInfo k p -> NodeInfo k p #

min :: NodeInfo k p -> NodeInfo k p -> NodeInfo k p #

(Read k, Read p, Read (PatchTarget p)) => Read (NodeInfo k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

(Show k, Show p, Show (PatchTarget p)) => Show (NodeInfo k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Methods

showsPrec :: Int -> NodeInfo k p -> ShowS #

show :: NodeInfo k p -> String #

showList :: [NodeInfo k p] -> ShowS #

bitraverseNodeInfo :: Applicative f => (k0 -> f k1) -> (p0 -> f p1) -> (PatchTarget p0 -> f (PatchTarget p1)) -> NodeInfo k0 p0 -> f (NodeInfo k1 p1) Source #

data From k p Source #

Describe how a key's new value should be produced

Constructors

From_Insert (PatchTarget p)

Insert the given value here

From_Delete

Delete the existing value, if any, from here

From_Move !k !p

Move the value here from the given key, and apply the given patch

Instances
(Eq k, Eq p, Eq (PatchTarget p)) => Eq (From k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Methods

(==) :: From k p -> From k p -> Bool #

(/=) :: From k p -> From k p -> Bool #

(Ord k, Ord p, Ord (PatchTarget p)) => Ord (From k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Methods

compare :: From k p -> From k p -> Ordering #

(<) :: From k p -> From k p -> Bool #

(<=) :: From k p -> From k p -> Bool #

(>) :: From k p -> From k p -> Bool #

(>=) :: From k p -> From k p -> Bool #

max :: From k p -> From k p -> From k p #

min :: From k p -> From k p -> From k p #

(Read k, Read p, Read (PatchTarget p)) => Read (From k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Methods

readsPrec :: Int -> ReadS (From k p) #

readList :: ReadS [From k p] #

readPrec :: ReadPrec (From k p) #

readListPrec :: ReadPrec [From k p] #

(Show k, Show p, Show (PatchTarget p)) => Show (From k p) Source # 
Instance details

Defined in Data.Patch.MapWithPatchingMove

Methods

showsPrec :: Int -> From k p -> ShowS #

show :: From k p -> String #

showList :: [From k p] -> ShowS #

bitraverseFrom :: Applicative f => (k0 -> f k1) -> (p0 -> f p1) -> (PatchTarget p0 -> f (PatchTarget p1)) -> From k0 p0 -> f (From k1 p1) Source #

type To = Maybe Source #

Describe where a key's old value will go. If this is Just, that means the key's old value will be moved to the given other key; if it is Nothing, that means it will be deleted.

insertMapKey :: k -> PatchTarget p -> PatchMapWithPatchingMove k p Source #

Make a PatchMapWithPatchingMove k p which has the effect of inserting or replacing a value v at the given key k, like insert.

moveMapKey :: (DecidablyEmpty p, Patch p) => Ord k => k -> k -> PatchMapWithPatchingMove k p Source #

Make a PatchMapWithPatchingMove k p which has the effect of moving the value from the first key k to the second key k, equivalent to:

    delete src (maybe map (insert dst) (Map.lookup src map))

swapMapKey :: (DecidablyEmpty p, Patch p) => Ord k => k -> k -> PatchMapWithPatchingMove k p Source #

Make a PatchMapWithPatchingMove k p which has the effect of swapping two keys in the mapping, equivalent to:

    let aMay = Map.lookup a map
        bMay = Map.lookup b map
    in maybe id (Map.insert a) (bMay mplus aMay)
     . maybe id (Map.insert b) (aMay mplus bMay)
     . Map.delete a . Map.delete b $ map

deleteMapKey :: k -> PatchMapWithPatchingMove k v Source #

Make a PatchMapWithPatchingMove k v which has the effect of deleting a key in the mapping, equivalent to delete.

unsafePatchMapWithPatchingMove :: Map k (NodeInfo k p) -> PatchMapWithPatchingMove k p Source #

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

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

patchMapWithPatchingMoveNewElements :: PatchMapWithPatchingMove k p -> [PatchTarget p] Source #

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

patchMapWithPatchingMoveNewElementsMap :: PatchMapWithPatchingMove k p -> Map k (PatchTarget p) Source #

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

patchThatSortsMapWith :: (Ord k, Monoid p) => (PatchTarget p -> PatchTarget p -> Ordering) -> Map k (PatchTarget p) -> PatchMapWithPatchingMove k p Source #

Create a PatchMapWithPatchingMove that, if applied to the given Map, will sort its values using the given ordering function. The set keys of the Map is not changed.

patchThatChangesAndSortsMapWith :: forall k p. (Ord k, Ord (PatchTarget p), Monoid p) => (PatchTarget p -> PatchTarget p -> Ordering) -> Map k (PatchTarget p) -> Map k (PatchTarget p) -> PatchMapWithPatchingMove k p Source #

Create a PatchMapWithPatchingMove that, if applied to the first Map provided, will produce a Map with the same values as the second Map but with the values sorted with the given ordering function.

patchThatChangesMap :: (Ord k, Ord (PatchTarget p), Monoid p) => Map k (PatchTarget p) -> Map k (PatchTarget p) -> PatchMapWithPatchingMove k p Source #

Create a PatchMapWithPatchingMove that, if applied to the first Map provided, will produce the second Map.

nodeInfoMapFrom :: (From k v -> From k v) -> NodeInfo k v -> NodeInfo k v Source #

Change the From value of a NodeInfo

nodeInfoMapMFrom :: Functor f => (From k v -> f (From k v)) -> NodeInfo k v -> f (NodeInfo k v) Source #

Change the From value of a NodeInfo, using a Functor (or Applicative, Monad, etc.) action to get the new value

nodeInfoSetTo :: To k -> NodeInfo k v -> NodeInfo k v Source #

Set the To field of a NodeInfo

data Fixup k v Source #

Helper data structure used for composing patches using the monoid instance.

Constructors

Fixup_Delete 
Fixup_Update (These (From k v) (To k))