module Reflex.Class where
import Control.Applicative
import Control.Monad.Identity hiding (mapM, mapM_, forM, forM_, sequence, sequence_)
import Control.Monad.State.Strict hiding (mapM, mapM_, forM, forM_, sequence, sequence_)
import Control.Monad.Reader hiding (mapM, mapM_, forM, forM_, sequence, sequence_)
import Control.Monad.Trans.Writer (WriterT())
import Control.Monad.Trans.Except (ExceptT())
import Control.Monad.Trans.Cont (ContT())
import Control.Monad.Trans.RWS (RWST())
import Data.List.NonEmpty (NonEmpty (..))
import Data.These
import Data.Align
import Data.GADT.Compare (GEq (..), (:~:) (..))
import Data.GADT.Show (GShow (..))
import Data.Dependent.Sum (ShowTag (..))
import Data.Map (Map)
import Data.Dependent.Map (DMap, DSum (..), GCompare (..), GOrdering (..))
import qualified Data.Dependent.Map as DMap
import Data.Functor.Misc
import Data.Semigroup
import Data.Traversable
import Prelude hiding (mapM, mapM_, sequence, sequence_, foldl)
import Debug.Trace (trace)
class (MonadHold t (PushM t), MonadSample t (PullM t), MonadFix (PushM t), Functor (Event t), Functor (Behavior t)) => Reflex t where
data Behavior t :: * -> *
data Event t :: * -> *
never :: Event t a
constant :: a -> Behavior t a
push :: (a -> PushM t (Maybe b)) -> Event t a -> Event t b
type PushM t :: * -> *
pull :: PullM t a -> Behavior t a
type PullM t :: * -> *
merge :: GCompare k => DMap k (Event t) -> Event t (DMap k Identity)
fan :: GCompare k => Event t (DMap k Identity) -> EventSelector t k
switch :: Behavior t (Event t a) -> Event t a
coincidence :: Event t (Event t a) -> Event t a
class (Applicative m, Monad m) => MonadSample t m | m -> t where
sample :: Behavior t a -> m a
class MonadSample t m => MonadHold t m where
hold :: a -> Event t a -> m (Behavior t a)
newtype EventSelector t k = EventSelector { select :: forall a. k a -> Event t a }
instance MonadSample t m => MonadSample t (ReaderT r m) where
sample = lift . sample
instance MonadHold t m => MonadHold t (ReaderT r m) where
hold a0 = lift . hold a0
instance (MonadSample t m, Monoid r) => MonadSample t (WriterT r m) where
sample = lift . sample
instance (MonadHold t m, Monoid r) => MonadHold t (WriterT r m) where
hold a0 = lift . hold a0
instance MonadSample t m => MonadSample t (StateT s m) where
sample = lift . sample
instance MonadHold t m => MonadHold t (StateT s m) where
hold a0 = lift . hold a0
instance MonadSample t m => MonadSample t (ExceptT e m) where
sample = lift . sample
instance MonadHold t m => MonadHold t (ExceptT e m) where
hold a0 = lift . hold a0
instance (MonadSample t m, Monoid w) => MonadSample t (RWST r w s m) where
sample = lift . sample
instance (MonadHold t m, Monoid w) => MonadHold t (RWST r w s m) where
hold a0 = lift . hold a0
instance MonadSample t m => MonadSample t (ContT r m) where
sample = lift . sample
instance MonadHold t m => MonadHold t (ContT r m) where
hold a0 = lift . hold a0
pushAlways :: Reflex t => (a -> PushM t b) -> Event t a -> Event t b
pushAlways f = push (liftM Just . f)
ffor :: Functor f => f a -> (a -> b) -> f b
ffor = flip fmap
instance Reflex t => Functor (Behavior t) where
fmap f = pull . liftM f . sample
instance Reflex t => Applicative (Behavior t) where
pure = constant
f <*> x = pull $ sample f `ap` sample x
_ *> b = b
a <* _ = a
instance Reflex t => Monad (Behavior t) where
a >>= f = pull $ sample a >>= sample . f
return = constant
fail = error "Monad (Behavior t) does not support fail"
instance (Reflex t, Semigroup a) => Semigroup (Behavior t a) where
a <> b = pull $ liftM2 (<>) (sample a) (sample b)
sconcat = pull . liftM sconcat . mapM sample
#if MIN_VERSION_semigroups(0,17,0)
stimes n = fmap $ stimes n
#else
times1p n = fmap $ times1p n
#endif
instance (Reflex t, Monoid a) => Monoid (Behavior t a) where
mempty = constant mempty
mappend a b = pull $ liftM2 mappend (sample a) (sample b)
mconcat = pull . liftM mconcat . mapM sample
class FunctorMaybe f where
fmapMaybe :: (a -> Maybe b) -> f a -> f b
fforMaybe :: FunctorMaybe f => f a -> (a -> Maybe b) -> f b
fforMaybe = flip fmapMaybe
ffilter :: FunctorMaybe f => (a -> Bool) -> f a -> f a
ffilter f = fmapMaybe $ \x -> if f x then Just x else Nothing
instance Reflex t => FunctorMaybe (Event t) where
fmapMaybe f = push $ return . f
instance Reflex t => Functor (Event t) where
fmap f = fmapMaybe $ Just . f
zipListWithEvent :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> c) -> [a] -> Event t b -> m (Event t c)
zipListWithEvent f l e = do
rec lb <- hold l eTail
let eBoth = flip push e $ \o -> do
l' <- sample lb
return $ case l' of
(h : t) -> Just (f h o, t)
[] -> Nothing
let eTail = fmap snd eBoth
lb `seq` eBoth `seq` eTail `seq` return ()
return $ fmap fst eBoth
tag :: Reflex t => Behavior t b -> Event t a -> Event t b
tag b = pushAlways $ \_ -> sample b
attach :: Reflex t => Behavior t a -> Event t b -> Event t (a, b)
attach = attachWith (,)
attachWith :: Reflex t => (a -> b -> c) -> Behavior t a -> Event t b -> Event t c
attachWith f = attachWithMaybe $ \a b -> Just $ f a b
attachWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Behavior t a -> Event t b -> Event t c
attachWithMaybe f b e = flip push e $ \o -> liftM (flip f o) $ sample b
onceE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a)
onceE = headE
headE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a)
headE e = do
rec be <- hold e $ fmap (const never) e'
let e' = switch be
e' `seq` return ()
return e'
tailE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a)
tailE e = liftM snd $ headTailE e
headTailE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a, Event t a)
headTailE e = do
eHead <- headE e
be <- hold never $ fmap (const e) eHead
return (eHead, switch be)
splitE :: Reflex t => Event t (a, b) -> (Event t a, Event t b)
splitE e = (fmap fst e, fmap snd e)
traceEvent :: (Reflex t, Show a) => String -> Event t a -> Event t a
traceEvent s = traceEventWith $ \x -> s <> ": " <> show x
traceEventWith :: Reflex t => (a -> String) -> Event t a -> Event t a
traceEventWith f = push $ \x -> trace (f x) $ return $ Just x
data EitherTag l r a where
LeftTag :: EitherTag l r l
RightTag :: EitherTag l r r
instance GEq (EitherTag l r) where
geq a b = case (a, b) of
(LeftTag, LeftTag) -> Just Refl
(RightTag, RightTag) -> Just Refl
_ -> Nothing
instance GCompare (EitherTag l r) where
gcompare a b = case (a, b) of
(LeftTag, LeftTag) -> GEQ
(LeftTag, RightTag) -> GLT
(RightTag, LeftTag) -> GGT
(RightTag, RightTag) -> GEQ
instance GShow (EitherTag l r) where
gshowsPrec _ a = case a of
LeftTag -> showString "LeftTag"
RightTag -> showString "RightTag"
instance (Show l, Show r) => ShowTag (EitherTag l r) Identity where
showTaggedPrec t n (Identity a) = case t of
LeftTag -> showsPrec n a
RightTag -> showsPrec n a
eitherToDSum :: Either a b -> DSum (EitherTag a b) Identity
eitherToDSum = \case
Left a -> (LeftTag :=> Identity a)
Right b -> (RightTag :=> Identity b)
dsumToEither :: DSum (EitherTag a b) Identity -> Either a b
dsumToEither = \case
(LeftTag :=> Identity a) -> Left a
(RightTag :=> Identity b) -> Right b
dmapToThese :: DMap (EitherTag a b) Identity -> Maybe (These a b)
dmapToThese m = case (DMap.lookup LeftTag m, DMap.lookup RightTag m) of
(Nothing, Nothing) -> Nothing
(Just (Identity a), Nothing) -> Just $ This a
(Nothing, Just (Identity b)) -> Just $ That b
(Just (Identity a), Just (Identity b)) -> Just $ These a b
appendEvents :: (Reflex t, Monoid a) => Event t a -> Event t a -> Event t a
appendEvents e1 e2 = mergeThese mappend <$> align e1 e2
sequenceThese :: Monad m => These (m a) (m b) -> m (These a b)
sequenceThese t = case t of
This ma -> liftM This ma
These ma mb -> liftM2 These ma mb
That mb -> liftM That mb
instance (Semigroup a, Reflex t) => Monoid (Event t a) where
mempty = never
mappend a b = mconcat [a, b]
mconcat = fmap sconcat . mergeList
mergeWith :: Reflex t => (a -> a -> a) -> [Event t a] -> Event t a
mergeWith f es = fmap (Prelude.foldl1 f . map (\(Const2 _ :=> Identity v) -> v) . DMap.toList)
. merge
. DMap.fromDistinctAscList
. map (\(k, v) -> (Const2 k) :=> v)
$ zip [0 :: Int ..] es
leftmost :: Reflex t => [Event t a] -> Event t a
leftmost = mergeWith const
mergeList :: Reflex t => [Event t a] -> Event t (NonEmpty a)
mergeList [] = never
mergeList es = mergeWith (<>) $ map (fmap (:|[])) es
mergeMap :: (Reflex t, Ord k) => Map k (Event t a) -> Event t (Map k a)
mergeMap = fmap dmapToMap . merge . mapWithFunctorToDMap
fanMap :: (Reflex t, Ord k) => Event t (Map k a) -> EventSelector t (Const2 k a)
fanMap = fan . fmap mapToDMap
switchPromptly :: forall t m a. (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a)
switchPromptly ea0 eea = do
bea <- hold ea0 eea
let eLag = switch bea
eCoincidences = coincidence eea
return $ leftmost [eCoincidences, eLag]
instance Reflex t => Align (Event t) where
nil = never
align ea eb = fmapMaybe dmapToThese $ merge $ DMap.fromList [LeftTag :=> ea, RightTag :=> eb]
gate :: Reflex t => Behavior t Bool -> Event t a -> Event t a
gate = attachWithMaybe $ \allow a -> if allow then Just a else Nothing
switcher :: (Reflex t, MonadHold t m)
=> Behavior t a -> Event t (Behavior t a) -> m (Behavior t a)
switcher b eb = pull . (sample <=< sample) <$> hold b eb