{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
#ifdef USE_TEMPLATE_HASKELL
{-# LANGUAGE TemplateHaskell #-}
#endif
-- |
-- Module:
--   Reflex.Time
-- Description:
--   Clocks, timers, and other time-related functions.
module Reflex.Time where

import Reflex.Class
import Reflex.Dynamic
import Reflex.PerformEvent.Class
import Reflex.PostBuild.Class
import Reflex.TriggerEvent.Class

import Control.Concurrent
import qualified Control.Concurrent.Thread.Delay as Concurrent
import Control.Lens hiding ((|>))
import Control.Monad
import Control.Monad.Fix
import Control.Monad.IO.Class
import Data.Align
import Data.Data (Data)
import Data.Fixed
import Data.Semigroup (Semigroup(..))
import Data.Sequence (Seq, (|>))
import qualified Data.Sequence as Seq
import Data.These
import Data.Time.Clock
import Data.Typeable
import GHC.Generics (Generic)
import System.Random

-- | Metadata associated with a timer "tick"
data TickInfo
  = TickInfo { TickInfo -> UTCTime
_tickInfo_lastUTC :: UTCTime
             -- ^ UTC time immediately after the last tick.
             , TickInfo -> Integer
_tickInfo_n :: Integer
             -- ^ Number of time periods or ticks since the start of the timer
             , TickInfo -> NominalDiffTime
_tickInfo_alreadyElapsed :: NominalDiffTime
             -- ^ Amount of time that has elapsed in the current tick period.
             }
  deriving (TickInfo -> TickInfo -> Bool
(TickInfo -> TickInfo -> Bool)
-> (TickInfo -> TickInfo -> Bool) -> Eq TickInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TickInfo -> TickInfo -> Bool
== :: TickInfo -> TickInfo -> Bool
$c/= :: TickInfo -> TickInfo -> Bool
/= :: TickInfo -> TickInfo -> Bool
Eq, Eq TickInfo
Eq TickInfo
-> (TickInfo -> TickInfo -> Ordering)
-> (TickInfo -> TickInfo -> Bool)
-> (TickInfo -> TickInfo -> Bool)
-> (TickInfo -> TickInfo -> Bool)
-> (TickInfo -> TickInfo -> Bool)
-> (TickInfo -> TickInfo -> TickInfo)
-> (TickInfo -> TickInfo -> TickInfo)
-> Ord TickInfo
TickInfo -> TickInfo -> Bool
TickInfo -> TickInfo -> Ordering
TickInfo -> TickInfo -> TickInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TickInfo -> TickInfo -> Ordering
compare :: TickInfo -> TickInfo -> Ordering
$c< :: TickInfo -> TickInfo -> Bool
< :: TickInfo -> TickInfo -> Bool
$c<= :: TickInfo -> TickInfo -> Bool
<= :: TickInfo -> TickInfo -> Bool
$c> :: TickInfo -> TickInfo -> Bool
> :: TickInfo -> TickInfo -> Bool
$c>= :: TickInfo -> TickInfo -> Bool
>= :: TickInfo -> TickInfo -> Bool
$cmax :: TickInfo -> TickInfo -> TickInfo
max :: TickInfo -> TickInfo -> TickInfo
$cmin :: TickInfo -> TickInfo -> TickInfo
min :: TickInfo -> TickInfo -> TickInfo
Ord, Int -> TickInfo -> ShowS
[TickInfo] -> ShowS
TickInfo -> String
(Int -> TickInfo -> ShowS)
-> (TickInfo -> String) -> ([TickInfo] -> ShowS) -> Show TickInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TickInfo -> ShowS
showsPrec :: Int -> TickInfo -> ShowS
$cshow :: TickInfo -> String
show :: TickInfo -> String
$cshowList :: [TickInfo] -> ShowS
showList :: [TickInfo] -> ShowS
Show, Typeable)

-- | 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.
tickLossy :: (PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) => NominalDiffTime -> UTCTime -> m (Event t TickInfo)
tickLossy :: forall t (m :: * -> *).
(PostBuild t m, PerformEvent t m, TriggerEvent t m,
 MonadIO (Performable m), MonadFix m) =>
NominalDiffTime -> UTCTime -> m (Event t TickInfo)
tickLossy NominalDiffTime
dt UTCTime
t0 = NominalDiffTime -> UTCTime -> Event t () -> m (Event t TickInfo)
forall t (m :: * -> *) a.
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m),
 MonadFix m) =>
NominalDiffTime -> UTCTime -> Event t a -> m (Event t TickInfo)
tickLossyFrom NominalDiffTime
dt UTCTime
t0 (Event t () -> m (Event t TickInfo))
-> m (Event t ()) -> m (Event t TickInfo)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m (Event t ())
forall t (m :: * -> *). PostBuild t m => m (Event t ())
getPostBuild

-- | 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.
tickLossyFromPostBuildTime :: (PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) => NominalDiffTime -> m (Event t TickInfo)
tickLossyFromPostBuildTime :: forall t (m :: * -> *).
(PostBuild t m, PerformEvent t m, TriggerEvent t m,
 MonadIO (Performable m), MonadFix m) =>
NominalDiffTime -> m (Event t TickInfo)
tickLossyFromPostBuildTime NominalDiffTime
dt = do
  Event t ()
postBuild <- m (Event t ())
forall t (m :: * -> *). PostBuild t m => m (Event t ())
getPostBuild
  Event t UTCTime
postBuildTime <- Event t (Performable m UTCTime) -> m (Event t UTCTime)
forall a. Event t (Performable m a) -> m (Event t a)
forall t (m :: * -> *) a.
PerformEvent t m =>
Event t (Performable m a) -> m (Event t a)
performEvent (Event t (Performable m UTCTime) -> m (Event t UTCTime))
-> Event t (Performable m UTCTime) -> m (Event t UTCTime)
forall a b. (a -> b) -> a -> b
$ IO UTCTime -> Performable m UTCTime
forall a. IO a -> Performable m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UTCTime
getCurrentTime Performable m UTCTime
-> Event t () -> Event t (Performable m UTCTime)
forall a b. a -> Event t b -> Event t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Event t ()
postBuild
  Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo)
forall t (m :: * -> *).
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m),
 MonadFix m) =>
Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo)
tickLossyFrom' (Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo))
-> Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo)
forall a b. (a -> b) -> a -> b
$ (NominalDiffTime
dt,) (UTCTime -> (NominalDiffTime, UTCTime))
-> Event t UTCTime -> Event t (NominalDiffTime, UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event t UTCTime
postBuildTime

-- | 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
    :: (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)
tickLossyFrom :: forall t (m :: * -> *) a.
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m),
 MonadFix m) =>
NominalDiffTime -> UTCTime -> Event t a -> m (Event t TickInfo)
tickLossyFrom NominalDiffTime
dt UTCTime
t0 Event t a
e = Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo)
forall t (m :: * -> *).
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m),
 MonadFix m) =>
Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo)
tickLossyFrom' (Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo))
-> Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo)
forall a b. (a -> b) -> a -> b
$ (NominalDiffTime
dt, UTCTime
t0) (NominalDiffTime, UTCTime)
-> Event t a -> Event t (NominalDiffTime, UTCTime)
forall a b. a -> Event t b -> Event t a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Event t a
e

-- | Generalization of tickLossyFrom that takes the delay and initial time as an 'Event'.
tickLossyFrom'
    :: (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)
tickLossyFrom' :: forall t (m :: * -> *).
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m),
 MonadFix m) =>
Event t (NominalDiffTime, UTCTime) -> m (Event t TickInfo)
tickLossyFrom' Event t (NominalDiffTime, UTCTime)
e = do
  rec Event t (TickInfo, (NominalDiffTime, UTCTime))
result <- Event
  t
  (((TickInfo, (NominalDiffTime, UTCTime)) -> IO ())
   -> Performable m ())
-> m (Event t (TickInfo, (NominalDiffTime, UTCTime)))
forall t (m :: * -> *) a.
(TriggerEvent t m, PerformEvent t m) =>
Event t ((a -> IO ()) -> Performable m ()) -> m (Event t a)
performEventAsync (Event
   t
   (((TickInfo, (NominalDiffTime, UTCTime)) -> IO ())
    -> Performable m ())
 -> m (Event t (TickInfo, (NominalDiffTime, UTCTime))))
-> Event
     t
     (((TickInfo, (NominalDiffTime, UTCTime)) -> IO ())
      -> Performable m ())
-> m (Event t (TickInfo, (NominalDiffTime, UTCTime)))
forall a b. (a -> b) -> a -> b
$ (NominalDiffTime, UTCTime)
-> ((TickInfo, (NominalDiffTime, UTCTime)) -> IO ())
-> Performable m ()
forall {f :: * -> *}.
MonadIO f =>
(NominalDiffTime, UTCTime)
-> ((TickInfo, (NominalDiffTime, UTCTime)) -> IO ()) -> f ()
callAtNextInterval ((NominalDiffTime, UTCTime)
 -> ((TickInfo, (NominalDiffTime, UTCTime)) -> IO ())
 -> Performable m ())
-> Event t (NominalDiffTime, UTCTime)
-> Event
     t
     (((TickInfo, (NominalDiffTime, UTCTime)) -> IO ())
      -> Performable m ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Event t (NominalDiffTime, UTCTime)]
-> Event t (NominalDiffTime, UTCTime)
forall {k} (t :: k) a. Reflex t => [Event t a] -> Event t a
leftmost [Event t (NominalDiffTime, UTCTime)
e, (TickInfo, (NominalDiffTime, UTCTime))
-> (NominalDiffTime, UTCTime)
forall a b. (a, b) -> b
snd ((TickInfo, (NominalDiffTime, UTCTime))
 -> (NominalDiffTime, UTCTime))
-> Event t (TickInfo, (NominalDiffTime, UTCTime))
-> Event t (NominalDiffTime, UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event t (TickInfo, (NominalDiffTime, UTCTime))
result]
  Event t TickInfo -> m (Event t TickInfo)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Event t TickInfo -> m (Event t TickInfo))
-> Event t TickInfo -> m (Event t TickInfo)
forall a b. (a -> b) -> a -> b
$ (TickInfo, (NominalDiffTime, UTCTime)) -> TickInfo
forall a b. (a, b) -> a
fst ((TickInfo, (NominalDiffTime, UTCTime)) -> TickInfo)
-> Event t (TickInfo, (NominalDiffTime, UTCTime))
-> Event t TickInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Event t (TickInfo, (NominalDiffTime, UTCTime))
result
  where callAtNextInterval :: (NominalDiffTime, UTCTime)
-> ((TickInfo, (NominalDiffTime, UTCTime)) -> IO ()) -> f ()
callAtNextInterval (NominalDiffTime, UTCTime)
pair (TickInfo, (NominalDiffTime, UTCTime)) -> IO ()
cb = f ThreadId -> f ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (f ThreadId -> f ()) -> f ThreadId -> f ()
forall a b. (a -> b) -> a -> b
$ IO ThreadId -> f ThreadId
forall a. IO a -> f a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThreadId -> f ThreadId) -> IO ThreadId -> f ThreadId
forall a b. (a -> b) -> a -> b
$ IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ do
          TickInfo
tick <- (NominalDiffTime -> UTCTime -> IO TickInfo)
-> (NominalDiffTime, UTCTime) -> IO TickInfo
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry NominalDiffTime -> UTCTime -> IO TickInfo
getCurrentTick (NominalDiffTime, UTCTime)
pair
          Integer -> IO ()
Concurrent.delay (Integer -> IO ()) -> Integer -> IO ()
forall a b. (a -> b) -> a -> b
$ NominalDiffTime -> Integer
forall b. Integral b => NominalDiffTime -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (NominalDiffTime -> Integer) -> NominalDiffTime -> Integer
forall a b. (a -> b) -> a -> b
$ ((NominalDiffTime, UTCTime) -> NominalDiffTime
forall a b. (a, b) -> a
fst (NominalDiffTime, UTCTime)
pair NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall a. Num a => a -> a -> a
- TickInfo -> NominalDiffTime
_tickInfo_alreadyElapsed TickInfo
tick) NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall a. Num a => a -> a -> a
* NominalDiffTime
1000000
          (TickInfo, (NominalDiffTime, UTCTime)) -> IO ()
cb (TickInfo
tick, (NominalDiffTime, UTCTime)
pair)

-- | Like 'tickLossy', but immediately calculates the first tick and provides a 'Dynamic' that is updated as ticks fire.
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)
clockLossy :: forall (m :: * -> *) t.
(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)
clockLossy NominalDiffTime
dt UTCTime
t0 = do
  TickInfo
initial <- IO TickInfo -> m TickInfo
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TickInfo -> m TickInfo) -> IO TickInfo -> m TickInfo
forall a b. (a -> b) -> a -> b
$ NominalDiffTime -> UTCTime -> IO TickInfo
getCurrentTick NominalDiffTime
dt UTCTime
t0
  Event t TickInfo
e <- NominalDiffTime -> UTCTime -> m (Event t TickInfo)
forall t (m :: * -> *).
(PostBuild t m, PerformEvent t m, TriggerEvent t m,
 MonadIO (Performable m), MonadFix m) =>
NominalDiffTime -> UTCTime -> m (Event t TickInfo)
tickLossy NominalDiffTime
dt UTCTime
t0
  TickInfo -> Event t TickInfo -> m (Dynamic t TickInfo)
forall a. a -> Event t a -> m (Dynamic t a)
forall {k} (t :: k) (m :: * -> *) a.
MonadHold t m =>
a -> Event t a -> m (Dynamic t a)
holdDyn TickInfo
initial Event t TickInfo
e

-- | 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.
getCurrentTick :: NominalDiffTime -> UTCTime -> IO TickInfo
getCurrentTick :: NominalDiffTime -> UTCTime -> IO TickInfo
getCurrentTick NominalDiffTime
dt UTCTime
t0 = do
  UTCTime
t <- IO UTCTime
getCurrentTime
  let offset :: NominalDiffTime
offset = UTCTime
t UTCTime -> UTCTime -> NominalDiffTime
`diffUTCTime` UTCTime
t0
      (Integer
n, NominalDiffTime
alreadyElapsed) = NominalDiffTime
offset NominalDiffTime -> NominalDiffTime -> (Integer, NominalDiffTime)
forall a b. (Real a, Integral b) => a -> a -> (b, a)
`divMod'` NominalDiffTime
dt
  TickInfo -> IO TickInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TickInfo -> IO TickInfo) -> TickInfo -> IO TickInfo
forall a b. (a -> b) -> a -> b
$ UTCTime -> Integer -> NominalDiffTime -> TickInfo
TickInfo UTCTime
t Integer
n NominalDiffTime
alreadyElapsed

-- | Delay an Event's occurrences by a given amount in seconds.
delay :: (PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a)
delay :: forall t (m :: * -> *) a.
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) =>
NominalDiffTime -> Event t a -> m (Event t a)
delay NominalDiffTime
dt Event t a
e = Event t ((a -> IO ()) -> Performable m ()) -> m (Event t a)
forall t (m :: * -> *) a.
(TriggerEvent t m, PerformEvent t m) =>
Event t ((a -> IO ()) -> Performable m ()) -> m (Event t a)
performEventAsync (Event t ((a -> IO ()) -> Performable m ()) -> m (Event t a))
-> Event t ((a -> IO ()) -> Performable m ()) -> m (Event t a)
forall a b. (a -> b) -> a -> b
$ Event t a
-> (a -> (a -> IO ()) -> Performable m ())
-> Event t ((a -> IO ()) -> Performable m ())
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
ffor Event t a
e ((a -> (a -> IO ()) -> Performable m ())
 -> Event t ((a -> IO ()) -> Performable m ()))
-> (a -> (a -> IO ()) -> Performable m ())
-> Event t ((a -> IO ()) -> Performable m ())
forall a b. (a -> b) -> a -> b
$ \a
a a -> IO ()
cb -> IO () -> Performable m ()
forall a. IO a -> Performable m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Performable m ()) -> IO () -> Performable m ()
forall a b. (a -> b) -> a -> b
$ IO ThreadId -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO ThreadId -> IO ()) -> IO ThreadId -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ do
  Integer -> IO ()
Concurrent.delay (Integer -> IO ()) -> Integer -> IO ()
forall a b. (a -> b) -> a -> b
$ NominalDiffTime -> Integer
forall b. Integral b => NominalDiffTime -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (NominalDiffTime -> Integer) -> NominalDiffTime -> Integer
forall a b. (a -> b) -> a -> b
$ NominalDiffTime
dt NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall a. Num a => a -> a -> a
* NominalDiffTime
1000000
  a -> IO ()
cb a
a

-- | 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
poissonLossyFrom
  :: (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)
poissonLossyFrom :: forall g (m :: * -> *) t a.
(RandomGen g, MonadIO (Performable m), PerformEvent t m,
 TriggerEvent t m) =>
g -> Double -> UTCTime -> Event t a -> m (Event t TickInfo)
poissonLossyFrom g
rnd Double
rate = g
-> Behavior t Double
-> Double
-> UTCTime
-> Event t a
-> m (Event t TickInfo)
forall g (m :: * -> *) t a.
(RandomGen g, MonadIO (Performable m), PerformEvent t m,
 TriggerEvent t m) =>
g
-> Behavior t Double
-> Double
-> UTCTime
-> Event t a
-> m (Event t TickInfo)
inhomogeneousPoissonFrom g
rnd (Double -> Behavior t Double
forall a. a -> Behavior t a
forall {k} (t :: k) a. Reflex t => a -> Behavior t a
constant Double
rate) Double
rate


-- | 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
poissonLossy
  :: (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)
poissonLossy :: forall g (m :: * -> *) t.
(RandomGen g, MonadIO (Performable m), PerformEvent t m,
 TriggerEvent t m, PostBuild t m) =>
g -> Double -> UTCTime -> m (Event t TickInfo)
poissonLossy g
rnd Double
rate UTCTime
t0 = g -> Double -> UTCTime -> Event t () -> m (Event t TickInfo)
forall g (m :: * -> *) t a.
(RandomGen g, MonadIO (Performable m), PerformEvent t m,
 TriggerEvent t m) =>
g -> Double -> UTCTime -> Event t a -> m (Event t TickInfo)
poissonLossyFrom g
rnd Double
rate UTCTime
t0 (Event t () -> m (Event t TickInfo))
-> m (Event t ()) -> m (Event t TickInfo)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m (Event t ())
forall t (m :: * -> *). PostBuild t m => m (Event t ())
getPostBuild

-- | Send events with inhomogeneous Poisson timing with the given basis
--   and variable rate. Provide a maxRate that you expect to support.
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)
inhomogeneousPoissonFrom :: forall g (m :: * -> *) t a.
(RandomGen g, MonadIO (Performable m), PerformEvent t m,
 TriggerEvent t m) =>
g
-> Behavior t Double
-> Double
-> UTCTime
-> Event t a
-> m (Event t TickInfo)
inhomogeneousPoissonFrom g
rnd Behavior t Double
rate Double
maxRate UTCTime
t0 Event t a
e = do

  -- Create a thread for producing homogeneous poisson events
  -- along with random Doubles (usage of Double's explained below)
  Event t (TickInfo, Double)
ticksWithRateRand <- Event t (((TickInfo, Double) -> IO ()) -> Performable m ())
-> m (Event t (TickInfo, Double))
forall t (m :: * -> *) a.
(TriggerEvent t m, PerformEvent t m) =>
Event t ((a -> IO ()) -> Performable m ()) -> m (Event t a)
performEventAsync (Event t (((TickInfo, Double) -> IO ()) -> Performable m ())
 -> m (Event t (TickInfo, Double)))
-> Event t (((TickInfo, Double) -> IO ()) -> Performable m ())
-> m (Event t (TickInfo, Double))
forall a b. (a -> b) -> a -> b
$
                       (a -> ((TickInfo, Double) -> IO ()) -> Performable m ())
-> Event t a
-> Event t (((TickInfo, Double) -> IO ()) -> Performable m ())
forall a b. (a -> b) -> Event t a -> Event t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> ((TickInfo, Double) -> IO ()) -> Performable m ()
callAtNextInterval Event t a
e

  -- Filter homogeneous events according to associated
  -- random values and the current rate parameter
  Event t TickInfo -> m (Event t TickInfo)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Event t TickInfo -> m (Event t TickInfo))
-> Event t TickInfo -> m (Event t TickInfo)
forall a b. (a -> b) -> a -> b
$ (Double -> (TickInfo, Double) -> Maybe TickInfo)
-> Behavior t Double
-> Event t (TickInfo, Double)
-> Event t TickInfo
forall {k} (t :: k) a b c.
Reflex t =>
(a -> b -> Maybe c) -> Behavior t a -> Event t b -> Event t c
attachWithMaybe Double -> (TickInfo, Double) -> Maybe TickInfo
filterFun Behavior t Double
rate Event t (TickInfo, Double)
ticksWithRateRand

  where

    -- Inhomogeneous poisson processes are built from faster
    -- homogeneous ones by randomly dropping events from the
    -- fast process. For each fast homogeneous event, choose
    -- a uniform random sample from (0, rMax). If the
    -- inhomogeneous rate at this moment is greater than the
    -- random sample, then keep this event, otherwise drop it
    filterFun :: Double -> (TickInfo, Double) -> Maybe TickInfo
    filterFun :: Double -> (TickInfo, Double) -> Maybe TickInfo
filterFun Double
r (TickInfo
tInfo, Double
p)
      | Double
r Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
p    = TickInfo -> Maybe TickInfo
forall a. a -> Maybe a
Just TickInfo
tInfo
      | Bool
otherwise = Maybe TickInfo
forall a. Maybe a
Nothing

    callAtNextInterval :: a -> ((TickInfo, Double) -> IO ()) -> Performable m ()
callAtNextInterval a
_ (TickInfo, Double) -> IO ()
cb = Performable m ThreadId -> Performable m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Performable m ThreadId -> Performable m ())
-> Performable m ThreadId -> Performable m ()
forall a b. (a -> b) -> a -> b
$ IO ThreadId -> Performable m ThreadId
forall a. IO a -> Performable m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThreadId -> Performable m ThreadId)
-> IO ThreadId -> Performable m ThreadId
forall a b. (a -> b) -> a -> b
$ IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ UTCTime -> g -> ((TickInfo, Double) -> IO ()) -> Integer -> IO ()
go UTCTime
t0 g
rnd (TickInfo, Double) -> IO ()
cb Integer
0

    go :: UTCTime -> g -> ((TickInfo, Double) -> IO ()) -> Integer -> IO ()
go UTCTime
tTargetLast g
lastGen (TickInfo, Double) -> IO ()
cb Integer
lastN = do
      UTCTime
t <- IO UTCTime
getCurrentTime

      -- Generate random numbers for this poisson interval (u)
      -- and sample-retention likelihood (p)
      let (Double
u, g
nextGen)            = (Double, Double) -> g -> (Double, g)
forall g. RandomGen g => (Double, Double) -> g -> (Double, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (Double
0,Double
1) g
lastGen
          (Double
p :: Double, g
nextGen') = (Double, Double) -> g -> (Double, g)
forall g. RandomGen g => (Double, Double) -> g -> (Double, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (Double
0,Double
maxRate) g
nextGen

      -- Inter-event interval is drawn from exponential
      -- distribution accourding to u
      let dt :: NominalDiffTime
dt             = Double -> NominalDiffTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double -> NominalDiffTime) -> Double -> NominalDiffTime
forall a b. (a -> b) -> a -> b
$ (-Double
1) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
forall a. Floating a => a -> a
log Double
u Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
maxRate :: NominalDiffTime
          nEvents :: Integer
nEvents        = Integer
lastN Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
          alreadyElapsed :: NominalDiffTime
alreadyElapsed = UTCTime -> UTCTime -> NominalDiffTime
diffUTCTime UTCTime
t UTCTime
tTargetLast
          tTarget :: UTCTime
tTarget        = NominalDiffTime -> UTCTime -> UTCTime
addUTCTime NominalDiffTime
dt UTCTime
tTargetLast
          thisDelay :: Double
thisDelay      = NominalDiffTime -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (NominalDiffTime -> Double) -> NominalDiffTime -> Double
forall a b. (a -> b) -> a -> b
$ UTCTime -> UTCTime -> NominalDiffTime
diffUTCTime UTCTime
tTarget UTCTime
t :: Double
      Integer -> IO ()
Concurrent.delay (Integer -> IO ()) -> Integer -> IO ()
forall a b. (a -> b) -> a -> b
$ Double -> Integer
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Double -> Integer) -> Double -> Integer
forall a b. (a -> b) -> a -> b
$ Double
thisDelay Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000000
      ()
_ <- (TickInfo, Double) -> IO ()
cb (UTCTime -> Integer -> NominalDiffTime -> TickInfo
TickInfo UTCTime
t Integer
nEvents NominalDiffTime
alreadyElapsed, Double
p)
      UTCTime -> g -> ((TickInfo, Double) -> IO ()) -> Integer -> IO ()
go UTCTime
tTarget g
nextGen' (TickInfo, Double) -> IO ()
cb Integer
nEvents

-- | 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)
inhomogeneousPoisson :: forall g (m :: * -> *) t.
(RandomGen g, MonadIO (Performable m), PerformEvent t m,
 TriggerEvent t m, PostBuild t m) =>
g -> Behavior t Double -> Double -> UTCTime -> m (Event t TickInfo)
inhomogeneousPoisson g
rnd Behavior t Double
rate Double
maxRate UTCTime
t0 =
  g
-> Behavior t Double
-> Double
-> UTCTime
-> Event t ()
-> m (Event t TickInfo)
forall g (m :: * -> *) t a.
(RandomGen g, MonadIO (Performable m), PerformEvent t m,
 TriggerEvent t m) =>
g
-> Behavior t Double
-> Double
-> UTCTime
-> Event t a
-> m (Event t TickInfo)
inhomogeneousPoissonFrom g
rnd Behavior t Double
rate Double
maxRate UTCTime
t0 (Event t () -> m (Event t TickInfo))
-> m (Event t ()) -> m (Event t TickInfo)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m (Event t ())
forall t (m :: * -> *). PostBuild t m => m (Event t ())
getPostBuild

-- | 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.
debounce :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a)
debounce :: forall (m :: * -> *) t a.
(MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m,
 MonadIO (Performable m)) =>
NominalDiffTime -> Event t a -> m (Event t a)
debounce NominalDiffTime
dt Event t a
e = do
  Dynamic t Integer
n :: Dynamic t Integer <- Event t a -> m (Dynamic t Integer)
forall {k} (t :: k) (m :: * -> *) b a.
(Reflex t, MonadHold t m, MonadFix m, Num b) =>
Event t a -> m (Dynamic t b)
count Event t a
e
  let tagged :: Event t (Integer, a)
tagged = (Integer -> a -> (Integer, a))
-> Dynamic t Integer -> Event t a -> Event t (Integer, a)
forall {k} (t :: k) a b c.
Reflex t =>
(a -> b -> c) -> Dynamic t a -> Event t b -> Event t c
attachPromptlyDynWith (,) Dynamic t Integer
n Event t a
e
  Event t (Integer, a)
delayed <- NominalDiffTime -> Event t (Integer, a) -> m (Event t (Integer, a))
forall t (m :: * -> *) a.
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) =>
NominalDiffTime -> Event t a -> m (Event t a)
delay NominalDiffTime
dt Event t (Integer, a)
tagged
  Event t a -> m (Event t a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Event t a -> m (Event t a)) -> Event t a -> m (Event t a)
forall a b. (a -> b) -> a -> b
$ (Integer -> (Integer, a) -> Maybe a)
-> Behavior t Integer -> Event t (Integer, a) -> Event t a
forall {k} (t :: k) a b c.
Reflex t =>
(a -> b -> Maybe c) -> Behavior t a -> Event t b -> Event t c
attachWithMaybe (\Integer
n' (Integer
t, a
v) -> if Integer
n' Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
t then a -> Maybe a
forall a. a -> Maybe a
Just a
v else Maybe a
forall a. Maybe a
Nothing) (Dynamic t Integer -> Behavior t Integer
forall a. Dynamic t a -> Behavior t a
forall {k} (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current Dynamic t Integer
n) Event t (Integer, a)
delayed

-- | 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.
batchOccurrences :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t (Seq a))
batchOccurrences :: forall (m :: * -> *) t a.
(MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m,
 MonadIO (Performable m)) =>
NominalDiffTime -> Event t a -> m (Event t (Seq a))
batchOccurrences NominalDiffTime
t Event t a
newValues = do
  let f :: Seq a -> These a b -> (Maybe (Seq a), Maybe ())
f Seq a
s These a b
x = (Seq a -> Maybe (Seq a)
forall a. a -> Maybe a
Just Seq a
newState, Maybe ()
out)
        where newState :: Seq a
newState = case These a b
x of
                This a
a -> Seq a
s Seq a -> a -> Seq a
forall a. Seq a -> a -> Seq a
|> a
a
                That b
_ -> Seq a
forall a. Monoid a => a
mempty
                These a
a b
_ -> a -> Seq a
forall a. a -> Seq a
Seq.singleton a
a
              out :: Maybe ()
out = case These a b
x of
                This a
_ -> if Seq a -> Bool
forall a. Seq a -> Bool
Seq.null Seq a
s then () -> Maybe ()
forall a. a -> Maybe a
Just () else Maybe ()
forall a. Maybe a
Nothing
                That b
_ -> Maybe ()
forall a. Maybe a
Nothing
                These a
_ b
_ -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
  rec (Behavior t (Seq a)
buffer, Event t ()
toDelay) <- (Seq a -> These a () -> (Maybe (Seq a), Maybe ()))
-> Seq a
-> Event t (These a ())
-> m (Behavior t (Seq a), Event t ())
forall {k} (t :: k) (f :: * -> *) (m :: * -> *) a b c.
(Accumulator t f, MonadHold t m, MonadFix m) =>
(a -> b -> (Maybe a, Maybe c))
-> a -> Event t b -> m (f a, Event t c)
forall (m :: * -> *) a b c.
(MonadHold t m, MonadFix m) =>
(a -> b -> (Maybe a, Maybe c))
-> a -> Event t b -> m (Behavior t a, Event t c)
mapAccumMaybe Seq a -> These a () -> (Maybe (Seq a), Maybe ())
forall {a} {b}. Seq a -> These a b -> (Maybe (Seq a), Maybe ())
f Seq a
forall a. Monoid a => a
mempty (Event t (These a ()) -> m (Behavior t (Seq a), Event t ()))
-> Event t (These a ()) -> m (Behavior t (Seq a), Event t ())
forall a b. (a -> b) -> a -> b
$ Event t a -> Event t () -> Event t (These a ())
forall a b. Event t a -> Event t b -> Event t (These a b)
forall (f :: * -> *) a b.
Semialign f =>
f a -> f b -> f (These a b)
align Event t a
newValues Event t ()
delayed
      Event t ()
delayed <- NominalDiffTime -> Event t () -> m (Event t ())
forall t (m :: * -> *) a.
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) =>
NominalDiffTime -> Event t a -> m (Event t a)
delay NominalDiffTime
t Event t ()
toDelay
  Event t (Seq a) -> m (Event t (Seq a))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Event t (Seq a) -> m (Event t (Seq a)))
-> Event t (Seq a) -> m (Event t (Seq a))
forall a b. (a -> b) -> a -> b
$ Behavior t (Seq a) -> Event t () -> Event t (Seq a)
forall {k} (t :: k) b a.
Reflex t =>
Behavior t b -> Event t a -> Event t b
tag Behavior t (Seq a)
buffer Event t ()
delayed

-- | 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.
throttle :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a)
throttle :: forall (m :: * -> *) t a.
(MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m,
 MonadIO (Performable m)) =>
NominalDiffTime -> Event t a -> m (Event t a)
throttle NominalDiffTime
t Event t a
e = do
  let f :: (Bool, Maybe a) -> These a b -> (Maybe (Bool, Maybe a), Maybe a)
f (Bool
immediate, Maybe a
buffer) These a b
x = case These a b
x of -- (Just newState, out)
        This a
a -- If only the input event fires
          | Bool
immediate -> -- and we're in immediate mode
            -- Immediate mode turns off, and the buffer is empty.
            -- We fire the output event with the input event value immediately.
            ((Bool, Maybe a) -> Maybe (Bool, Maybe a)
forall a. a -> Maybe a
Just (Bool
False, Maybe a
forall a. Maybe a
Nothing), a -> Maybe a
forall a. a -> Maybe a
Just a
a)
          | Bool
otherwise -> -- and we're not in immediate mode
            -- Immediate mode remains off, and we replace the contents of the buffer (if any) with the input value.
            -- We don't fire the output event.
            ((Bool, Maybe a) -> Maybe (Bool, Maybe a)
forall a. a -> Maybe a
Just (Bool
False, a -> Maybe a
forall a. a -> Maybe a
Just a
a), Maybe a
forall a. Maybe a
Nothing)
        That b
_ -> -- If only the delayed output event fires,
          case Maybe a
buffer of
            Maybe a
Nothing -> -- and the buffer is empty:
              -- Immediate mode turns back on, and the buffer remains empty.
              -- We don't fire.
              ((Bool, Maybe a) -> Maybe (Bool, Maybe a)
forall a. a -> Maybe a
Just (Bool
True, Maybe a
forall a. Maybe a
Nothing), Maybe a
forall a. Maybe a
Nothing)
            Just a
b -> -- and the buffer is full:
              -- Immediate mode remains off, and the buffer is cleared.
              -- We fire with the buffered value.
              ((Bool, Maybe a) -> Maybe (Bool, Maybe a)
forall a. a -> Maybe a
Just (Bool
False, Maybe a
forall a. Maybe a
Nothing), a -> Maybe a
forall a. a -> Maybe a
Just a
b)
        These a
a b
_ -> -- If both the input and delayed output event fire simultaneously:
          -- Immediate mode turns off, and the buffer is empty.
          -- We fire with the input event's value, as it is the most recent we have seen at this moment.
          ((Bool, Maybe a) -> Maybe (Bool, Maybe a)
forall a. a -> Maybe a
Just (Bool
False, Maybe a
forall a. Maybe a
Nothing), a -> Maybe a
forall a. a -> Maybe a
Just a
a)
  rec (Dynamic t (Bool, Maybe a)
_, Event t a
outE) <- ((Bool, Maybe a) -> These a a -> (Maybe (Bool, Maybe a), Maybe a))
-> (Bool, Maybe a)
-> Event t (These a a)
-> m (Dynamic t (Bool, Maybe a), Event t a)
forall {k} (t :: k) (m :: * -> *) a b c.
(Reflex t, MonadHold t m, MonadFix m) =>
(a -> b -> (Maybe a, Maybe c))
-> a -> Event t b -> m (Dynamic t a, Event t c)
mapAccumMaybeDyn (Bool, Maybe a) -> These a a -> (Maybe (Bool, Maybe a), Maybe a)
forall {a} {b}.
(Bool, Maybe a) -> These a b -> (Maybe (Bool, Maybe a), Maybe a)
f (Bool
True, Maybe a
forall a. Maybe a
Nothing) (Event t (These a a) -> m (Dynamic t (Bool, Maybe a), Event t a))
-> Event t (These a a) -> m (Dynamic t (Bool, Maybe a), Event t a)
forall a b. (a -> b) -> a -> b
$ Event t a -> Event t a -> Event t (These a a)
forall a b. Event t a -> Event t b -> Event t (These a b)
forall (f :: * -> *) a b.
Semialign f =>
f a -> f b -> f (These a b)
align Event t a
e Event t a
delayed -- We start in immediate mode with an empty buffer.
      Event t a
delayed <- NominalDiffTime -> Event t a -> m (Event t a)
forall t (m :: * -> *) a.
(PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) =>
NominalDiffTime -> Event t a -> m (Event t a)
delay NominalDiffTime
t Event t a
outE
  Event t a -> m (Event t a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Event t a
outE

data ThrottleState b
  = ThrottleState_Immediate
  | ThrottleState_Buffered (ThrottleBuffer b)
  deriving (ThrottleState b -> ThrottleState b -> Bool
(ThrottleState b -> ThrottleState b -> Bool)
-> (ThrottleState b -> ThrottleState b -> Bool)
-> Eq (ThrottleState b)
forall b. Eq b => ThrottleState b -> ThrottleState b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall b. Eq b => ThrottleState b -> ThrottleState b -> Bool
== :: ThrottleState b -> ThrottleState b -> Bool
$c/= :: forall b. Eq b => ThrottleState b -> ThrottleState b -> Bool
/= :: ThrottleState b -> ThrottleState b -> Bool
Eq, Eq (ThrottleState b)
Eq (ThrottleState b)
-> (ThrottleState b -> ThrottleState b -> Ordering)
-> (ThrottleState b -> ThrottleState b -> Bool)
-> (ThrottleState b -> ThrottleState b -> Bool)
-> (ThrottleState b -> ThrottleState b -> Bool)
-> (ThrottleState b -> ThrottleState b -> Bool)
-> (ThrottleState b -> ThrottleState b -> ThrottleState b)
-> (ThrottleState b -> ThrottleState b -> ThrottleState b)
-> Ord (ThrottleState b)
ThrottleState b -> ThrottleState b -> Bool
ThrottleState b -> ThrottleState b -> Ordering
ThrottleState b -> ThrottleState b -> ThrottleState b
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {b}. Ord b => Eq (ThrottleState b)
forall b. Ord b => ThrottleState b -> ThrottleState b -> Bool
forall b. Ord b => ThrottleState b -> ThrottleState b -> Ordering
forall b.
Ord b =>
ThrottleState b -> ThrottleState b -> ThrottleState b
$ccompare :: forall b. Ord b => ThrottleState b -> ThrottleState b -> Ordering
compare :: ThrottleState b -> ThrottleState b -> Ordering
$c< :: forall b. Ord b => ThrottleState b -> ThrottleState b -> Bool
< :: ThrottleState b -> ThrottleState b -> Bool
$c<= :: forall b. Ord b => ThrottleState b -> ThrottleState b -> Bool
<= :: ThrottleState b -> ThrottleState b -> Bool
$c> :: forall b. Ord b => ThrottleState b -> ThrottleState b -> Bool
> :: ThrottleState b -> ThrottleState b -> Bool
$c>= :: forall b. Ord b => ThrottleState b -> ThrottleState b -> Bool
>= :: ThrottleState b -> ThrottleState b -> Bool
$cmax :: forall b.
Ord b =>
ThrottleState b -> ThrottleState b -> ThrottleState b
max :: ThrottleState b -> ThrottleState b -> ThrottleState b
$cmin :: forall b.
Ord b =>
ThrottleState b -> ThrottleState b -> ThrottleState b
min :: ThrottleState b -> ThrottleState b -> ThrottleState b
Ord, Int -> ThrottleState b -> ShowS
[ThrottleState b] -> ShowS
ThrottleState b -> String
(Int -> ThrottleState b -> ShowS)
-> (ThrottleState b -> String)
-> ([ThrottleState b] -> ShowS)
-> Show (ThrottleState b)
forall b. Show b => Int -> ThrottleState b -> ShowS
forall b. Show b => [ThrottleState b] -> ShowS
forall b. Show b => ThrottleState b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall b. Show b => Int -> ThrottleState b -> ShowS
showsPrec :: Int -> ThrottleState b -> ShowS
$cshow :: forall b. Show b => ThrottleState b -> String
show :: ThrottleState b -> String
$cshowList :: forall b. Show b => [ThrottleState b] -> ShowS
showList :: [ThrottleState b] -> ShowS
Show, (forall a b. (a -> b) -> ThrottleState a -> ThrottleState b)
-> (forall a b. a -> ThrottleState b -> ThrottleState a)
-> Functor ThrottleState
forall a b. a -> ThrottleState b -> ThrottleState a
forall a b. (a -> b) -> ThrottleState a -> ThrottleState b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> ThrottleState a -> ThrottleState b
fmap :: forall a b. (a -> b) -> ThrottleState a -> ThrottleState b
$c<$ :: forall a b. a -> ThrottleState b -> ThrottleState a
<$ :: forall a b. a -> ThrottleState b -> ThrottleState a
Functor, (forall m. Monoid m => ThrottleState m -> m)
-> (forall m a. Monoid m => (a -> m) -> ThrottleState a -> m)
-> (forall m a. Monoid m => (a -> m) -> ThrottleState a -> m)
-> (forall a b. (a -> b -> b) -> b -> ThrottleState a -> b)
-> (forall a b. (a -> b -> b) -> b -> ThrottleState a -> b)
-> (forall b a. (b -> a -> b) -> b -> ThrottleState a -> b)
-> (forall b a. (b -> a -> b) -> b -> ThrottleState a -> b)
-> (forall a. (a -> a -> a) -> ThrottleState a -> a)
-> (forall a. (a -> a -> a) -> ThrottleState a -> a)
-> (forall a. ThrottleState a -> [a])
-> (forall a. ThrottleState a -> Bool)
-> (forall a. ThrottleState a -> Int)
-> (forall a. Eq a => a -> ThrottleState a -> Bool)
-> (forall a. Ord a => ThrottleState a -> a)
-> (forall a. Ord a => ThrottleState a -> a)
-> (forall a. Num a => ThrottleState a -> a)
-> (forall a. Num a => ThrottleState a -> a)
-> Foldable ThrottleState
forall a. Eq a => a -> ThrottleState a -> Bool
forall a. Num a => ThrottleState a -> a
forall a. Ord a => ThrottleState a -> a
forall m. Monoid m => ThrottleState m -> m
forall a. ThrottleState a -> Bool
forall a. ThrottleState a -> Int
forall a. ThrottleState a -> [a]
forall a. (a -> a -> a) -> ThrottleState a -> a
forall m a. Monoid m => (a -> m) -> ThrottleState a -> m
forall b a. (b -> a -> b) -> b -> ThrottleState a -> b
forall a b. (a -> b -> b) -> b -> ThrottleState a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => ThrottleState m -> m
fold :: forall m. Monoid m => ThrottleState m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> ThrottleState a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> ThrottleState a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> ThrottleState a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> ThrottleState a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> ThrottleState a -> b
foldr :: forall a b. (a -> b -> b) -> b -> ThrottleState a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> ThrottleState a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> ThrottleState a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> ThrottleState a -> b
foldl :: forall b a. (b -> a -> b) -> b -> ThrottleState a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> ThrottleState a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> ThrottleState a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> ThrottleState a -> a
foldr1 :: forall a. (a -> a -> a) -> ThrottleState a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ThrottleState a -> a
foldl1 :: forall a. (a -> a -> a) -> ThrottleState a -> a
$ctoList :: forall a. ThrottleState a -> [a]
toList :: forall a. ThrottleState a -> [a]
$cnull :: forall a. ThrottleState a -> Bool
null :: forall a. ThrottleState a -> Bool
$clength :: forall a. ThrottleState a -> Int
length :: forall a. ThrottleState a -> Int
$celem :: forall a. Eq a => a -> ThrottleState a -> Bool
elem :: forall a. Eq a => a -> ThrottleState a -> Bool
$cmaximum :: forall a. Ord a => ThrottleState a -> a
maximum :: forall a. Ord a => ThrottleState a -> a
$cminimum :: forall a. Ord a => ThrottleState a -> a
minimum :: forall a. Ord a => ThrottleState a -> a
$csum :: forall a. Num a => ThrottleState a -> a
sum :: forall a. Num a => ThrottleState a -> a
$cproduct :: forall a. Num a => ThrottleState a -> a
product :: forall a. Num a => ThrottleState a -> a
Foldable, Functor ThrottleState
Foldable ThrottleState
Functor ThrottleState
-> Foldable ThrottleState
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> ThrottleState a -> f (ThrottleState b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    ThrottleState (f a) -> f (ThrottleState a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> ThrottleState a -> m (ThrottleState b))
-> (forall (m :: * -> *) a.
    Monad m =>
    ThrottleState (m a) -> m (ThrottleState a))
-> Traversable ThrottleState
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ThrottleState (m a) -> m (ThrottleState a)
forall (f :: * -> *) a.
Applicative f =>
ThrottleState (f a) -> f (ThrottleState a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ThrottleState a -> m (ThrottleState b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ThrottleState a -> f (ThrottleState b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ThrottleState a -> f (ThrottleState b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ThrottleState a -> f (ThrottleState b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ThrottleState (f a) -> f (ThrottleState a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ThrottleState (f a) -> f (ThrottleState a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ThrottleState a -> m (ThrottleState b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ThrottleState a -> m (ThrottleState b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
ThrottleState (m a) -> m (ThrottleState a)
sequence :: forall (m :: * -> *) a.
Monad m =>
ThrottleState (m a) -> m (ThrottleState a)
Traversable, (forall x. ThrottleState b -> Rep (ThrottleState b) x)
-> (forall x. Rep (ThrottleState b) x -> ThrottleState b)
-> Generic (ThrottleState b)
forall x. Rep (ThrottleState b) x -> ThrottleState b
forall x. ThrottleState b -> Rep (ThrottleState b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (ThrottleState b) x -> ThrottleState b
forall b x. ThrottleState b -> Rep (ThrottleState b) x
$cfrom :: forall b x. ThrottleState b -> Rep (ThrottleState b) x
from :: forall x. ThrottleState b -> Rep (ThrottleState b) x
$cto :: forall b x. Rep (ThrottleState b) x -> ThrottleState b
to :: forall x. Rep (ThrottleState b) x -> ThrottleState b
Generic, Typeable (ThrottleState b)
Typeable (ThrottleState b)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> ThrottleState b -> c (ThrottleState b))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (ThrottleState b))
-> (ThrottleState b -> Constr)
-> (ThrottleState b -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (ThrottleState b)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (ThrottleState b)))
-> ((forall b. Data b => b -> b)
    -> ThrottleState b -> ThrottleState b)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ThrottleState b -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ThrottleState b -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ThrottleState b -> m (ThrottleState b))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ThrottleState b -> m (ThrottleState b))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ThrottleState b -> m (ThrottleState b))
-> Data (ThrottleState b)
ThrottleState b -> Constr
ThrottleState b -> DataType
(forall b. Data b => b -> b) -> ThrottleState b -> ThrottleState b
forall {b}. Data b => Typeable (ThrottleState b)
forall b. Data b => ThrottleState b -> Constr
forall b. Data b => ThrottleState b -> DataType
forall b.
Data b =>
(forall b. Data b => b -> b) -> ThrottleState b -> ThrottleState b
forall b u.
Data b =>
Int -> (forall d. Data d => d -> u) -> ThrottleState b -> u
forall b u.
Data b =>
(forall d. Data d => d -> u) -> ThrottleState b -> [u]
forall b r r'.
Data b =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
forall b r r'.
Data b =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
forall b (m :: * -> *).
(Data b, Monad m) =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
forall b (m :: * -> *).
(Data b, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
forall b (c :: * -> *).
Data b =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleState b)
forall b (c :: * -> *).
Data b =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleState b -> c (ThrottleState b)
forall b (t :: * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleState b))
forall b (t :: * -> * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleState b))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ThrottleState b -> u
forall u. (forall d. Data d => d -> u) -> ThrottleState b -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleState b)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleState b -> c (ThrottleState b)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleState b))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleState b))
$cgfoldl :: forall b (c :: * -> *).
Data b =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleState b -> c (ThrottleState b)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleState b -> c (ThrottleState b)
$cgunfold :: forall b (c :: * -> *).
Data b =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleState b)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleState b)
$ctoConstr :: forall b. Data b => ThrottleState b -> Constr
toConstr :: ThrottleState b -> Constr
$cdataTypeOf :: forall b. Data b => ThrottleState b -> DataType
dataTypeOf :: ThrottleState b -> DataType
$cdataCast1 :: forall b (t :: * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleState b))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleState b))
$cdataCast2 :: forall b (t :: * -> * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleState b))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleState b))
$cgmapT :: forall b.
Data b =>
(forall b. Data b => b -> b) -> ThrottleState b -> ThrottleState b
gmapT :: (forall b. Data b => b -> b) -> ThrottleState b -> ThrottleState b
$cgmapQl :: forall b r r'.
Data b =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
$cgmapQr :: forall b r r'.
Data b =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleState b -> r
$cgmapQ :: forall b u.
Data b =>
(forall d. Data d => d -> u) -> ThrottleState b -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ThrottleState b -> [u]
$cgmapQi :: forall b u.
Data b =>
Int -> (forall d. Data d => d -> u) -> ThrottleState b -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ThrottleState b -> u
$cgmapM :: forall b (m :: * -> *).
(Data b, Monad m) =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
$cgmapMp :: forall b (m :: * -> *).
(Data b, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
$cgmapMo :: forall b (m :: * -> *).
(Data b, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ThrottleState b -> m (ThrottleState b)
Data, Typeable)

data ThrottleBuffer b
  = ThrottleBuffer_Empty -- Empty conflicts with lens, and hiding it would require turning
                         -- on PatternSynonyms
  | ThrottleBuffer_Full b
  deriving (ThrottleBuffer b -> ThrottleBuffer b -> Bool
(ThrottleBuffer b -> ThrottleBuffer b -> Bool)
-> (ThrottleBuffer b -> ThrottleBuffer b -> Bool)
-> Eq (ThrottleBuffer b)
forall b. Eq b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall b. Eq b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
== :: ThrottleBuffer b -> ThrottleBuffer b -> Bool
$c/= :: forall b. Eq b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
/= :: ThrottleBuffer b -> ThrottleBuffer b -> Bool
Eq, Eq (ThrottleBuffer b)
Eq (ThrottleBuffer b)
-> (ThrottleBuffer b -> ThrottleBuffer b -> Ordering)
-> (ThrottleBuffer b -> ThrottleBuffer b -> Bool)
-> (ThrottleBuffer b -> ThrottleBuffer b -> Bool)
-> (ThrottleBuffer b -> ThrottleBuffer b -> Bool)
-> (ThrottleBuffer b -> ThrottleBuffer b -> Bool)
-> (ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b)
-> (ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b)
-> Ord (ThrottleBuffer b)
ThrottleBuffer b -> ThrottleBuffer b -> Bool
ThrottleBuffer b -> ThrottleBuffer b -> Ordering
ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {b}. Ord b => Eq (ThrottleBuffer b)
forall b. Ord b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
forall b. Ord b => ThrottleBuffer b -> ThrottleBuffer b -> Ordering
forall b.
Ord b =>
ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
$ccompare :: forall b. Ord b => ThrottleBuffer b -> ThrottleBuffer b -> Ordering
compare :: ThrottleBuffer b -> ThrottleBuffer b -> Ordering
$c< :: forall b. Ord b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
< :: ThrottleBuffer b -> ThrottleBuffer b -> Bool
$c<= :: forall b. Ord b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
<= :: ThrottleBuffer b -> ThrottleBuffer b -> Bool
$c> :: forall b. Ord b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
> :: ThrottleBuffer b -> ThrottleBuffer b -> Bool
$c>= :: forall b. Ord b => ThrottleBuffer b -> ThrottleBuffer b -> Bool
>= :: ThrottleBuffer b -> ThrottleBuffer b -> Bool
$cmax :: forall b.
Ord b =>
ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
max :: ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
$cmin :: forall b.
Ord b =>
ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
min :: ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
Ord, Int -> ThrottleBuffer b -> ShowS
[ThrottleBuffer b] -> ShowS
ThrottleBuffer b -> String
(Int -> ThrottleBuffer b -> ShowS)
-> (ThrottleBuffer b -> String)
-> ([ThrottleBuffer b] -> ShowS)
-> Show (ThrottleBuffer b)
forall b. Show b => Int -> ThrottleBuffer b -> ShowS
forall b. Show b => [ThrottleBuffer b] -> ShowS
forall b. Show b => ThrottleBuffer b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall b. Show b => Int -> ThrottleBuffer b -> ShowS
showsPrec :: Int -> ThrottleBuffer b -> ShowS
$cshow :: forall b. Show b => ThrottleBuffer b -> String
show :: ThrottleBuffer b -> String
$cshowList :: forall b. Show b => [ThrottleBuffer b] -> ShowS
showList :: [ThrottleBuffer b] -> ShowS
Show, (forall a b. (a -> b) -> ThrottleBuffer a -> ThrottleBuffer b)
-> (forall a b. a -> ThrottleBuffer b -> ThrottleBuffer a)
-> Functor ThrottleBuffer
forall a b. a -> ThrottleBuffer b -> ThrottleBuffer a
forall a b. (a -> b) -> ThrottleBuffer a -> ThrottleBuffer b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> ThrottleBuffer a -> ThrottleBuffer b
fmap :: forall a b. (a -> b) -> ThrottleBuffer a -> ThrottleBuffer b
$c<$ :: forall a b. a -> ThrottleBuffer b -> ThrottleBuffer a
<$ :: forall a b. a -> ThrottleBuffer b -> ThrottleBuffer a
Functor, (forall m. Monoid m => ThrottleBuffer m -> m)
-> (forall m a. Monoid m => (a -> m) -> ThrottleBuffer a -> m)
-> (forall m a. Monoid m => (a -> m) -> ThrottleBuffer a -> m)
-> (forall a b. (a -> b -> b) -> b -> ThrottleBuffer a -> b)
-> (forall a b. (a -> b -> b) -> b -> ThrottleBuffer a -> b)
-> (forall b a. (b -> a -> b) -> b -> ThrottleBuffer a -> b)
-> (forall b a. (b -> a -> b) -> b -> ThrottleBuffer a -> b)
-> (forall a. (a -> a -> a) -> ThrottleBuffer a -> a)
-> (forall a. (a -> a -> a) -> ThrottleBuffer a -> a)
-> (forall a. ThrottleBuffer a -> [a])
-> (forall a. ThrottleBuffer a -> Bool)
-> (forall a. ThrottleBuffer a -> Int)
-> (forall a. Eq a => a -> ThrottleBuffer a -> Bool)
-> (forall a. Ord a => ThrottleBuffer a -> a)
-> (forall a. Ord a => ThrottleBuffer a -> a)
-> (forall a. Num a => ThrottleBuffer a -> a)
-> (forall a. Num a => ThrottleBuffer a -> a)
-> Foldable ThrottleBuffer
forall a. Eq a => a -> ThrottleBuffer a -> Bool
forall a. Num a => ThrottleBuffer a -> a
forall a. Ord a => ThrottleBuffer a -> a
forall m. Monoid m => ThrottleBuffer m -> m
forall a. ThrottleBuffer a -> Bool
forall a. ThrottleBuffer a -> Int
forall a. ThrottleBuffer a -> [a]
forall a. (a -> a -> a) -> ThrottleBuffer a -> a
forall m a. Monoid m => (a -> m) -> ThrottleBuffer a -> m
forall b a. (b -> a -> b) -> b -> ThrottleBuffer a -> b
forall a b. (a -> b -> b) -> b -> ThrottleBuffer a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => ThrottleBuffer m -> m
fold :: forall m. Monoid m => ThrottleBuffer m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> ThrottleBuffer a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> ThrottleBuffer a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> ThrottleBuffer a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> ThrottleBuffer a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> ThrottleBuffer a -> b
foldr :: forall a b. (a -> b -> b) -> b -> ThrottleBuffer a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> ThrottleBuffer a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> ThrottleBuffer a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> ThrottleBuffer a -> b
foldl :: forall b a. (b -> a -> b) -> b -> ThrottleBuffer a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> ThrottleBuffer a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> ThrottleBuffer a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> ThrottleBuffer a -> a
foldr1 :: forall a. (a -> a -> a) -> ThrottleBuffer a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ThrottleBuffer a -> a
foldl1 :: forall a. (a -> a -> a) -> ThrottleBuffer a -> a
$ctoList :: forall a. ThrottleBuffer a -> [a]
toList :: forall a. ThrottleBuffer a -> [a]
$cnull :: forall a. ThrottleBuffer a -> Bool
null :: forall a. ThrottleBuffer a -> Bool
$clength :: forall a. ThrottleBuffer a -> Int
length :: forall a. ThrottleBuffer a -> Int
$celem :: forall a. Eq a => a -> ThrottleBuffer a -> Bool
elem :: forall a. Eq a => a -> ThrottleBuffer a -> Bool
$cmaximum :: forall a. Ord a => ThrottleBuffer a -> a
maximum :: forall a. Ord a => ThrottleBuffer a -> a
$cminimum :: forall a. Ord a => ThrottleBuffer a -> a
minimum :: forall a. Ord a => ThrottleBuffer a -> a
$csum :: forall a. Num a => ThrottleBuffer a -> a
sum :: forall a. Num a => ThrottleBuffer a -> a
$cproduct :: forall a. Num a => ThrottleBuffer a -> a
product :: forall a. Num a => ThrottleBuffer a -> a
Foldable, Functor ThrottleBuffer
Foldable ThrottleBuffer
Functor ThrottleBuffer
-> Foldable ThrottleBuffer
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> ThrottleBuffer a -> f (ThrottleBuffer b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    ThrottleBuffer (f a) -> f (ThrottleBuffer a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> ThrottleBuffer a -> m (ThrottleBuffer b))
-> (forall (m :: * -> *) a.
    Monad m =>
    ThrottleBuffer (m a) -> m (ThrottleBuffer a))
-> Traversable ThrottleBuffer
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ThrottleBuffer (m a) -> m (ThrottleBuffer a)
forall (f :: * -> *) a.
Applicative f =>
ThrottleBuffer (f a) -> f (ThrottleBuffer a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ThrottleBuffer a -> m (ThrottleBuffer b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ThrottleBuffer a -> f (ThrottleBuffer b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ThrottleBuffer a -> f (ThrottleBuffer b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ThrottleBuffer a -> f (ThrottleBuffer b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ThrottleBuffer (f a) -> f (ThrottleBuffer a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ThrottleBuffer (f a) -> f (ThrottleBuffer a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ThrottleBuffer a -> m (ThrottleBuffer b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ThrottleBuffer a -> m (ThrottleBuffer b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
ThrottleBuffer (m a) -> m (ThrottleBuffer a)
sequence :: forall (m :: * -> *) a.
Monad m =>
ThrottleBuffer (m a) -> m (ThrottleBuffer a)
Traversable, (forall x. ThrottleBuffer b -> Rep (ThrottleBuffer b) x)
-> (forall x. Rep (ThrottleBuffer b) x -> ThrottleBuffer b)
-> Generic (ThrottleBuffer b)
forall x. Rep (ThrottleBuffer b) x -> ThrottleBuffer b
forall x. ThrottleBuffer b -> Rep (ThrottleBuffer b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall b x. Rep (ThrottleBuffer b) x -> ThrottleBuffer b
forall b x. ThrottleBuffer b -> Rep (ThrottleBuffer b) x
$cfrom :: forall b x. ThrottleBuffer b -> Rep (ThrottleBuffer b) x
from :: forall x. ThrottleBuffer b -> Rep (ThrottleBuffer b) x
$cto :: forall b x. Rep (ThrottleBuffer b) x -> ThrottleBuffer b
to :: forall x. Rep (ThrottleBuffer b) x -> ThrottleBuffer b
Generic, Typeable (ThrottleBuffer b)
Typeable (ThrottleBuffer b)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> ThrottleBuffer b
    -> c (ThrottleBuffer b))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (ThrottleBuffer b))
-> (ThrottleBuffer b -> Constr)
-> (ThrottleBuffer b -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (ThrottleBuffer b)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (ThrottleBuffer b)))
-> ((forall b. Data b => b -> b)
    -> ThrottleBuffer b -> ThrottleBuffer b)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> ThrottleBuffer b -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ThrottleBuffer b -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> ThrottleBuffer b -> m (ThrottleBuffer b))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ThrottleBuffer b -> m (ThrottleBuffer b))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ThrottleBuffer b -> m (ThrottleBuffer b))
-> Data (ThrottleBuffer b)
ThrottleBuffer b -> Constr
ThrottleBuffer b -> DataType
(forall b. Data b => b -> b)
-> ThrottleBuffer b -> ThrottleBuffer b
forall {b}. Data b => Typeable (ThrottleBuffer b)
forall b. Data b => ThrottleBuffer b -> Constr
forall b. Data b => ThrottleBuffer b -> DataType
forall b.
Data b =>
(forall b. Data b => b -> b)
-> ThrottleBuffer b -> ThrottleBuffer b
forall b u.
Data b =>
Int -> (forall d. Data d => d -> u) -> ThrottleBuffer b -> u
forall b u.
Data b =>
(forall d. Data d => d -> u) -> ThrottleBuffer b -> [u]
forall b r r'.
Data b =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
forall b r r'.
Data b =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
forall b (m :: * -> *).
(Data b, Monad m) =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
forall b (m :: * -> *).
(Data b, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
forall b (c :: * -> *).
Data b =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleBuffer b)
forall b (c :: * -> *).
Data b =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleBuffer b -> c (ThrottleBuffer b)
forall b (t :: * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleBuffer b))
forall b (t :: * -> * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleBuffer b))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ThrottleBuffer b -> u
forall u. (forall d. Data d => d -> u) -> ThrottleBuffer b -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleBuffer b)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleBuffer b -> c (ThrottleBuffer b)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleBuffer b))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleBuffer b))
$cgfoldl :: forall b (c :: * -> *).
Data b =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleBuffer b -> c (ThrottleBuffer b)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ThrottleBuffer b -> c (ThrottleBuffer b)
$cgunfold :: forall b (c :: * -> *).
Data b =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleBuffer b)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ThrottleBuffer b)
$ctoConstr :: forall b. Data b => ThrottleBuffer b -> Constr
toConstr :: ThrottleBuffer b -> Constr
$cdataTypeOf :: forall b. Data b => ThrottleBuffer b -> DataType
dataTypeOf :: ThrottleBuffer b -> DataType
$cdataCast1 :: forall b (t :: * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleBuffer b))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ThrottleBuffer b))
$cdataCast2 :: forall b (t :: * -> * -> *) (c :: * -> *).
(Data b, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleBuffer b))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ThrottleBuffer b))
$cgmapT :: forall b.
Data b =>
(forall b. Data b => b -> b)
-> ThrottleBuffer b -> ThrottleBuffer b
gmapT :: (forall b. Data b => b -> b)
-> ThrottleBuffer b -> ThrottleBuffer b
$cgmapQl :: forall b r r'.
Data b =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
$cgmapQr :: forall b r r'.
Data b =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ThrottleBuffer b -> r
$cgmapQ :: forall b u.
Data b =>
(forall d. Data d => d -> u) -> ThrottleBuffer b -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ThrottleBuffer b -> [u]
$cgmapQi :: forall b u.
Data b =>
Int -> (forall d. Data d => d -> u) -> ThrottleBuffer b -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ThrottleBuffer b -> u
$cgmapM :: forall b (m :: * -> *).
(Data b, Monad m) =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
$cgmapMp :: forall b (m :: * -> *).
(Data b, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
$cgmapMo :: forall b (m :: * -> *).
(Data b, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ThrottleBuffer b -> m (ThrottleBuffer b)
Data, Typeable)

instance Semigroup b => Semigroup (ThrottleBuffer b) where
  ThrottleBuffer b
x <> :: ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
<> ThrottleBuffer b
y = case ThrottleBuffer b
x of
    ThrottleBuffer b
ThrottleBuffer_Empty -> ThrottleBuffer b
y
    ThrottleBuffer_Full b
b1 -> case ThrottleBuffer b
y of
      ThrottleBuffer b
ThrottleBuffer_Empty -> ThrottleBuffer b
x
      ThrottleBuffer_Full b
b2 -> b -> ThrottleBuffer b
forall b. b -> ThrottleBuffer b
ThrottleBuffer_Full (b -> ThrottleBuffer b) -> b -> ThrottleBuffer b
forall a b. (a -> b) -> a -> b
$ b
b1 b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
b2
  {-# INLINE (<>) #-}

instance Semigroup b => Monoid (ThrottleBuffer b) where
  mempty :: ThrottleBuffer b
mempty = ThrottleBuffer b
forall b. ThrottleBuffer b
ThrottleBuffer_Empty
  {-# INLINE mempty #-}
  mappend :: ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
mappend = ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
forall a. Semigroup a => a -> a -> a
(<>)
  {-# INLINE mappend #-}

-- | 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.
throttleBatchWithLag :: (MonadFix m, MonadHold t m, PerformEvent t m, Semigroup a) => (Event t () -> m (Event t ())) -> Event t a -> m (Event t a)
-- Invariants:
-- * 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
--   buffer, but not both.
-- * An existing full buffer must either stay in the buffer or go to output,
--   but not both.
throttleBatchWithLag :: forall (m :: * -> *) t a.
(MonadFix m, MonadHold t m, PerformEvent t m, Semigroup a) =>
(Event t () -> m (Event t ())) -> Event t a -> m (Event t a)
throttleBatchWithLag Event t () -> m (Event t ())
lag Event t a
e = do
  let f :: ThrottleState b -> These b b -> (Maybe (ThrottleState b), Maybe b)
f ThrottleState b
state These b b
x = case These b b
x of -- (Just $ newState, out)
        This b
a -> -- If only the input event fires
          case ThrottleState b
state of
            ThrottleState b
ThrottleState_Immediate -> -- and we're in immediate mode
              -- Immediate mode turns off, and the buffer is empty.
              -- We fire the output event with the input event value immediately.
              (ThrottleState b -> Maybe (ThrottleState b)
forall a. a -> Maybe a
Just (ThrottleState b -> Maybe (ThrottleState b))
-> ThrottleState b -> Maybe (ThrottleState b)
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b -> ThrottleState b
forall b. ThrottleBuffer b -> ThrottleState b
ThrottleState_Buffered (ThrottleBuffer b -> ThrottleState b)
-> ThrottleBuffer b -> ThrottleState b
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b
forall b. ThrottleBuffer b
ThrottleBuffer_Empty, b -> Maybe b
forall a. a -> Maybe a
Just b
a)
            ThrottleState_Buffered ThrottleBuffer b
b -> -- and we're not in immediate mode
              -- Immediate mode remains off, and we accumulate the input value.
              -- We don't fire the output event.
              (ThrottleState b -> Maybe (ThrottleState b)
forall a. a -> Maybe a
Just (ThrottleState b -> Maybe (ThrottleState b))
-> ThrottleState b -> Maybe (ThrottleState b)
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b -> ThrottleState b
forall b. ThrottleBuffer b -> ThrottleState b
ThrottleState_Buffered (ThrottleBuffer b -> ThrottleState b)
-> ThrottleBuffer b -> ThrottleState b
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b
b ThrottleBuffer b -> ThrottleBuffer b -> ThrottleBuffer b
forall a. Semigroup a => a -> a -> a
<> b -> ThrottleBuffer b
forall b. b -> ThrottleBuffer b
ThrottleBuffer_Full b
a, Maybe b
forall a. Maybe a
Nothing)
        That b
_ -> -- If only the delayed output event fires,
          case ThrottleState b
state of
            ThrottleState b
ThrottleState_Immediate -> -- and we're in immediate mode
              -- Nothing happens.
              (Maybe (ThrottleState b)
forall a. Maybe a
Nothing, Maybe b
forall a. Maybe a
Nothing)
            ThrottleState_Buffered ThrottleBuffer b
ThrottleBuffer_Empty -> -- and the buffer is empty:
              -- Immediate mode turns back on, and the buffer remains empty.
              -- We don't fire.
              (ThrottleState b -> Maybe (ThrottleState b)
forall a. a -> Maybe a
Just ThrottleState b
forall b. ThrottleState b
ThrottleState_Immediate, Maybe b
forall a. Maybe a
Nothing)
            ThrottleState_Buffered (ThrottleBuffer_Full b
b) -> -- and the buffer is full:
              -- Immediate mode remains off, and the buffer is cleared.
              -- We fire with the buffered value.
              (ThrottleState b -> Maybe (ThrottleState b)
forall a. a -> Maybe a
Just (ThrottleState b -> Maybe (ThrottleState b))
-> ThrottleState b -> Maybe (ThrottleState b)
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b -> ThrottleState b
forall b. ThrottleBuffer b -> ThrottleState b
ThrottleState_Buffered ThrottleBuffer b
forall b. ThrottleBuffer b
ThrottleBuffer_Empty, b -> Maybe b
forall a. a -> Maybe a
Just b
b)
        These b
a b
_ -> -- If both the input and delayed output event fire simultaneously:
          case ThrottleState b
state of
            ThrottleState b
ThrottleState_Immediate -> -- and we're in immediate mode
              -- Immediate mode turns off, and the buffer is empty.
              -- We fire with the input event's value, as it is the most recent we have seen at this moment.
              (ThrottleState b -> Maybe (ThrottleState b)
forall a. a -> Maybe a
Just (ThrottleState b -> Maybe (ThrottleState b))
-> ThrottleState b -> Maybe (ThrottleState b)
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b -> ThrottleState b
forall b. ThrottleBuffer b -> ThrottleState b
ThrottleState_Buffered ThrottleBuffer b
forall b. ThrottleBuffer b
ThrottleBuffer_Empty, b -> Maybe b
forall a. a -> Maybe a
Just b
a)
            ThrottleState_Buffered ThrottleBuffer b
ThrottleBuffer_Empty -> -- and the buffer is empty:
              -- Immediate mode stays off, and the buffer remains empty.
              -- We fire with the input event's value.
              (ThrottleState b -> Maybe (ThrottleState b)
forall a. a -> Maybe a
Just (ThrottleState b -> Maybe (ThrottleState b))
-> ThrottleState b -> Maybe (ThrottleState b)
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b -> ThrottleState b
forall b. ThrottleBuffer b -> ThrottleState b
ThrottleState_Buffered ThrottleBuffer b
forall b. ThrottleBuffer b
ThrottleBuffer_Empty, b -> Maybe b
forall a. a -> Maybe a
Just b
a)
            ThrottleState_Buffered (ThrottleBuffer_Full b
b) -> -- and the buffer is full:
              -- Immediate mode remains off, and the buffer is cleared.
              -- We fire with everything including the buffered value.
              (ThrottleState b -> Maybe (ThrottleState b)
forall a. a -> Maybe a
Just (ThrottleState b -> Maybe (ThrottleState b))
-> ThrottleState b -> Maybe (ThrottleState b)
forall a b. (a -> b) -> a -> b
$ ThrottleBuffer b -> ThrottleState b
forall b. ThrottleBuffer b -> ThrottleState b
ThrottleState_Buffered ThrottleBuffer b
forall b. ThrottleBuffer b
ThrottleBuffer_Empty, b -> Maybe b
forall a. a -> Maybe a
Just (b
b b -> b -> b
forall a. Semigroup a => a -> a -> a
<> b
a))
  rec (Dynamic t (ThrottleState a)
_stateDyn, Event t a
outE) <- (ThrottleState a
 -> These a () -> (Maybe (ThrottleState a), Maybe a))
-> ThrottleState a
-> Event t (These a ())
-> m (Dynamic t (ThrottleState a), Event t a)
forall {k} (t :: k) (m :: * -> *) a b c.
(Reflex t, MonadHold t m, MonadFix m) =>
(a -> b -> (Maybe a, Maybe c))
-> a -> Event t b -> m (Dynamic t a, Event t c)
mapAccumMaybeDyn ThrottleState a -> These a () -> (Maybe (ThrottleState a), Maybe a)
forall {b} {b}.
Semigroup b =>
ThrottleState b -> These b b -> (Maybe (ThrottleState b), Maybe b)
f
        ThrottleState a
forall b. ThrottleState b
ThrottleState_Immediate -- We start in immediate mode with an empty buffer.
        (Event t a -> Event t () -> Event t (These a ())
forall a b. Event t a -> Event t b -> Event t (These a b)
forall (f :: * -> *) a b.
Semialign f =>
f a -> f b -> f (These a b)
align Event t a
e Event t ()
delayed)
      Event t ()
delayed <- Event t () -> m (Event t ())
lag (Event t a -> Event t ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Event t a
outE)
  Event t a -> m (Event t a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Event t a
outE

#ifdef USE_TEMPLATE_HASKELL
makeLensesWith (lensRules & simpleLenses .~ True) ''TickInfo
#else
tickInfo_lastUTC :: Lens' TickInfo UTCTime
tickInfo_lastUTC f (TickInfo x1 x2 x3) = (\y -> TickInfo y x2 x3) <$> f x1
{-# INLINE tickInfo_lastUTC #-}

tickInfo_n :: Lens' TickInfo Integer
tickInfo_n f (TickInfo x1 x2 x3) = (\y -> TickInfo x1 y x3) <$> f x2
{-# INLINE tickInfo_n #-}

tickInfo_alreadyElapsed :: Lens' TickInfo NominalDiffTime
tickInfo_alreadyElapsed f (TickInfo x1 x2 x3) = (\y -> TickInfo x1 x2 y) <$> f x3
{-# INLINE tickInfo_alreadyElapsed #-}
#endif