reflex-0.6.4.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell2010

Reflex.Time

Contents

Description

 
Synopsis

Documentation

data TickInfo Source #

Metadata associated with a timer "tick"

Constructors

TickInfo 

Fields

Instances
Eq TickInfo Source # 
Instance details

Defined in Reflex.Time

Ord TickInfo Source # 
Instance details

Defined in Reflex.Time

Show TickInfo Source # 
Instance details

Defined in Reflex.Time

tickLossy :: (PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) => NominalDiffTime -> UTCTime -> m (Event t TickInfo) Source #

Fires an Event once every time provided interval elapses, approximately. The provided UTCTime is used bootstrap the determination of how much time has elapsed with each tick. This is a special case of tickLossyFrom that uses the post-build event to start the tick thread.

tickLossyFromPostBuildTime :: (PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) => NominalDiffTime -> m (Event t TickInfo) Source #

Fires an Event once every time provided interval elapses, approximately. This is a special case of tickLossyFrom that uses the post-build event to start the tick thread and the time of the post-build as the tick basis time.

tickLossyFrom Source #

Arguments

:: (PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) 
=> NominalDiffTime

The length of a tick interval

-> UTCTime

The basis time from which intervals count and with which the initial calculation of elapsed time will be made.

-> Event t a

Event that starts a tick generation thread. Usually you want this to be something like the result of getPostBuild that only fires once. But there could be uses for starting multiple timer threads.

-> m (Event t TickInfo) 

Fires an Event approximately each time the provided interval elapses. If the system starts running behind, occurrences will be dropped rather than buffered. Each occurrence of the resulting event will contain the index of the current interval, with 0 representing the provided initial time.

tickLossyFrom' Source #

Arguments

:: (PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) 
=> Event t (NominalDiffTime, UTCTime)

Event that starts a tick generation thread. Usually you want this to be something like the result of getPostBuild that only fires once. But there could be uses for starting multiple timer threads.

-> m (Event t TickInfo) 

Generalization of tickLossyFrom that takes the delay and initial time as an Event.

clockLossy :: (MonadIO m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), PostBuild t m, MonadHold t m, MonadFix m) => NominalDiffTime -> UTCTime -> m (Dynamic t TickInfo) Source #

Like tickLossy, but immediately calculates the first tick and provides a Dynamic that is updated as ticks fire.

getCurrentTick :: NominalDiffTime -> UTCTime -> IO TickInfo Source #

Generates a TickInfo, given the specified interval and timestamp. The TickInfo will include the current time, the number of ticks that have elapsed since the timestamp, and the amount of time that has elapsed since the start time of this tick.

delay :: (PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a) Source #

Delay an Event's occurrences by a given amount in seconds.

poissonLossyFrom Source #

Arguments

:: (RandomGen g, MonadIO (Performable m), PerformEvent t m, TriggerEvent t m) 
=> g 
-> Double

Poisson event rate (Hz)

-> UTCTime

Baseline time for events

-> Event t a

Event that starts a tick generation thread. Usually you want this to be something like the result of getPostBuild that only fires once. But there could be uses for starting multiple timer threads. Start sending events in response to the event parameter.

-> m (Event t TickInfo) 

Send events with Poisson timing with the given basis and rate Each occurrence of the resulting event will contain the index of the current interval, with 0 representing the basis time

poissonLossy Source #

Arguments

:: (RandomGen g, MonadIO (Performable m), PerformEvent t m, TriggerEvent t m, PostBuild t m) 
=> g 
-> Double

Poisson event rate (Hz)

-> UTCTime

Baseline time for events

-> m (Event t TickInfo) 

Send events with Poisson timing with the given basis and rate Each occurrence of the resulting event will contain the index of the current interval, with 0 representing the basis time. Automatically begin sending events when the DOM is built

inhomogeneousPoissonFrom :: (RandomGen g, MonadIO (Performable m), PerformEvent t m, TriggerEvent t m) => g -> Behavior t Double -> Double -> UTCTime -> Event t a -> m (Event t TickInfo) Source #

Send events with inhomogeneous Poisson timing with the given basis and variable rate. Provide a maxRate that you expect to support.

inhomogeneousPoisson :: (RandomGen g, MonadIO (Performable m), PerformEvent t m, TriggerEvent t m, PostBuild t m) => g -> Behavior t Double -> Double -> UTCTime -> m (Event t TickInfo) Source #

Send events with inhomogeneous Poisson timing with the given basis and variable rate. Provide a maxRate that you expect to support

debounce :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a) Source #

Block occurrences of an Event until the given number of seconds elapses without the Event firing, at which point the last occurrence of the Event will fire.

batchOccurrences :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t (Seq a)) Source #

When the given Event occurs, wait the given amount of time and collect all occurrences during that time. Then, fire the output Event with the collected output.

throttle :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a) Source #

Throttle an input event, ensuring that at least a given amount of time passes between occurrences of the output event. If the input event occurs too frequently, the output event occurs with the most recently seen input value after the given delay passes since the last occurrence of the output. If the output event has not occurred recently, occurrences of the input event will cause the output event to fire immediately.

data ThrottleState b Source #

Instances
Functor ThrottleState Source # 
Instance details

Defined in Reflex.Time

Methods

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

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

Foldable ThrottleState Source # 
Instance details

Defined in Reflex.Time

Methods

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

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

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

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

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

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

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

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

toList :: ThrottleState a -> [a] #

null :: ThrottleState a -> Bool #

length :: ThrottleState a -> Int #

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

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

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

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

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

Traversable ThrottleState Source # 
Instance details

Defined in Reflex.Time

Methods

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

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

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

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

Eq b => Eq (ThrottleState b) Source # 
Instance details

Defined in Reflex.Time

Data b => Data (ThrottleState b) Source # 
Instance details

Defined in Reflex.Time

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> ThrottleState b -> c (ThrottleState b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ThrottleState b) #

toConstr :: ThrottleState b -> Constr #

dataTypeOf :: ThrottleState b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ThrottleState b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ThrottleState b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> ThrottleState b -> ThrottleState b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThrottleState b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThrottleState b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThrottleState b -> m (ThrottleState b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThrottleState b -> m (ThrottleState b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThrottleState b -> m (ThrottleState b) #

Ord b => Ord (ThrottleState b) Source # 
Instance details

Defined in Reflex.Time

Show b => Show (ThrottleState b) Source # 
Instance details

Defined in Reflex.Time

Generic (ThrottleState b) Source # 
Instance details

Defined in Reflex.Time

Associated Types

type Rep (ThrottleState b) :: Type -> Type #

type Rep (ThrottleState b) Source # 
Instance details

Defined in Reflex.Time

type Rep (ThrottleState b) = D1 (MetaData "ThrottleState" "Reflex.Time" "reflex-0.6.4.1-BXfMCqc8R3bEOzORITL7qe" False) (C1 (MetaCons "ThrottleState_Immediate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ThrottleState_Buffered" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ThrottleBuffer b))))

data ThrottleBuffer b Source #

Instances
Functor ThrottleBuffer Source # 
Instance details

Defined in Reflex.Time

Methods

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

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

Foldable ThrottleBuffer Source # 
Instance details

Defined in Reflex.Time

Methods

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

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

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

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

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

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

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

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

toList :: ThrottleBuffer a -> [a] #

null :: ThrottleBuffer a -> Bool #

length :: ThrottleBuffer a -> Int #

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

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

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

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

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

Traversable ThrottleBuffer Source # 
Instance details

Defined in Reflex.Time

Methods

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

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

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

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

Eq b => Eq (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

Data b => Data (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> ThrottleBuffer b -> c (ThrottleBuffer b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ThrottleBuffer b) #

toConstr :: ThrottleBuffer b -> Constr #

dataTypeOf :: ThrottleBuffer b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ThrottleBuffer b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ThrottleBuffer b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> ThrottleBuffer b -> ThrottleBuffer b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThrottleBuffer b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThrottleBuffer b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThrottleBuffer b -> m (ThrottleBuffer b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThrottleBuffer b -> m (ThrottleBuffer b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThrottleBuffer b -> m (ThrottleBuffer b) #

Ord b => Ord (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

Show b => Show (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

Generic (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

Associated Types

type Rep (ThrottleBuffer b) :: Type -> Type #

Semigroup b => Semigroup (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

Semigroup b => Monoid (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

type Rep (ThrottleBuffer b) Source # 
Instance details

Defined in Reflex.Time

type Rep (ThrottleBuffer b) = D1 (MetaData "ThrottleBuffer" "Reflex.Time" "reflex-0.6.4.1-BXfMCqc8R3bEOzORITL7qe" False) (C1 (MetaCons "ThrottleBuffer_Empty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ThrottleBuffer_Full" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)))

throttleBatchWithLag :: (MonadFix m, MonadHold t m, PerformEvent t m, Semigroup a) => (Event t () -> m (Event t ())) -> Event t a -> m (Event t a) Source #

Throttle an input event, ensuring that the output event doesn't occur more often than you are ready for it. If the input event occurs too frequently, the output event will contain semigroup-based summaries of the input firings that happened since the last output firing. If the output event has not occurred recently, occurrences of the input event will cause the output event to fire immediately. The first parameter is a function that receives access to the output event, and should construct an event that fires when the receiver is ready for more input. For example, using delay 20 would give a simple time-based throttle.

NB: The provided lag function must *actually* delay the event.

Immediate mode must turn off whenever output is produced.

Output must be produced whenever immediate mode turns from on to off.

Immediate mode can only go from off to on when the delayed event fires.

Every input firing must go into either an immediate output firing or the

An existing full buffer must either stay in the buffer or go to output,