module Reactive.Banana.Switch (
    
    
    
    
    Moment, AnyMoment, anyMoment, now,
    
    
    trimE, trimB,
    switchE, switchB,
    observeE, valueB,
    
    
    Identity(..),
    ) where
import Control.Applicative
import Control.Monad
import           Reactive.Banana.Combinators
import qualified Reactive.Banana.Internal.Combinators as Prim
import           Reactive.Banana.Types
newtype Identity t a = Identity { getIdentity :: a }
instance Functor (Identity t) where
    fmap f (Identity a) = Identity (f a)
newtype AnyMoment f a = AnyMoment { now :: forall t. Moment t (f t a) }
instance Functor (AnyMoment Identity) where
    fmap = liftM
instance Applicative (AnyMoment Identity) where
    pure = return
    (<*>) = ap
instance Monad (AnyMoment Identity) where
    return x = AnyMoment $ return (Identity x)
    (AnyMoment m) >>= g = AnyMoment $ m >>= \(Identity x) -> now (g x)
instance Functor (AnyMoment Behavior) where
    fmap f (AnyMoment x) = AnyMoment (fmap (fmap f) x)
instance Applicative (AnyMoment Behavior) where
    pure x  = AnyMoment $ return $ pure x
    (AnyMoment f) <*> (AnyMoment x) = AnyMoment $ liftM2 (<*>) f x
instance Functor (AnyMoment Event) where
    fmap f (AnyMoment x) = AnyMoment (fmap (fmap f) x)
anyMoment :: (forall t. Moment t (f t a)) -> AnyMoment f a
anyMoment = AnyMoment
trimE :: Event t a -> Moment t (AnyMoment Event a)
trimE = M . fmap (\x -> AnyMoment (M $ fmap E x)) . Prim.trimE . unE
trimB :: Behavior t a -> Moment t (AnyMoment Behavior a)
trimB = M . fmap (\x -> AnyMoment (M $ fmap B x)) . Prim.trimB . unB
observeE :: Event t (AnyMoment Identity a) -> Event t a
observeE = E . Prim.observeE
    . Prim.mapE (sequence . map (fmap getIdentity . unM . now)) . unE
valueB :: Behavior t a -> Moment t a
valueB = M . Prim.initialB . unB
switchE
    :: forall t a. Event t (AnyMoment Event a)
    -> Event t a
switchE = E . Prim.switchE . Prim.mapE (fmap unE . unM . now . last) . unE
switchB
    :: forall t a. Behavior t a
    -> Event t (AnyMoment Behavior a)
    -> Behavior t a
switchB b e = B $ Prim.switchB (unB b) $
    Prim.mapE (fmap unB . unM . now . last) (unE e)