reflex-0.6: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Reflex.Pure

Contents

Description

 
Synopsis

Documentation

data Pure t Source #

A completely pure-functional Reflex timeline, identifying moments in time with the type t.

Instances
(Enum t, HasTrie t, Ord t) => Reflex (Pure t :: *) Source #

The Enum instance of t must be dense: for all x :: t, there must not exist any y :: t such that pred x < y < x. The HasTrie instance will be used exclusively to memoize functions of t, not for any of its other capabilities.

Instance details

Defined in Reflex.Pure

Associated Types

data Behavior (Pure t) a :: * Source #

data Event (Pure t) a :: * Source #

data Dynamic (Pure t) a :: * Source #

data Incremental (Pure t) a :: * Source #

type PushM (Pure t) :: * -> * Source #

type PullM (Pure t) :: * -> * Source #

Methods

never :: Event (Pure t) a Source #

constant :: a -> Behavior (Pure t) a Source #

push :: (a -> PushM (Pure t) (Maybe b)) -> Event (Pure t) a -> Event (Pure t) b Source #

pushCheap :: (a -> PushM (Pure t) (Maybe b)) -> Event (Pure t) a -> Event (Pure t) b Source #

pull :: PullM (Pure t) a -> Behavior (Pure t) a Source #

merge :: GCompare k => DMap k (Event (Pure t)) -> Event (Pure t) (DMap k Identity) Source #

fan :: GCompare k => Event (Pure t) (DMap k Identity) -> EventSelector (Pure t) k Source #

switch :: Behavior (Pure t) (Event (Pure t) a) -> Event (Pure t) a Source #

coincidence :: Event (Pure t) (Event (Pure t) a) -> Event (Pure t) a Source #

current :: Dynamic (Pure t) a -> Behavior (Pure t) a Source #

updated :: Dynamic (Pure t) a -> Event (Pure t) a Source #

unsafeBuildDynamic :: PullM (Pure t) a -> Event (Pure t) a -> Dynamic (Pure t) a Source #

unsafeBuildIncremental :: Patch p => PullM (Pure t) (PatchTarget p) -> Event (Pure t) p -> Incremental (Pure t) p Source #

mergeIncremental :: GCompare k => Incremental (Pure t) (PatchDMap k (Event (Pure t))) -> Event (Pure t) (DMap k Identity) Source #

mergeIncrementalWithMove :: GCompare k => Incremental (Pure t) (PatchDMapWithMove k (Event (Pure t))) -> Event (Pure t) (DMap k Identity) Source #

currentIncremental :: Patch p => Incremental (Pure t) p -> Behavior (Pure t) (PatchTarget p) Source #

updatedIncremental :: Patch p => Incremental (Pure t) p -> Event (Pure t) p Source #

incrementalToDynamic :: Patch p => Incremental (Pure t) p -> Dynamic (Pure t) (PatchTarget p) Source #

behaviorCoercion :: Coercion a b -> Coercion (Behavior (Pure t) a) (Behavior (Pure t) b) Source #

eventCoercion :: Coercion a b -> Coercion (Event (Pure t) a) (Event (Pure t) b) Source #

dynamicCoercion :: Coercion a b -> Coercion (Dynamic (Pure t) a) (Dynamic (Pure t) b) Source #

mergeIntIncremental :: Incremental (Pure t) (PatchIntMap (Event (Pure t) a)) -> Event (Pure t) (IntMap a) Source #

fanInt :: Event (Pure t) (IntMap a) -> EventSelectorInt (Pure t) a Source #

(Enum t, HasTrie t, Ord t) => MonadHold (Pure t :: *) ((->) t :: * -> *) Source # 
Instance details

Defined in Reflex.Pure

Methods

hold :: a -> Event (Pure t) a -> t -> Behavior (Pure t) a Source #

holdDyn :: a -> Event (Pure t) a -> t -> Dynamic (Pure t) a Source #

holdIncremental :: Patch p => PatchTarget p -> Event (Pure t) p -> t -> Incremental (Pure t) p Source #

buildDynamic :: PushM (Pure t) a -> Event (Pure t) a -> t -> Dynamic (Pure t) a Source #

headE :: Event (Pure t) a -> t -> Event (Pure t) a Source #

MonadSample (Pure t :: *) ((->) t :: * -> *) Source # 
Instance details

Defined in Reflex.Pure

Methods

sample :: Behavior (Pure t) a -> t -> a Source #

Monad (Dynamic (Pure t)) Source # 
Instance details

Defined in Reflex.Pure

Methods

(>>=) :: Dynamic (Pure t) a -> (a -> Dynamic (Pure t) b) -> Dynamic (Pure t) b #

(>>) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) b #

return :: a -> Dynamic (Pure t) a #

fail :: String -> Dynamic (Pure t) a #

Functor (Dynamic (Pure t)) Source # 
Instance details

Defined in Reflex.Pure

Methods

fmap :: (a -> b) -> Dynamic (Pure t) a -> Dynamic (Pure t) b #

(<$) :: a -> Dynamic (Pure t) b -> Dynamic (Pure t) a #

Applicative (Dynamic (Pure t)) Source # 
Instance details

Defined in Reflex.Pure

Methods

pure :: a -> Dynamic (Pure t) a #

(<*>) :: Dynamic (Pure t) (a -> b) -> Dynamic (Pure t) a -> Dynamic (Pure t) b #

liftA2 :: (a -> b -> c) -> Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) c #

(*>) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) b #

(<*) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) a #

data Behavior (Pure t :: *) a Source # 
Instance details

Defined in Reflex.Pure

data Behavior (Pure t :: *) a = Behavior {}
data Event (Pure t :: *) a Source # 
Instance details

Defined in Reflex.Pure

data Event (Pure t :: *) a = Event {}
data Dynamic (Pure t :: *) a Source # 
Instance details

Defined in Reflex.Pure

data Dynamic (Pure t :: *) a = Dynamic {}
data Incremental (Pure t :: *) p Source # 
Instance details

Defined in Reflex.Pure

data Incremental (Pure t :: *) p = Incremental {}
type PushM (Pure t :: *) Source # 
Instance details

Defined in Reflex.Pure

type PushM (Pure t :: *) = ((->) t :: * -> *)
type PullM (Pure t :: *) Source # 
Instance details

Defined in Reflex.Pure

type PullM (Pure t :: *) = ((->) t :: * -> *)

data family Behavior t :: * -> * Source #

A container for a value that can change over time. Behaviors can be sampled at will, but it is not possible to be notified when they change

Instances
Reflex t => Accumulator (t :: k) (Behavior t) Source # 
Instance details

Defined in Reflex.Class

Methods

accum :: (MonadHold t m, MonadFix m) => (a -> b -> a) -> a -> Event t b -> m (Behavior t a) Source #

accumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t a) -> a -> Event t b -> m (Behavior t a) Source #

accumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> Maybe a) -> a -> Event t b -> m (Behavior t a) Source #

accumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a)) -> a -> Event t b -> m (Behavior t a) Source #

mapAccum :: (MonadHold t m, MonadFix m) => (a -> b -> (a, c)) -> a -> Event t b -> m (Behavior t a, Event t c) Source #

mapAccumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (a, c)) -> a -> Event t b -> m (Behavior t a, Event t c) Source #

mapAccumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> (Maybe a, Maybe c)) -> a -> Event t b -> m (Behavior t a, Event t c) Source #

mapAccumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a, Maybe c)) -> a -> Event t b -> m (Behavior t a, Event t c) Source #

Reflex t => Monad (Behavior t) Source # 
Instance details

Defined in Reflex.Class

Methods

(>>=) :: Behavior t a -> (a -> Behavior t b) -> Behavior t b #

(>>) :: Behavior t a -> Behavior t b -> Behavior t b #

return :: a -> Behavior t a #

fail :: String -> Behavior t a #

Reflex t => Functor (Behavior t) Source # 
Instance details

Defined in Reflex.Class

Methods

fmap :: (a -> b) -> Behavior t a -> Behavior t b #

(<$) :: a -> Behavior t b -> Behavior t a #

Reflex t => Applicative (Behavior t) Source # 
Instance details

Defined in Reflex.Class

Methods

pure :: a -> Behavior t a #

(<*>) :: Behavior t (a -> b) -> Behavior t a -> Behavior t b #

liftA2 :: (a -> b -> c) -> Behavior t a -> Behavior t b -> Behavior t c #

(*>) :: Behavior t a -> Behavior t b -> Behavior t b #

(<*) :: Behavior t a -> Behavior t b -> Behavior t a #

Reflex t => Apply (Behavior t) Source # 
Instance details

Defined in Reflex.Class

Methods

(<.>) :: Behavior t (a -> b) -> Behavior t a -> Behavior t b #

(.>) :: Behavior t a -> Behavior t b -> Behavior t b #

(<.) :: Behavior t a -> Behavior t b -> Behavior t a #

liftF2 :: (a -> b -> c) -> Behavior t a -> Behavior t b -> Behavior t c #

Reflex t => Bind (Behavior t) Source # 
Instance details

Defined in Reflex.Class

Methods

(>>-) :: Behavior t a -> (a -> Behavior t b) -> Behavior t b #

join :: Behavior t (Behavior t a) -> Behavior t a #

(Reflex t, Fractional a) => Fractional (Behavior t a) Source # 
Instance details

Defined in Reflex.Class

Methods

(/) :: Behavior t a -> Behavior t a -> Behavior t a #

recip :: Behavior t a -> Behavior t a #

fromRational :: Rational -> Behavior t a #

(Reflex t, Num a) => Num (Behavior t a) Source # 
Instance details

Defined in Reflex.Class

Methods

(+) :: Behavior t a -> Behavior t a -> Behavior t a #

(-) :: Behavior t a -> Behavior t a -> Behavior t a #

(*) :: Behavior t a -> Behavior t a -> Behavior t a #

negate :: Behavior t a -> Behavior t a #

abs :: Behavior t a -> Behavior t a #

signum :: Behavior t a -> Behavior t a #

fromInteger :: Integer -> Behavior t a #

(Reflex t, IsString a) => IsString (Behavior t a) Source # 
Instance details

Defined in Reflex.Class

Methods

fromString :: String -> Behavior t a #

(Reflex t, Semigroup a) => Semigroup (Behavior t a) Source # 
Instance details

Defined in Reflex.Class

Methods

(<>) :: Behavior t a -> Behavior t a -> Behavior t a #

sconcat :: NonEmpty (Behavior t a) -> Behavior t a #

stimes :: Integral b => b -> Behavior t a -> Behavior t a #

(Reflex t, Monoid a) => Monoid (Behavior t a) Source # 
Instance details

Defined in Reflex.Class

Methods

mempty :: Behavior t a #

mappend :: Behavior t a -> Behavior t a -> Behavior t a #

mconcat :: [Behavior t a] -> Behavior t a #

data Behavior (Pure t :: *) a Source # 
Instance details

Defined in Reflex.Pure

data Behavior (Pure t :: *) a = Behavior {}
data Behavior (ProfiledTimeline t :: *) a Source # 
Instance details

Defined in Reflex.Profiled

data Behavior (SpiderTimeline x :: *) a Source # 
Instance details

Defined in Reflex.Spider.Internal

data family Event t :: * -> * Source #

A stream of occurrences. During any given frame, an Event is either occurring or not occurring; if it is occurring, it will contain a value of the given type (its "occurrence type")

Instances
Reflex t => Accumulator (t :: k) (Event t) Source # 
Instance details

Defined in Reflex.Class

Methods

accum :: (MonadHold t m, MonadFix m) => (a -> b -> a) -> a -> Event t b -> m (Event t a) Source #

accumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t a) -> a -> Event t b -> m (Event t a) Source #

accumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> Maybe a) -> a -> Event t b -> m (Event t a) Source #

accumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a)) -> a -> Event t b -> m (Event t a) Source #

mapAccum :: (MonadHold t m, MonadFix m) => (a -> b -> (a, c)) -> a -> Event t b -> m (Event t a, Event t c) Source #

mapAccumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (a, c)) -> a -> Event t b -> m (Event t a, Event t c) Source #

mapAccumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> (Maybe a, Maybe c)) -> a -> Event t b -> m (Event t a, Event t c) Source #

mapAccumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a, Maybe c)) -> a -> Event t b -> m (Event t a, Event t c) Source #

Reflex t => Functor (Event t) Source # 
Instance details

Defined in Reflex.Class

Methods

fmap :: (a -> b) -> Event t a -> Event t b #

(<$) :: a -> Event t b -> Event t a #

Reflex t => Apply (Event t) Source #

Event intersection (convenient interface to coincidence).

Instance details

Defined in Reflex.Class

Methods

(<.>) :: Event t (a -> b) -> Event t a -> Event t b #

(.>) :: Event t a -> Event t b -> Event t b #

(<.) :: Event t a -> Event t b -> Event t a #

liftF2 :: (a -> b -> c) -> Event t a -> Event t b -> Event t c #

Reflex t => Plus (Event t) Source #

Never: zero = never.

Instance details

Defined in Reflex.Class

Methods

zero :: Event t a #

Reflex t => Alt (Event t) Source #

Left-biased event union (prefers left event on simultaneous occurrence).

Instance details

Defined in Reflex.Class

Methods

(<!>) :: Event t a -> Event t a -> Event t a #

some :: Applicative (Event t) => Event t a -> Event t [a] #

many :: Applicative (Event t) => Event t a -> Event t [a] #

Reflex t => Bind (Event t) Source #

Event intersection (convenient interface to coincidence).

Instance details

Defined in Reflex.Class

Methods

(>>-) :: Event t a -> (a -> Event t b) -> Event t b #

join :: Event t (Event t a) -> Event t a #

Reflex t => Align (Event t) Source # 
Instance details

Defined in Reflex.Class

Methods

nil :: Event t a #

align :: Event t a -> Event t b -> Event t (These a b) #

alignWith :: (These a b -> c) -> Event t a -> Event t b -> Event t c #

Reflex t => Filterable (Event t) Source # 
Instance details

Defined in Reflex.Class

Methods

mapMaybe :: (a -> Maybe b) -> Event t a -> Event t b #

catMaybes :: Event t (Maybe a) -> Event t a #

filter :: (a -> Bool) -> Event t a -> Event t a #

Reflex t => FunctorMaybe (Event t) Source # 
Instance details

Defined in Reflex.Class

Methods

fmapMaybe :: (a -> Maybe b) -> Event t a -> Event t b Source #

(Semigroup a, Reflex t) => Semigroup (Event t a) Source # 
Instance details

Defined in Reflex.Class

Methods

(<>) :: Event t a -> Event t a -> Event t a #

sconcat :: NonEmpty (Event t a) -> Event t a #

stimes :: Integral b => b -> Event t a -> Event t a #

(Semigroup a, Reflex t) => Monoid (Event t a) Source # 
Instance details

Defined in Reflex.Class

Methods

mempty :: Event t a #

mappend :: Event t a -> Event t a -> Event t a #

mconcat :: [Event t a] -> Event t a #

data Event (Pure t :: *) a Source # 
Instance details

Defined in Reflex.Pure

data Event (Pure t :: *) a = Event {}
data Event (ProfiledTimeline t :: *) a Source # 
Instance details

Defined in Reflex.Profiled

data Event (SpiderTimeline x :: *) a Source # 
Instance details

Defined in Reflex.Spider.Internal

data family Dynamic t :: * -> * Source #

A container for a value that can change over time and allows notifications on changes. Basically a combination of a Behavior and an Event, with a rule that the Behavior will change if and only if the Event fires.

Instances
Reflex t => Accumulator (t :: k) (Dynamic t) Source # 
Instance details

Defined in Reflex.Class

Methods

accum :: (MonadHold t m, MonadFix m) => (a -> b -> a) -> a -> Event t b -> m (Dynamic t a) Source #

accumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t a) -> a -> Event t b -> m (Dynamic t a) Source #

accumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> Maybe a) -> a -> Event t b -> m (Dynamic t a) Source #

accumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a)) -> a -> Event t b -> m (Dynamic t a) Source #

mapAccum :: (MonadHold t m, MonadFix m) => (a -> b -> (a, c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

mapAccumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (a, c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

mapAccumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> (Maybe a, Maybe c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

mapAccumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a, Maybe c)) -> a -> Event t b -> m (Dynamic t a, Event t c) Source #

Monad (Dynamic (Pure t)) # 
Instance details

Defined in Reflex.Pure

Methods

(>>=) :: Dynamic (Pure t) a -> (a -> Dynamic (Pure t) b) -> Dynamic (Pure t) b #

(>>) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) b #

return :: a -> Dynamic (Pure t) a #

fail :: String -> Dynamic (Pure t) a #

Monad (Dynamic t) => Monad (Dynamic (ProfiledTimeline t)) # 
Instance details

Defined in Reflex.Profiled

HasSpiderTimeline x => Monad (Dynamic (SpiderTimeline x)) # 
Instance details

Defined in Reflex.Spider.Internal

Functor (Dynamic (Pure t)) # 
Instance details

Defined in Reflex.Pure

Methods

fmap :: (a -> b) -> Dynamic (Pure t) a -> Dynamic (Pure t) b #

(<$) :: a -> Dynamic (Pure t) b -> Dynamic (Pure t) a #

Functor (Dynamic t) => Functor (Dynamic (ProfiledTimeline t)) # 
Instance details

Defined in Reflex.Profiled

Methods

fmap :: (a -> b) -> Dynamic (ProfiledTimeline t) a -> Dynamic (ProfiledTimeline t) b #

(<$) :: a -> Dynamic (ProfiledTimeline t) b -> Dynamic (ProfiledTimeline t) a #

HasSpiderTimeline x => Functor (Dynamic (SpiderTimeline x)) # 
Instance details

Defined in Reflex.Spider.Internal

Methods

fmap :: (a -> b) -> Dynamic (SpiderTimeline x) a -> Dynamic (SpiderTimeline x) b #

(<$) :: a -> Dynamic (SpiderTimeline x) b -> Dynamic (SpiderTimeline x) a #

Applicative (Dynamic (Pure t)) # 
Instance details

Defined in Reflex.Pure

Methods

pure :: a -> Dynamic (Pure t) a #

(<*>) :: Dynamic (Pure t) (a -> b) -> Dynamic (Pure t) a -> Dynamic (Pure t) b #

liftA2 :: (a -> b -> c) -> Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) c #

(*>) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) b #

(<*) :: Dynamic (Pure t) a -> Dynamic (Pure t) b -> Dynamic (Pure t) a #

Applicative (Dynamic t) => Applicative (Dynamic (ProfiledTimeline t)) # 
Instance details

Defined in Reflex.Profiled

HasSpiderTimeline x => Applicative (Dynamic (SpiderTimeline x)) # 
Instance details

Defined in Reflex.Spider.Internal

(Num a, Reflex t) => Num (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

(+) :: Dynamic t a -> Dynamic t a -> Dynamic t a #

(-) :: Dynamic t a -> Dynamic t a -> Dynamic t a #

(*) :: Dynamic t a -> Dynamic t a -> Dynamic t a #

negate :: Dynamic t a -> Dynamic t a #

abs :: Dynamic t a -> Dynamic t a #

signum :: Dynamic t a -> Dynamic t a #

fromInteger :: Integer -> Dynamic t a #

(Reflex t, IsString a) => IsString (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

fromString :: String -> Dynamic t a #

(Reflex t, Semigroup a) => Semigroup (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

(<>) :: Dynamic t a -> Dynamic t a -> Dynamic t a #

sconcat :: NonEmpty (Dynamic t a) -> Dynamic t a #

stimes :: Integral b => b -> Dynamic t a -> Dynamic t a #

(Reflex t, Monoid a) => Monoid (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

mempty :: Dynamic t a #

mappend :: Dynamic t a -> Dynamic t a -> Dynamic t a #

mconcat :: [Dynamic t a] -> Dynamic t a #

(Reflex t, Default a) => Default (Dynamic t a) Source # 
Instance details

Defined in Reflex.Class

Methods

def :: Dynamic t a #

data Dynamic (Pure t :: *) a Source # 
Instance details

Defined in Reflex.Pure

data Dynamic (Pure t :: *) a = Dynamic {}
data Dynamic (ProfiledTimeline t :: *) a Source # 
Instance details

Defined in Reflex.Profiled

data Dynamic (SpiderTimeline x :: *) a Source # 
Instance details

Defined in Reflex.Spider.Internal

data family Incremental t :: * -> * Source #

An Incremental is a more general form of a Dynamic. Instead of always fully replacing the value, only parts of it can be patched. This is only needed for performance critical code via mergeIncremental to make small changes to large values.

Instances
data Incremental (Pure t :: *) p Source # 
Instance details

Defined in Reflex.Pure

data Incremental (Pure t :: *) p = Incremental {}
data Incremental (ProfiledTimeline t :: *) p Source # 
Instance details

Defined in Reflex.Profiled

data Incremental (SpiderTimeline x :: *) p Source # 
Instance details

Defined in Reflex.Spider.Internal

Orphan instances

MonadSample (Pure t :: *) ((->) t :: * -> *) Source # 
Instance details

Methods

sample :: Behavior (Pure t) a -> t -> a Source #