-- | -- Module: FRP.NetWire.Request -- Copyright: (c) 2011 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- -- Unique identifiers and context-sensitive wires. module FRP.NetWire.Request ( -- * Context-sensitive mutation context, contextInt, contextLimited, contextLimitedInt, -- ** Simple variants context_, contextInt_, contextLimited_, contextLimitedInt_, -- * Identifiers. identifier ) where import qualified Data.IntMap as IM import qualified Data.Map as M import Control.Arrow import Control.Monad.IO.Class import Control.Concurrent.STM import Data.IntMap (IntMap) import Data.Map (Map) import FRP.NetWire.Wire import FRP.NetWire.Tools -- | Make the given wire context-sensitive. The left input signal is a -- context and the argument wire will mutate individually for each such -- context. -- -- Inherits inhibition and feedback behaviour from the current context's -- wire. context :: forall a b ctx m. (Ord ctx, Monad m) => Wire m (ctx, a) b -> Wire m (ctx, a) b context w0 = context' M.empty 0 where context' :: Map ctx (Time, Wire m (ctx, a) b) -> Time -> Wire m (ctx, a) b context' tm' t' = mkGen $ \ws@(wsDTime -> dt') inp@(ctx, _) -> do let t = t' + dt' let (dt, w') = case M.lookup ctx tm' of Nothing -> (0, w0) Just (lt, w') -> (t - lt, w') (mx, w) <- dt `seq` toGen w' (ws { wsDTime = dt }) inp let tm = M.insert ctx (t, w) tm' return (mx, context' tm t) -- | Simplified variant of 'context'. Takes a context signal only. context_ :: (Ord ctx, Monad m) => Wire m ctx b -> Wire m ctx b context_ w0 = arr (, ()) >>> context (arr fst >>> w0) -- | Specialized version of 'context'. Use this one, if your contexts -- are 'Int's and you have a lot of them. -- -- Inherits inhibition and feedback behaviour from the current context's -- wire. contextInt :: forall a b m. Monad m => Wire m (Int, a) b -> Wire m (Int, a) b contextInt w0 = context' IM.empty 0 where context' :: IntMap (Time, Wire m (Int, a) b) -> Time -> Wire m (Int, a) b context' tm' t' = mkGen $ \ws@(wsDTime -> dt') inp@(ctx, _) -> do let t = t' + dt' let (dt, w') = case IM.lookup ctx tm' of Nothing -> (0, w0) Just (lt, w') -> (t - lt, w') (mx, w) <- dt `seq` toGen w' (ws { wsDTime = dt }) inp let tm = IM.insert ctx (t, w) tm' return (mx, context' tm t) -- | Simplified variant of 'contextInt'. Takes a context signal only. contextInt_ :: Monad m => Wire m Int b -> Wire m Int b contextInt_ w0 = arr (, ()) >>> contextInt (arr fst >>> w0) -- | Same as 'context', but with a time limit. The first signal -- specifies a threshold and the second signal specifies a maximum age. -- If the current number of contexts exceeds the threshold, then all -- contexts exceeding the maximum age are deleted. -- -- Inherits inhibition and feedback behaviour from the current context's -- wire. contextLimited :: forall a b ctx m. (Ord ctx, Monad m) => Wire m (ctx, a) b -> Wire m (Int, Time, ctx, a) b contextLimited w0 = context' M.empty 0 where context' :: Map ctx (Time, Wire m (ctx, a) b) -> Time -> Wire m (Int, Time, ctx, a) b context' tm'' t' = mkGen $ \ws@(wsDTime -> dt') (limit, maxAge, ctx, x') -> do let t = t' + dt' let (dt, w') = case M.lookup ctx tm'' of Nothing -> (0, w0) Just (lt, w') -> (t - lt, w') (mx, w) <- dt `seq` toGen w' (ws { wsDTime = dt }) (ctx, x') let tm' = M.insert ctx (t, w) tm'' tm = if M.size tm' <= limit then tm' else M.filter (\(ct, _) -> t - ct <= maxAge) tm' return (mx, context' tm t) -- | Simplified variant of 'contextLimited'. Takes a context signal -- only. contextLimited_ :: (Ord ctx, Monad m) => Wire m ctx b -> Wire m (Int, Time, ctx) b contextLimited_ w0 = arr (\(thr, maxAge, ctx) -> (thr, maxAge, ctx, ())) >>> contextLimited (arr fst >>> w0) -- | Specialized version of 'contextLimited'. Use this one, if your -- contexts are 'Int's and you have a lot of them. -- -- Inherits inhibition and feedback behaviour from the current context's -- wire. contextLimitedInt :: forall a b m. Monad m => Wire m (Int, a) b -> Wire m (Int, Time, Int, a) b contextLimitedInt w0 = context' IM.empty 0 where context' :: IntMap (Time, Wire m (Int, a) b) -> Time -> Wire m (Int, Time, Int, a) b context' tm'' t' = mkGen $ \ws@(wsDTime -> dt') (limit, maxAge, ctx, x') -> do let t = t' + dt' let (dt, w') = case IM.lookup ctx tm'' of Nothing -> (0, w0) Just (lt, w') -> (t - lt, w') (mx, w) <- dt `seq` toGen w' (ws { wsDTime = dt }) (ctx, x') let tm' = IM.insert ctx (t, w) tm'' tm = if IM.size tm' <= limit then tm' else IM.filter (\(ct, _) -> t - ct <= maxAge) tm' return (mx, context' tm t) -- | Simplified variant of 'contextLimitedInt'. Takes a context signal -- only. contextLimitedInt_ :: Monad m => Wire m Int b -> Wire m (Int, Time, Int) b contextLimitedInt_ w0 = arr (\(thr, maxAge, ctx) -> (thr, maxAge, ctx, ())) >>> contextLimitedInt (arr fst >>> w0) -- | Choose a unique identifier when switching in and keep it. -- -- Never inhibits. identifier :: MonadIO m => Wire m a Int identifier = mkGen $ \ws _ -> do let reqVar = wsReqVar ws req <- liftIO . atomically $ do req' <- readTVar reqVar let req = succ req' req `seq` writeTVar reqVar (succ req') return req' return (Right req, constant req)