{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
#endif
module Reflex.Network
( networkView
, networkHold
, untilReady
) where
import Reflex.Class
import Reflex.Adjustable.Class
import Reflex.NotReady.Class
import Reflex.PostBuild.Class
networkView :: (NotReady t m, Adjustable t m, PostBuild t m) => Dynamic t (m a) -> m (Event t a)
networkView :: Dynamic t (m a) -> m (Event t a)
networkView child :: Dynamic t (m a)
child = do
Event t ()
postBuild <- m (Event t ())
forall t (m :: * -> *). PostBuild t m => m (Event t ())
getPostBuild
let newChild :: Event t (m a)
newChild = [Event t (m a)] -> Event t (m a)
forall k (t :: k) a. Reflex t => [Event t a] -> Event t a
leftmost [Dynamic t (m a) -> Event t (m a)
forall k (t :: k) a. Reflex t => Dynamic t a -> Event t a
updated Dynamic t (m a)
child, Behavior t (m a) -> Event t () -> Event t (m a)
forall k (t :: k) b a.
Reflex t =>
Behavior t b -> Event t a -> Event t b
tagCheap (Dynamic t (m a) -> Behavior t (m a)
forall k (t :: k) a. Reflex t => Dynamic t a -> Behavior t a
current Dynamic t (m a)
child) Event t ()
postBuild]
((), Event t a) -> Event t a
forall a b. (a, b) -> b
snd (((), Event t a) -> Event t a)
-> m ((), Event t a) -> m (Event t a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m () -> Event t (m a) -> m ((), Event t a)
forall t (m :: * -> *) a b.
Adjustable t m =>
m a -> Event t (m b) -> m (a, Event t b)
runWithReplace m ()
forall t (m :: * -> *). NotReady t m => m ()
notReady Event t (m a)
newChild
networkHold :: (Adjustable t m, MonadHold t m) => m a -> Event t (m a) -> m (Dynamic t a)
networkHold :: m a -> Event t (m a) -> m (Dynamic t a)
networkHold child0 :: m a
child0 newChild :: Event t (m a)
newChild = do
(result0 :: a
result0, newResult :: Event t a
newResult) <- m a -> Event t (m a) -> m (a, Event t a)
forall t (m :: * -> *) a b.
Adjustable t m =>
m a -> Event t (m b) -> m (a, Event t b)
runWithReplace m a
child0 Event t (m a)
newChild
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 a
result0 Event t a
newResult
untilReady :: (Adjustable t m, PostBuild t m) => m a -> m b -> m (a, Event t b)
untilReady :: m a -> m b -> m (a, Event t b)
untilReady a :: m a
a b :: m b
b = do
Event t ()
postBuild <- m (Event t ())
forall t (m :: * -> *). PostBuild t m => m (Event t ())
getPostBuild
m a -> Event t (m b) -> m (a, Event t b)
forall t (m :: * -> *) a b.
Adjustable t m =>
m a -> Event t (m b) -> m (a, Event t b)
runWithReplace m a
a (Event t (m b) -> m (a, Event t b))
-> Event t (m b) -> m (a, Event t b)
forall a b. (a -> b) -> a -> b
$ m b
b m b -> Event t () -> Event t (m b)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Event t ()
postBuild