{-# 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 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
data TickInfo
= TickInfo { _tickInfo_lastUTC :: UTCTime
, _tickInfo_n :: Integer
, _tickInfo_alreadyElapsed :: NominalDiffTime
}
deriving (Eq, Ord, Show, Typeable)
tickLossy :: (PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) => NominalDiffTime -> UTCTime -> m (Event t TickInfo)
tickLossy dt t0 = tickLossyFrom dt t0 =<< getPostBuild
tickLossyFromPostBuildTime :: (PostBuild t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m) => NominalDiffTime -> m (Event t TickInfo)
tickLossyFromPostBuildTime dt = do
postBuild <- getPostBuild
postBuildTime <- performEvent $ liftIO getCurrentTime <$ postBuild
tickLossyFrom' $ (dt,) <$> postBuildTime
tickLossyFrom
:: (PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m)
=> NominalDiffTime
-> UTCTime
-> Event t a
-> m (Event t TickInfo)
tickLossyFrom dt t0 e = tickLossyFrom' $ (dt, t0) <$ e
tickLossyFrom'
:: (PerformEvent t m, TriggerEvent t m, MonadIO (Performable m), MonadFix m)
=> Event t (NominalDiffTime, UTCTime)
-> m (Event t TickInfo)
tickLossyFrom' e = do
rec result <- performEventAsync $ callAtNextInterval <$> leftmost [e, snd <$> result]
return $ fst <$> result
where callAtNextInterval pair cb = void $ liftIO $ forkIO $ do
tick <- uncurry getCurrentTick pair
Concurrent.delay $ ceiling $ (fst pair - _tickInfo_alreadyElapsed tick) * 1000000
cb (tick, pair)
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 dt t0 = do
initial <- liftIO $ getCurrentTick dt t0
e <- tickLossy dt t0
holdDyn initial e
getCurrentTick :: NominalDiffTime -> UTCTime -> IO TickInfo
getCurrentTick dt t0 = do
t <- getCurrentTime
let offset = t `diffUTCTime` t0
(n, alreadyElapsed) = offset `divMod'` dt
return $ TickInfo t n alreadyElapsed
delay :: (PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a)
delay dt e = performEventAsync $ ffor e $ \a cb -> liftIO $ void $ forkIO $ do
Concurrent.delay $ ceiling $ dt * 1000000
cb a
poissonLossyFrom
:: (RandomGen g, MonadIO (Performable m), PerformEvent t m, TriggerEvent t m)
=> g
-> Double
-> UTCTime
-> Event t a
-> m (Event t TickInfo)
poissonLossyFrom rnd rate = inhomogeneousPoissonFrom rnd (constant rate) rate
poissonLossy
:: (RandomGen g, MonadIO (Performable m), PerformEvent t m, TriggerEvent t m, PostBuild t m)
=> g
-> Double
-> UTCTime
-> m (Event t TickInfo)
poissonLossy rnd rate t0 = poissonLossyFrom rnd rate t0 =<< getPostBuild
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 rnd rate maxRate t0 e = do
ticksWithRateRand <- performEventAsync $
fmap callAtNextInterval e
return $ attachWithMaybe filterFun rate ticksWithRateRand
where
filterFun :: Double -> (TickInfo, Double) -> Maybe TickInfo
filterFun r (tInfo, p)
| r >= p = Just tInfo
| otherwise = Nothing
callAtNextInterval _ cb = void $ liftIO $ forkIO $ go t0 rnd cb 0
go tTargetLast lastGen cb lastN = do
t <- getCurrentTime
let (u, nextGen) = randomR (0,1) lastGen
(p :: Double, nextGen') = randomR (0,maxRate) nextGen
let dt = realToFrac $ (-1) * log u / maxRate :: NominalDiffTime
nEvents = lastN + 1
alreadyElapsed = diffUTCTime t tTargetLast
tTarget = addUTCTime dt tTargetLast
thisDelay = realToFrac $ diffUTCTime tTarget t :: Double
Concurrent.delay $ ceiling $ thisDelay * 1000000
_ <- cb (TickInfo t nEvents alreadyElapsed, p)
go tTarget nextGen' cb nEvents
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 rnd rate maxRate t0 =
inhomogeneousPoissonFrom rnd rate maxRate t0 =<< getPostBuild
debounce :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a)
debounce dt e = do
n :: Dynamic t Integer <- count e
let tagged = attachPromptlyDynWith (,) n e
delayed <- delay dt tagged
return $ attachWithMaybe (\n' (t, v) -> if n' == t then Just v else Nothing) (current n) delayed
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 t newValues = do
let f s x = (Just newState, out)
where newState = case x of
This a -> s |> a
That _ -> mempty
These a _ -> Seq.singleton a
out = case x of
This _ -> if Seq.null s then Just () else Nothing
That _ -> Nothing
These _ _ -> Just ()
rec (buffer, toDelay) <- mapAccumMaybe f mempty $ align newValues delayed
delayed <- delay t toDelay
return $ tag buffer delayed
throttle :: (MonadFix m, MonadHold t m, PerformEvent t m, TriggerEvent t m, MonadIO (Performable m)) => NominalDiffTime -> Event t a -> m (Event t a)
throttle t e = do
let f (immediate, buffer) x = case x of
This a
| immediate ->
(Just (False, Nothing), Just a)
| otherwise ->
(Just (False, Just a), Nothing)
That _ ->
case buffer of
Nothing ->
(Just (True, Nothing), Nothing)
Just b ->
(Just (False, Nothing), Just b)
These a _ ->
(Just (False, Nothing), Just a)
rec (_, outE) <- mapAccumMaybeDyn f (True, Nothing) $ align e delayed
delayed <- delay t outE
return outE
data ThrottleState b
= ThrottleState_Immediate
| ThrottleState_Buffered (ThrottleBuffer b)
deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Generic, Data, Typeable)
data ThrottleBuffer b
= ThrottleBuffer_Empty
| ThrottleBuffer_Full b
deriving (Eq, Ord, Show, Functor, Foldable, Traversable, Generic, Data, Typeable)
instance Semigroup b => Semigroup (ThrottleBuffer b) where
x <> y = case x of
ThrottleBuffer_Empty -> y
ThrottleBuffer_Full b1 -> case y of
ThrottleBuffer_Empty -> x
ThrottleBuffer_Full b2 -> ThrottleBuffer_Full $ b1 <> b2
{-# INLINE (<>) #-}
instance Semigroup b => Monoid (ThrottleBuffer b) where
mempty = ThrottleBuffer_Empty
{-# INLINE mempty #-}
mappend = (<>)
{-# INLINE mappend #-}
throttleBatchWithLag :: (MonadFix m, MonadHold t m, PerformEvent t m, Semigroup a) => (Event t () -> m (Event t ())) -> Event t a -> m (Event t a)
throttleBatchWithLag lag e = do
let f state x = case x of
This a ->
case state of
ThrottleState_Immediate ->
(Just $ ThrottleState_Buffered $ ThrottleBuffer_Empty, Just a)
ThrottleState_Buffered b ->
(Just $ ThrottleState_Buffered $ b <> ThrottleBuffer_Full a, Nothing)
That _ ->
case state of
ThrottleState_Immediate ->
(Nothing, Nothing)
ThrottleState_Buffered ThrottleBuffer_Empty ->
(Just ThrottleState_Immediate, Nothing)
ThrottleState_Buffered (ThrottleBuffer_Full b) ->
(Just $ ThrottleState_Buffered ThrottleBuffer_Empty, Just b)
These a _ ->
case state of
ThrottleState_Immediate ->
(Just $ ThrottleState_Buffered ThrottleBuffer_Empty, Just a)
ThrottleState_Buffered ThrottleBuffer_Empty ->
(Just $ ThrottleState_Buffered ThrottleBuffer_Empty, Just a)
ThrottleState_Buffered (ThrottleBuffer_Full b) ->
(Just $ ThrottleState_Buffered ThrottleBuffer_Empty, Just (b <> a))
rec (_stateDyn, outE) <- mapAccumMaybeDyn f
ThrottleState_Immediate
(align e delayed)
delayed <- lag (void outE)
return 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