reflex-0.6.2.3: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Patch

Description

 
Synopsis

Documentation

newtype AdditivePatch p Source #

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

Constructors

AdditivePatch 

Fields

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

Defined in Reflex.Patch

Associated Types

type PatchTarget (AdditivePatch p) :: Type Source #

type PatchTarget (AdditivePatch p) Source # 
Instance details

Defined in Reflex.Patch

class Semigroup q => Additive q Source #

An Additive Semigroup is one where (<>) is commutative

Instances
Additive SelectedCount Source # 
Instance details

Defined in Reflex.Query.Class

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

Defined in Reflex.Patch

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
Group SelectedCount Source # 
Instance details

Defined in Reflex.Query.Class

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

Defined in Reflex.Patch

class Patch p where Source #

A Patch type represents a kind of change made to a datastructure.

If an instance of Patch is also an instance of Semigroup, it should obey the law that applyAlways (f <> g) == applyAlways f . applyAlways g.

Associated Types

type PatchTarget p :: * Source #

Methods

apply :: p -> PatchTarget p -> Maybe (PatchTarget p) Source #

Apply the patch p a to the value a. If no change is needed, return Nothing.

Instances
Patch (Identity a) Source #

Identity can be used as a Patch that always fully replaces the value

Instance details

Defined in Reflex.Patch.Class

Associated Types

type PatchTarget (Identity a) :: Type Source #

Patch (PatchIntMap a) Source #

Apply the insertions or deletions to a given IntMap.

Instance details

Defined in Reflex.Patch.IntMap

Associated Types

type PatchTarget (PatchIntMap a) :: Type Source #

Additive p => Patch (AdditivePatch p) Source # 
Instance details

Defined in Reflex.Patch

Associated Types

type PatchTarget (AdditivePatch p) :: Type Source #

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

Apply the insertions or deletions to a given Map.

Instance details

Defined in Reflex.Patch.Map

Associated Types

type PatchTarget (PatchMap k v) :: Type Source #

Methods

apply :: PatchMap k v -> PatchTarget (PatchMap k v) -> Maybe (PatchTarget (PatchMap k v)) Source #

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

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

Instance details

Defined in Reflex.Patch.MapWithMove

Associated Types

type PatchTarget (PatchMapWithMove k v) :: Type Source #

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

Apply the insertions or deletions to a given DMap.

Instance details

Defined in Reflex.Patch.DMap

Associated Types

type PatchTarget (PatchDMap k2 v) :: Type Source #

Methods

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

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

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

Instance details

Defined in Reflex.Patch.DMapWithMove

Associated Types

type PatchTarget (PatchDMapWithMove k2 v) :: Type Source #

applyAlways :: Patch p => p -> PatchTarget p -> PatchTarget p Source #

Apply a Patch; if it does nothing, return the original value

composePatchFunctions :: (Patch p, Semigroup p) => (PatchTarget p -> p) -> (PatchTarget p -> p) -> PatchTarget p -> p Source #

Like '(.)', but composes functions that return patches rather than functions that return new values. The Semigroup instance for patches must apply patches right-to-left, like '(.)'.

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 (IntMap (Maybe a)) 
Instances
Functor PatchIntMap Source # 
Instance details

Defined in Reflex.Patch.IntMap

Methods

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

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

Foldable PatchIntMap Source # 
Instance details

Defined in Reflex.Patch.IntMap

Methods

fold :: Monoid m => PatchIntMap m -> 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 Reflex.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) #

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 Reflex.Patch.IntMap

Monoid (PatchIntMap a) Source # 
Instance details

Defined in Reflex.Patch.IntMap

Patch (PatchIntMap a) Source #

Apply the insertions or deletions to a given IntMap.

Instance details

Defined in Reflex.Patch.IntMap

Associated Types

type PatchTarget (PatchIntMap a) :: Type Source #

type PatchTarget (PatchIntMap a) Source # 
Instance details

Defined in Reflex.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 PatchMap k v Source #

A set of changes to a Map. Any element may be inserted/updated or deleted. Insertions are represented as values wrapped in Just, while deletions are represented as Nothings

Constructors

PatchMap 

Fields

Instances
Functor (PatchMap k) Source #

fmapping a PatchMap will alter all of the values it will insert. Deletions are unaffected.

Instance details

Defined in Reflex.Patch.Map

Methods

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

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

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

Defined in Reflex.Patch.Map

Methods

(==) :: PatchMap k v -> PatchMap k v -> Bool #

(/=) :: PatchMap k v -> PatchMap k v -> Bool #

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

Defined in Reflex.Patch.Map

Methods

compare :: PatchMap k v -> PatchMap k v -> Ordering #

(<) :: PatchMap k v -> PatchMap k v -> Bool #

(<=) :: PatchMap k v -> PatchMap k v -> Bool #

(>) :: PatchMap k v -> PatchMap k v -> Bool #

(>=) :: PatchMap k v -> PatchMap k v -> Bool #

max :: PatchMap k v -> PatchMap k v -> PatchMap k v #

min :: PatchMap k v -> PatchMap k v -> PatchMap k v #

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

Defined in Reflex.Patch.Map

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

Defined in Reflex.Patch.Map

Methods

showsPrec :: Int -> PatchMap k v -> ShowS #

show :: PatchMap k v -> String #

showList :: [PatchMap k v] -> ShowS #

Ord k => Semigroup (PatchMap k 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 Reflex.Patch.Map

Methods

(<>) :: PatchMap k v -> PatchMap k v -> PatchMap k v #

sconcat :: NonEmpty (PatchMap k v) -> PatchMap k v #

stimes :: Integral b => b -> PatchMap k v -> PatchMap k v #

Ord k => Monoid (PatchMap k v) Source #

The empty PatchMap contains no insertions or deletions

Instance details

Defined in Reflex.Patch.Map

Methods

mempty :: PatchMap k v #

mappend :: PatchMap k v -> PatchMap k v -> PatchMap k v #

mconcat :: [PatchMap k v] -> PatchMap k v #

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

Apply the insertions or deletions to a given Map.

Instance details

Defined in Reflex.Patch.Map

Associated Types

type PatchTarget (PatchMap k v) :: Type Source #

Methods

apply :: PatchMap k v -> PatchTarget (PatchMap k v) -> Maybe (PatchTarget (PatchMap k v)) Source #

type PatchTarget (PatchMap k v) Source # 
Instance details

Defined in Reflex.Patch.Map

type PatchTarget (PatchMap k v) = Map k v

patchMapNewElements :: PatchMap k v -> [v] Source #

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

patchMapNewElementsMap :: PatchMap k v -> Map k v Source #

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

newtype PatchDMap k v 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
GCompare k2 => Semigroup (PatchDMap k2 v) Source # 
Instance details

Defined in Reflex.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 => Monoid (PatchDMap k2 v) Source # 
Instance details

Defined in Reflex.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 => Patch (PatchDMap k2 v) Source #

Apply the insertions or deletions to a given DMap.

Instance details

Defined in Reflex.Patch.DMap

Associated Types

type PatchTarget (PatchDMap k2 v) :: Type Source #

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 Reflex.Patch.DMap

type PatchTarget (PatchDMap k2 v) = DMap k2 v

mapPatchDMap :: (forall a. v a -> v' a) -> PatchDMap k v -> PatchDMap k 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 :: Applicative f => (forall a. v a -> f (v' a)) -> PatchDMap k v -> f (PatchDMap k 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 :: Applicative m => (forall a. k a -> v a -> m (v' a)) -> PatchDMap k v -> m (PatchDMap k 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 a. v a -> v') -> PatchDMap k v -> PatchMap (Some k) 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 :: (v a -> v') -> PatchDMap (Const2 k a) v -> PatchMap k 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 k v v' a. (v -> v' a) -> PatchMap k v -> PatchDMap (Const2 k a) v' Source #

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

const2IntPatchDMapWith :: forall v f a. (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.

data PatchMapWithMove k v Source #

Patch a DMap 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
Functor (PatchMapWithMove k) Source # 
Instance details

Defined in Reflex.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 Reflex.Patch.MapWithMove

Methods

fold :: Monoid m => PatchMapWithMove k m -> 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 Reflex.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) #

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

Defined in Reflex.Patch.MapWithMove

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

Defined in Reflex.Patch.MapWithMove

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

Defined in Reflex.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 Reflex.Patch.MapWithMove

Ord k => Monoid (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 Reflex.Patch.MapWithMove

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

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

Instance details

Defined in Reflex.Patch.MapWithMove

Associated Types

type PatchTarget (PatchMapWithMove k v) :: Type Source #

type PatchTarget (PatchMapWithMove k v) Source # 
Instance details

Defined in Reflex.Patch.MapWithMove

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

Extract the internal representation of the PatchMapWithMove

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.

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.

data PatchDMapWithMove k v 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
(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 Reflex.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 Reflex.Patch.DMapWithMove

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 Reflex.Patch.DMapWithMove

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

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

Instance details

Defined in Reflex.Patch.DMapWithMove

Associated Types

type PatchTarget (PatchDMapWithMove k2 v) :: Type Source #

type PatchTarget (PatchDMapWithMove k2 v) Source # 
Instance details

Defined in Reflex.Patch.DMapWithMove

unPatchDMapWithMove :: PatchDMapWithMove k v -> DMap k (NodeInfo k v) Source #

Extract the DMap representing the patch changes from the PatchDMapWithMove.

unsafePatchDMapWithMove :: DMap k (NodeInfo k v) -> PatchDMapWithMove k 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.

mapPatchDMapWithMove :: forall k v v'. (forall a. v a -> v' a) -> PatchDMapWithMove k v -> PatchDMapWithMove k v' Source #

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

traversePatchDMapWithMoveWithKey :: forall m k v v'. Applicative m => (forall a. k a -> v a -> m (v' a)) -> PatchDMapWithMove k v -> m (PatchDMapWithMove k 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').

weakenPatchDMapWithMoveWith :: forall k v v'. (forall a. v a -> v') -> PatchDMapWithMove k v -> PatchMapWithMove (Some k) 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.

patchDMapWithMoveToPatchMapWithMoveWith :: forall k v v' a. (v a -> v') -> PatchDMapWithMove (Const2 k a) v -> PatchMapWithMove k 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.

const2PatchDMapWithMoveWith :: forall k v v' a. (v -> v' a) -> PatchMapWithMove k v -> PatchDMapWithMove (Const2 k 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