Safe Haskell | None |
---|---|
Language | Haskell2010 |
Patches of this type can can insert, delete, and move values from one key to another, and move patches may also additionally patch the value being moved.
Synopsis
- newtype PatchMapWithPatchingMove k p = PatchMapWithPatchingMove {
- unPatchMapWithPatchingMove :: Map k (NodeInfo k p)
- patchMapWithPatchingMove :: Ord k => Map k (NodeInfo k p) -> Maybe (PatchMapWithPatchingMove k p)
- patchMapWithPatchingMoveInsertAll :: Map k (PatchTarget p) -> PatchMapWithPatchingMove k p
- insertMapKey :: k -> PatchTarget p -> PatchMapWithPatchingMove k p
- moveMapKey :: (DecidablyEmpty p, Patch p) => Ord k => k -> k -> PatchMapWithPatchingMove k p
- patchMapKey :: DecidablyEmpty p => k -> p -> PatchMapWithPatchingMove k p
- swapMapKey :: (DecidablyEmpty p, Patch p) => Ord k => k -> k -> PatchMapWithPatchingMove k p
- deleteMapKey :: k -> PatchMapWithPatchingMove k v
- unsafePatchMapWithPatchingMove :: Map k (NodeInfo k p) -> PatchMapWithPatchingMove k p
- patchMapWithPatchingMoveNewElements :: PatchMapWithPatchingMove k p -> [PatchTarget p]
- patchMapWithPatchingMoveNewElementsMap :: PatchMapWithPatchingMove k p -> Map k (PatchTarget p)
- patchThatSortsMapWith :: (Ord k, Monoid p) => (PatchTarget p -> PatchTarget p -> Ordering) -> Map k (PatchTarget p) -> PatchMapWithPatchingMove k p
- 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
- patchThatChangesMap :: forall k p. (Ord k, Ord (PatchTarget p), Monoid p) => Map k (PatchTarget p) -> Map k (PatchTarget p) -> PatchMapWithPatchingMove k p
- data NodeInfo k p = NodeInfo {
- _nodeInfo_from :: !(From k p)
- _nodeInfo_to :: !(To k)
- bitraverseNodeInfo :: Applicative f => (k0 -> f k1) -> (p0 -> f p1) -> (PatchTarget p0 -> f (PatchTarget p1)) -> NodeInfo k0 p0 -> f (NodeInfo k1 p1)
- nodeInfoMapFrom :: (From k v -> From k v) -> NodeInfo k v -> NodeInfo k v
- nodeInfoMapMFrom :: Functor f => (From k v -> f (From k v)) -> NodeInfo k v -> f (NodeInfo k v)
- nodeInfoSetTo :: To k -> NodeInfo k v -> NodeInfo k v
- data From k p
- = From_Insert (PatchTarget p)
- | From_Delete
- | From_Move !k !p
- bitraverseFrom :: Applicative f => (k0 -> f k1) -> (p0 -> f p1) -> (PatchTarget p0 -> f (PatchTarget p1)) -> From k0 p0 -> f (From k1 p1)
- type To = Maybe
- data Fixup k v
- = Fixup_Delete
- | Fixup_Update (These (From k v) (To k))
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.
PatchMapWithPatchingMove | |
|
Instances
patchMapWithPatchingMove :: Ord k => Map k (NodeInfo k p) -> Maybe (PatchMapWithPatchingMove k p) Source #
Create a PatchMapWithPatchingMove
, validating it
patchMapWithPatchingMoveInsertAll :: Map k (PatchTarget p) -> PatchMapWithPatchingMove k p Source #
Create a PatchMapWithPatchingMove
that inserts everything in the given Map
insertMapKey :: k -> PatchTarget p -> PatchMapWithPatchingMove k p Source #
Make a
which has the effect of inserting or replacing a value PatchMapWithPatchingMove
k pv
at the given key k
, like insert
.
moveMapKey :: (DecidablyEmpty p, Patch p) => Ord k => k -> k -> PatchMapWithPatchingMove k p Source #
Make a
which has the effect of moving the value from the first key PatchMapWithPatchingMove
k pk
to the second key k
, equivalent to:
delete
src (maybe map (insert
dst) (Map.lookup src map))
patchMapKey :: DecidablyEmpty p => k -> p -> PatchMapWithPatchingMove k p Source #
swapMapKey :: (DecidablyEmpty p, Patch p) => Ord k => k -> k -> PatchMapWithPatchingMove k p Source #
Make a
which has the effect of swapping two keys in the mapping, equivalent to:PatchMapWithPatchingMove
k p
let aMay = Map.lookup a map bMay = Map.lookup b map in maybe id (Map.insert a) (bMay <> aMay) . maybe id (Map.insert b) (aMay <> bMay) . Map.delete a . Map.delete b $ map
deleteMapKey :: k -> PatchMapWithPatchingMove k v Source #
Make a
which has the effect of deleting a key in
the mapping, equivalent to PatchMapWithPatchingMove
k vdelete
.
unsafePatchMapWithPatchingMove :: Map k (NodeInfo k p) -> PatchMapWithPatchingMove k p Source #
Wrap a
representing patch changes into a Map
k (NodeInfo k v)
, without checking any invariants.PatchMapWithPatchingMove
k v
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
with all the inserts/updates from the given Map
k v
.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 :: forall k p. (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
.
Note: this will never produce a patch on a value.
Node Info
Holds the information about each key: where its new value should come from, and where its old value should go to
NodeInfo | |
|
Instances
(Eq k, Eq p, Eq (PatchTarget p)) => Eq (NodeInfo k p) Source # | |
(Ord k, Ord p, Ord (PatchTarget p)) => Ord (NodeInfo k p) Source # | |
Defined in Data.Patch.MapWithPatchingMove | |
(Read k, Read p, Read (PatchTarget p)) => Read (NodeInfo k p) Source # | |
(Show k, Show p, Show (PatchTarget p)) => Show (NodeInfo k p) Source # | |
bitraverseNodeInfo :: Applicative f => (k0 -> f k1) -> (p0 -> f p1) -> (PatchTarget p0 -> f (PatchTarget p1)) -> NodeInfo k0 p0 -> f (NodeInfo k1 p1) Source #
Traverse the NodeInfo
over the key, patch, and patch target. Because of
the type families here, this doesn't it any bi- or tri-traversal class.
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
From
Describe how a key's new value should be produced
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 # | |
(Ord k, Ord p, Ord (PatchTarget p)) => Ord (From k p) Source # | |
Defined in Data.Patch.MapWithPatchingMove | |
(Read k, Read p, Read (PatchTarget p)) => Read (From k p) Source # | |
(Show k, Show p, Show (PatchTarget p)) => Show (From k p) Source # | |
bitraverseFrom :: Applicative f => (k0 -> f k1) -> (p0 -> f p1) -> (PatchTarget p0 -> f (PatchTarget p1)) -> From k0 p0 -> f (From k1 p1) Source #
Traverse the From
over the key, patch, and patch target. Because of
the type families here, this doesn't it any bi- or tri-traversal class.
To
Helper data structure used for composing patches using the monoid instance.
Fixup_Delete | |
Fixup_Update (These (From k v) (To k)) |