{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
#endif
module Reflex.Class
( module Reflex.Patch
, Reflex (..)
, mergeInt
, coerceBehavior
, coerceEvent
, coerceDynamic
, MonadSample (..)
, MonadHold (..)
, EventSelector (..)
, EventSelectorInt (..)
, constDyn
, pushAlways
, leftmost
, mergeMap
, mergeIntMap
, mergeMapIncremental
, mergeMapIncrementalWithMove
, mergeIntMapIncremental
, coincidencePatchMap
, coincidencePatchMapWithMove
, coincidencePatchIntMap
, mergeList
, mergeWith
, difference
, alignEventWithMaybe
, splitE
, fanEither
, fanThese
, fanMap
, dmapToThese
, EitherTag (..)
, eitherToDSum
, dsumToEither
, factorEvent
, filterEventKey
, switchHold
, switchHoldPromptly
, switchHoldPromptOnly
, switchHoldPromptOnlyIncremental
, tag
, tagMaybe
, attach
, attachWith
, attachWithMaybe
, gate
, distributeDMapOverDynPure
, distributeListOverDyn
, distributeListOverDynWith
, zipDyn
, zipDynWith
, Accumulator (..)
, accumDyn
, accumMDyn
, accumMaybeDyn
, accumMaybeMDyn
, mapAccumDyn
, mapAccumMDyn
, mapAccumMaybeDyn
, mapAccumMaybeMDyn
, accumB
, accumMB
, accumMaybeB
, accumMaybeMB
, mapAccumB
, mapAccumMB
, mapAccumMaybeB
, mapAccumMaybeMB
, mapAccum_
, mapAccumM_
, mapAccumMaybe_
, mapAccumMaybeM_
, accumIncremental
, accumMIncremental
, accumMaybeIncremental
, accumMaybeMIncremental
, mapAccumIncremental
, mapAccumMIncremental
, mapAccumMaybeIncremental
, mapAccumMaybeMIncremental
, zipListWithEvent
, numberOccurrences
, numberOccurrencesFrom
, numberOccurrencesFrom_
, (<@>)
, (<@)
, tailE
, headTailE
, takeWhileE
, takeWhileJustE
, dropWhileE
, takeDropWhileJustE
, switcher
, traceEvent
, traceEventWith
, unsafeDynamic
, unsafeMapIncremental
, FunctorMaybe
, mapMaybe
, fmapMaybe
, fforMaybe
, ffilter
, filterLeft
, filterRight
, ffor
, ffor2
, ffor3
, switchPromptly
, switchPromptOnly
, fmapMaybeCheap
, mapMaybeCheap
, fmapCheap
, fforCheap
, fforMaybeCheap
, pushAlwaysCheap
, tagCheap
, mergeWithCheap
, mergeWithCheap'
, slowHeadE
) where
import Control.Applicative
import Control.Monad.Identity
import Control.Monad.Reader
import Control.Monad.State.Strict
import Control.Monad.Trans.Cont (ContT)
import Control.Monad.Trans.Except (ExceptT)
import Control.Monad.Trans.RWS (RWST)
import Control.Monad.Trans.Writer (WriterT)
import Data.Align
import Data.Bifunctor
import Data.Coerce
import Data.Default
import Data.Dependent.Map (DMap, DSum (..))
import qualified Data.Dependent.Map as DMap
import Data.Functor.Compose
import Data.Functor.Product
import Data.GADT.Compare (GEq (..), GCompare (..), (:~:) (..))
import Data.FastMutableIntMap (PatchIntMap)
import Data.Foldable
import Data.Functor.Bind
import Data.Functor.Misc
import Data.Functor.Plus
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as IntMap
import Data.List.NonEmpty (NonEmpty (..))
import Data.Map (Map)
import Data.Semigroup (Semigroup, sconcat, stimes, (<>))
import Data.Some (Some)
import qualified Data.Some as Some
import Data.String
import Data.These
import Data.Type.Coercion
import Data.Witherable (Filterable(..))
import qualified Data.Witherable as W
import Reflex.FunctorMaybe (FunctorMaybe)
import qualified Reflex.FunctorMaybe
import Reflex.Patch
import qualified Reflex.Patch.MapWithMove as PatchMapWithMove
import Debug.Trace (trace)
class ( MonadHold t (PushM t)
, MonadSample t (PullM t)
, MonadFix (PushM t)
, Functor (Dynamic t)
, Applicative (Dynamic t)
, Monad (Dynamic t)
) => Reflex t where
data Behavior t :: * -> *
data Event t :: * -> *
data Dynamic t :: * -> *
data Incremental t :: * -> *
type PushM t :: * -> *
type PullM t :: * -> *
never :: Event t a
constant :: a -> Behavior t a
push :: (a -> PushM t (Maybe b)) -> Event t a -> Event t b
pushCheap :: (a -> PushM t (Maybe b)) -> Event t a -> Event t b
pull :: PullM t a -> Behavior t a
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
current :: Dynamic t a -> Behavior t a
updated :: Dynamic t a -> Event t a
unsafeBuildDynamic :: PullM t a -> Event t a -> Dynamic t a
unsafeBuildIncremental :: Patch p => PullM t (PatchTarget p) -> Event t p -> Incremental t p
mergeIncremental :: GCompare k => Incremental t (PatchDMap k (Event t)) -> Event t (DMap k Identity)
mergeIncrementalWithMove :: GCompare k => Incremental t (PatchDMapWithMove k (Event t)) -> Event t (DMap k Identity)
currentIncremental :: Patch p => Incremental t p -> Behavior t (PatchTarget p)
updatedIncremental :: Patch p => Incremental t p -> Event t p
incrementalToDynamic :: Patch p => Incremental t p -> Dynamic t (PatchTarget p)
behaviorCoercion :: Coercion a b -> Coercion (Behavior t a) (Behavior t b)
eventCoercion :: Coercion a b -> Coercion (Event t a) (Event t b)
dynamicCoercion :: Coercion a b -> Coercion (Dynamic t a) (Dynamic t b)
mergeIntIncremental :: Incremental t (PatchIntMap (Event t a)) -> Event t (IntMap a)
fanInt :: Event t (IntMap a) -> EventSelectorInt t a
mergeInt :: Reflex t => IntMap (Event t a) -> Event t (IntMap a)
mergeInt m = mergeIntIncremental $ unsafeBuildIncremental (return m) never
coerceBehavior :: (Reflex t, Coercible a b) => Behavior t a -> Behavior t b
coerceBehavior = coerceWith $ behaviorCoercion Coercion
coerceEvent :: (Reflex t, Coercible a b) => Event t a -> Event t b
coerceEvent = coerceWith $ eventCoercion Coercion
coerceDynamic :: (Reflex t, Coercible a b) => Dynamic t a -> Dynamic t b
coerceDynamic = coerceWith $ dynamicCoercion Coercion
unsafeDynamic :: Reflex t => Behavior t a -> Event t a -> Dynamic t a
unsafeDynamic = unsafeBuildDynamic . sample
constDyn :: Reflex t => a -> Dynamic t a
constDyn = pure
instance (Reflex t, Default a) => Default (Dynamic t a) where
def = pure def
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)
default hold :: (m ~ f m', MonadTrans f, MonadHold t m') => a -> Event t a -> m (Behavior t a)
hold v0 = lift . hold v0
holdDyn :: a -> Event t a -> m (Dynamic t a)
default holdDyn :: (m ~ f m', MonadTrans f, MonadHold t m') => a -> Event t a -> m (Dynamic t a)
holdDyn v0 = lift . holdDyn v0
holdIncremental :: Patch p => PatchTarget p -> Event t p -> m (Incremental t p)
default holdIncremental :: (Patch p, m ~ f m', MonadTrans f, MonadHold t m') => PatchTarget p -> Event t p -> m (Incremental t p)
holdIncremental v0 = lift . holdIncremental v0
buildDynamic :: PushM t a -> Event t a -> m (Dynamic t a)
headE :: Event t a -> m (Event t a)
accumIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> p) -> PatchTarget p -> Event t b -> m (Incremental t p)
accumIncremental f = accumMaybeIncremental $ \v o -> Just $ f v o
accumMIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> PushM t p) -> PatchTarget p -> Event t b -> m (Incremental t p)
accumMIncremental f = accumMaybeMIncremental $ \v o -> Just <$> f v o
accumMaybeIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> Maybe p) -> PatchTarget p -> Event t b -> m (Incremental t p)
accumMaybeIncremental f = accumMaybeMIncremental $ \v o -> return $ f v o
accumMaybeMIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> PushM t (Maybe p)) -> PatchTarget p -> Event t b -> m (Incremental t p)
accumMaybeMIncremental f z e = do
rec let e' = flip push e $ \o -> do
v <- sample $ currentIncremental d'
f v o
d' <- holdIncremental z e'
return d'
mapAccumIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> (p, c)) -> PatchTarget p -> Event t b -> m (Incremental t p, Event t c)
mapAccumIncremental f = mapAccumMaybeIncremental $ \v o -> bimap Just Just $ f v o
mapAccumMIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> PushM t (p, c)) -> PatchTarget p -> Event t b -> m (Incremental t p, Event t c)
mapAccumMIncremental f = mapAccumMaybeMIncremental $ \v o -> bimap Just Just <$> f v o
mapAccumMaybeIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> (Maybe p, Maybe c)) -> PatchTarget p -> Event t b -> m (Incremental t p, Event t c)
mapAccumMaybeIncremental f = mapAccumMaybeMIncremental $ \v o -> return $ f v o
mapAccumMaybeMIncremental :: (Reflex t, Patch p, MonadHold t m, MonadFix m) => (PatchTarget p -> b -> PushM t (Maybe p, Maybe c)) -> PatchTarget p -> Event t b -> m (Incremental t p, Event t c)
mapAccumMaybeMIncremental f z e = do
rec let e' = flip push e $ \o -> do
v <- sample $ currentIncremental d'
result <- f v o
return $ case result of
(Nothing, Nothing) -> Nothing
_ -> Just result
d' <- holdIncremental z $ mapMaybe fst e'
return (d', mapMaybe snd e')
slowHeadE :: (Reflex t, MonadHold t m, MonadFix m) => Event t a -> m (Event t a)
slowHeadE e = do
rec be <- hold e $ fmapCheap (const never) e'
let e' = switch be
return e'
newtype EventSelector t k = EventSelector
{
select :: forall a. k a -> Event t a
}
newtype EventSelectorInt t a = EventSelectorInt { selectInt :: Int -> 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
holdDyn a0 = lift . holdDyn a0
holdIncremental a0 = lift . holdIncremental a0
buildDynamic a0 = lift . buildDynamic a0
headE = lift . headE
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
holdDyn a0 = lift . holdDyn a0
holdIncremental a0 = lift . holdIncremental a0
buildDynamic a0 = lift . buildDynamic a0
headE = lift . headE
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
holdDyn a0 = lift . holdDyn a0
holdIncremental a0 = lift . holdIncremental a0
buildDynamic a0 = lift . buildDynamic a0
headE = lift . headE
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
holdDyn a0 = lift . holdDyn a0
holdIncremental a0 = lift . holdIncremental a0
buildDynamic a0 = lift . buildDynamic a0
headE = lift . headE
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
holdDyn a0 = lift . holdDyn a0
holdIncremental a0 = lift . holdIncremental a0
buildDynamic a0 = lift . buildDynamic a0
headE = lift . headE
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
holdDyn a0 = lift . holdDyn a0
holdIncremental a0 = lift . holdIncremental a0
buildDynamic a0 = lift . buildDynamic a0
headE = lift . headE
pushAlways :: Reflex t => (a -> PushM t b) -> Event t a -> Event t b
pushAlways f = push (fmap Just . f)
ffor :: Functor f => f a -> (a -> b) -> f b
ffor = flip fmap
ffor2 :: Applicative f => f a -> f b -> (a -> b -> c) -> f c
ffor2 a b f = liftA2 f a b
ffor3 :: Applicative f => f a -> f b -> f c -> (a -> b -> c -> d) -> f d
ffor3 a b c f = liftA3 f a b c
instance Reflex t => Applicative (Behavior t) where
pure = constant
f <*> x = pull $ sample f `ap` sample x
_ *> b = b
a <* _ = a
instance Reflex t => Apply (Behavior t) where
(<.>) = (<*>)
instance Reflex t => Bind (Behavior t) where
(>>-) = (>>=)
instance (Reflex t, Fractional a) => Fractional (Behavior t a) where
(/) = liftA2 (/)
fromRational = pure . fromRational
recip = fmap recip
instance Reflex t => Functor (Behavior t) where
fmap f = pull . fmap f . sample
instance (Reflex t, IsString a) => IsString (Behavior t a) where
fromString = pure . fromString
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, Monoid a) => Monoid (Behavior t a) where
mempty = constant mempty
mappend a b = pull $ liftM2 mappend (sample a) (sample b)
mconcat = pull . fmap mconcat . mapM sample
instance (Reflex t, Num a) => Num (Behavior t a) where
(+) = liftA2 (+)
(-) = liftA2 (-)
(*) = liftA2 (*)
abs = fmap abs
fromInteger = pure . fromInteger
negate = fmap negate
signum = fmap signum
instance (Num a, Reflex t) => Num (Dynamic t a) where
(+) = liftA2 (+)
(*) = liftA2 (*)
abs = fmap abs
signum = fmap signum
fromInteger = pure . fromInteger
negate = fmap negate
(-) = liftA2 (-)
instance (Reflex t, Semigroup a) => Semigroup (Behavior t a) where
a <> b = pull $ liftM2 (<>) (sample a) (sample b)
sconcat = pull . fmap sconcat . mapM sample
#if MIN_VERSION_semigroups(0,17,0)
stimes n = fmap $ stimes n
#else
times1p n = fmap $ times1p n
#endif
fmapMaybe :: Filterable f => (a -> Maybe b) -> f a -> f b
fmapMaybe = mapMaybe
fforMaybe :: Filterable f => f a -> (a -> Maybe b) -> f b
fforMaybe = flip mapMaybe
ffilter :: Filterable f => (a -> Bool) -> f a -> f a
ffilter = W.filter
filterLeft :: Filterable f => f (Either a b) -> f a
filterLeft = mapMaybe (either Just (const Nothing))
filterRight :: Filterable f => f (Either a b) -> f b
filterRight = mapMaybe (either (const Nothing) Just)
instance Reflex t => Alt (Event t) where
ev1 <!> ev2 = leftmost [ev1, ev2]
instance Reflex t => Apply (Event t) where
evf <.> evx = coincidence (fmap (<$> evx) evf)
instance Reflex t => Bind (Event t) where
evx >>- f = coincidence (f <$> evx)
join = coincidence
instance Reflex t => Functor (Event t) where
{-# INLINE fmap #-}
fmap f = mapMaybe $ Just . f
{-# INLINE (<$) #-}
x <$ e = fmapCheap (const x) e
instance Reflex t => FunctorMaybe (Event t) where
{-# INLINE fmapMaybe #-}
fmapMaybe = mapMaybe
instance Reflex t => Filterable (Event t) where
{-# INLINE mapMaybe #-}
mapMaybe f = push $ return . f
instance Reflex t => Plus (Event t) where
zero = never
tag :: Reflex t => Behavior t b -> Event t a -> Event t b
tag b = pushAlways $ \_ -> sample b
tagMaybe :: Reflex t => Behavior t (Maybe b) -> Event t a -> Event t b
tagMaybe b = push $ \_ -> 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 -> (`f` o) <$> sample b
tailE :: (Reflex t, MonadHold t m) => Event t a -> m (Event t a)
tailE e = snd <$> headTailE e
headTailE :: (Reflex t, MonadHold t 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)
takeWhileE
:: forall t m a
. (Reflex t, MonadFix m, MonadHold t m)
=> (a -> Bool)
-> Event t a
-> m (Event t a)
takeWhileE f = takeWhileJustE $ \v -> guard (f v) $> v
takeWhileJustE
:: forall t m a b
. (Reflex t, MonadFix m, MonadHold t m)
=> (a -> Maybe b)
-> Event t a
-> m (Event t b)
takeWhileJustE f e = do
rec let (eBad, eTrue) = fanEither $ ffor e' $ \a -> case f a of
Nothing -> Left never
Just b -> Right b
eFirstBad <- headE eBad
e' <- switchHold e eFirstBad
return eTrue
dropWhileE
:: forall t m a
. (Reflex t, MonadFix m, MonadHold t m)
=> (a -> Bool)
-> Event t a
-> m (Event t a)
dropWhileE f e = snd <$> takeDropWhileJustE (\v -> guard (f v) $> v) e
takeDropWhileJustE
:: forall t m a b
. (Reflex t, MonadFix m, MonadHold t m)
=> (a -> Maybe b)
-> Event t a
-> m (Event t b, Event t a)
takeDropWhileJustE f e = do
rec let (eBad, eGood) = fanEither $ ffor e' $ \a -> case f a of
Nothing -> Left ()
Just b -> Right b
eFirstBad <- headE eBad
e' <- switchHold e (never <$ eFirstBad)
eRest <- switchHoldPromptOnly never (e <$ eFirstBad)
return (eGood, eRest)
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
instance (Semigroup a, Reflex t) => Semigroup (Event t a) where
(<>) = alignWith (mergeThese (<>))
sconcat = fmap sconcat . mergeList . toList
#if MIN_VERSION_semigroups(0,17,0)
stimes n = fmap $ stimes n
#else
times1p n = fmap $ times1p n
#endif
instance (Semigroup a, Reflex t) => Monoid (Event t a) where
mempty = never
mappend = (<>)
mconcat = fmap sconcat . mergeList
{-# INLINE mergeWith #-}
mergeWith :: Reflex t => (a -> a -> a) -> [Event t a] -> Event t a
mergeWith = mergeWith' id
{-# INLINE mergeWith' #-}
mergeWith' :: Reflex t => (a -> b) -> (b -> b -> b) -> [Event t a] -> Event t b
mergeWith' f g es = fmap (Prelude.foldl1 g . fmap f)
. mergeInt
. IntMap.fromDistinctAscList
$ zip [0 :: Int ..] es
{-# INLINE leftmost #-}
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 = mergeWithFoldCheap' id es
unsafeMapIncremental :: (Reflex t, Patch p, Patch p') => (PatchTarget p -> PatchTarget p') -> (p -> p') -> Incremental t p -> Incremental t p'
unsafeMapIncremental f g a = unsafeBuildIncremental (fmap f $ sample $ currentIncremental a) $ g <$> updatedIncremental a
mergeMap :: (Reflex t, Ord k) => Map k (Event t a) -> Event t (Map k a)
mergeMap = fmap dmapToMap . merge . mapWithFunctorToDMap
mergeIntMap :: Reflex t => IntMap (Event t a) -> Event t (IntMap a)
mergeIntMap = fmap dmapToIntMap . merge . intMapWithFunctorToDMap
mergeMapIncremental :: (Reflex t, Ord k) => Incremental t (PatchMap k (Event t a)) -> Event t (Map k a)
mergeMapIncremental = fmap dmapToMap . mergeIncremental . unsafeMapIncremental mapWithFunctorToDMap (const2PatchDMapWith id)
mergeIntMapIncremental :: Reflex t => Incremental t (PatchIntMap (Event t a)) -> Event t (IntMap a)
mergeIntMapIncremental = fmap dmapToIntMap . mergeIncremental . unsafeMapIncremental intMapWithFunctorToDMap (const2IntPatchDMapWith id)
mergeMapIncrementalWithMove :: (Reflex t, Ord k) => Incremental t (PatchMapWithMove k (Event t a)) -> Event t (Map k a)
mergeMapIncrementalWithMove = fmap dmapToMap . mergeIncrementalWithMove . unsafeMapIncremental mapWithFunctorToDMap (const2PatchDMapWithMoveWith id)
fanEither :: Reflex t => Event t (Either a b) -> (Event t a, Event t b)
fanEither e =
let justLeft = either Just (const Nothing)
justRight = either (const Nothing) Just
in (mapMaybe justLeft e, mapMaybe justRight e)
fanThese :: Reflex t => Event t (These a b) -> (Event t a, Event t b)
fanThese e =
let this (This x) = Just x
this (These x _) = Just x
this _ = Nothing
that (That y) = Just y
that (These _ y) = Just y
that _ = Nothing
in (mapMaybe this e, mapMaybe that e)
fanMap :: (Reflex t, Ord k) => Event t (Map k a) -> EventSelector t (Const2 k a)
fanMap = fan . fmap mapToDMap
switchHold :: (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a)
switchHold ea0 eea = switch <$> hold ea0 eea
switchHoldPromptly :: (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a)
switchHoldPromptly ea0 eea = do
bea <- hold ea0 eea
let eLag = switch bea
eCoincidences = coincidence eea
return $ leftmost [eCoincidences, eLag]
switchHoldPromptOnly :: (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a)
switchHoldPromptOnly e0 e' = do
eLag <- switch <$> hold e0 e'
return $ coincidence $ leftmost [e', eLag <$ eLag]
coincidencePatchMap :: (Reflex t, Ord k) => Event t (PatchMap k (Event t v)) -> Event t (PatchMap k v)
coincidencePatchMap e = fmapCheap PatchMap $ coincidence $ ffor e $ \(PatchMap m) -> mergeMap $ ffor m $ \case
Nothing -> fmapCheap (const Nothing) e
Just ev -> leftmost [fmapCheap Just ev, fmapCheap (const Nothing) e]
coincidencePatchIntMap :: Reflex t => Event t (PatchIntMap (Event t v)) -> Event t (PatchIntMap v)
coincidencePatchIntMap e = fmapCheap PatchIntMap $ coincidence $ ffor e $ \(PatchIntMap m) -> mergeIntMap $ ffor m $ \case
Nothing -> fmapCheap (const Nothing) e
Just ev -> leftmost [fmapCheap Just ev, fmapCheap (const Nothing) e]
coincidencePatchMapWithMove :: (Reflex t, Ord k) => Event t (PatchMapWithMove k (Event t v)) -> Event t (PatchMapWithMove k v)
coincidencePatchMapWithMove e = fmapCheap unsafePatchMapWithMove $ coincidence $ ffor e $ \p -> mergeMap $ ffor (unPatchMapWithMove p) $ \ni -> case PatchMapWithMove._nodeInfo_from ni of
PatchMapWithMove.From_Delete -> fforCheap e $ \_ ->
ni { PatchMapWithMove._nodeInfo_from = PatchMapWithMove.From_Delete }
PatchMapWithMove.From_Move k -> fforCheap e $ \_ ->
ni { PatchMapWithMove._nodeInfo_from = PatchMapWithMove.From_Move k }
PatchMapWithMove.From_Insert ev -> leftmost
[ fforCheap ev $ \v ->
ni { PatchMapWithMove._nodeInfo_from = PatchMapWithMove.From_Insert v }
, fforCheap e $ \_ ->
ni { PatchMapWithMove._nodeInfo_from = PatchMapWithMove.From_Delete }
]
switchHoldPromptOnlyIncremental
:: forall t m p pt w
. ( Reflex t
, MonadHold t m
, Patch (p (Event t w))
, PatchTarget (p (Event t w)) ~ pt (Event t w)
, Patch (p w)
, PatchTarget (p w) ~ pt w
, Monoid (pt w)
)
=> (Incremental t (p (Event t w)) -> Event t (pt w))
-> (Event t (p (Event t w)) -> Event t (p w))
-> pt (Event t w)
-> Event t (p (Event t w))
-> m (Event t (pt w))
switchHoldPromptOnlyIncremental mergePatchIncremental coincidencePatch e0 e' = do
lag <- mergePatchIncremental <$> holdIncremental e0 e'
pure $ ffor (align lag (coincidencePatch e')) $ \case
This old -> old
That new -> new `applyAlways` mempty
These old new -> new `applyAlways` old
instance Reflex t => Align (Event t) where
nil = never
align = alignEventWithMaybe Just
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
instance (Reflex t, IsString a) => IsString (Dynamic t a) where
fromString = pure . fromString
zipDyn :: Reflex t => Dynamic t a -> Dynamic t b -> Dynamic t (a, b)
zipDyn = zipDynWith (,)
zipDynWith :: Reflex t => (a -> b -> c) -> Dynamic t a -> Dynamic t b -> Dynamic t c
zipDynWith f da db =
let eab = align (updated da) (updated db)
ec = flip push eab $ \o -> do
(a, b) <- case o of
This a -> do
b <- sample $ current db
return (a, b)
That b -> do
a <- sample $ current da
return (a, b)
These a b -> return (a, b)
return $ Just $ f a b
in unsafeBuildDynamic (f <$> sample (current da) <*> sample (current db)) ec
instance (Reflex t, Semigroup a) => Semigroup (Dynamic t a) where
(<>) = zipDynWith (<>)
#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 (Dynamic t a) where
mconcat = distributeListOverDynWith mconcat
mempty = constDyn mempty
mappend = zipDynWith mappend
distributeDMapOverDynPure :: forall t k. (Reflex t, GCompare k) => DMap k (Dynamic t) -> Dynamic t (DMap k Identity)
distributeDMapOverDynPure dm = case DMap.toList dm of
[] -> constDyn DMap.empty
[k :=> v] -> fmap (DMap.singleton k . Identity) v
_ ->
let getInitial = DMap.traverseWithKey (\_ -> fmap Identity . sample . current) dm
edmPre = merge $ DMap.map updated dm
result = unsafeBuildDynamic getInitial $ flip pushAlways edmPre $ \news -> do
olds <- sample $ current result
return $ DMap.unionWithKey (\_ _ new -> new) olds news
in result
distributeListOverDyn :: Reflex t => [Dynamic t a] -> Dynamic t [a]
distributeListOverDyn = distributeListOverDynWith id
distributeListOverDynWith :: Reflex t => ([a] -> b) -> [Dynamic t a] -> Dynamic t b
distributeListOverDynWith f = fmap (f . map (\(Const2 _ :=> Identity v) -> v) . DMap.toList) . distributeDMapOverDynPure . DMap.fromList . map (\(k, v) -> Const2 k :=> v) . zip [0 :: Int ..]
difference :: Reflex t => Event t a -> Event t b -> Event t a
difference = alignEventWithMaybe $ \case
This a -> Just a
_ -> Nothing
alignEventWithMaybe :: Reflex t => (These a b -> Maybe c) -> Event t a -> Event t b -> Event t c
alignEventWithMaybe f ea eb = mapMaybe (f <=< dmapToThese) $
merge $ DMap.fromList [LeftTag :=> ea, RightTag :=> eb]
filterEventKey
:: forall t m k v a.
( Reflex t
, MonadFix m
, MonadHold t m
, GEq k
)
=> k a
-> Event t (DSum k v)
-> m (Event t (v a))
filterEventKey k kv' = do
let f :: DSum k v -> Maybe (v a)
f (newK :=> newV) = case newK `geq` k of
Just Refl -> Just newV
Nothing -> Nothing
takeWhileJustE f kv'
factorEvent
:: forall t m k v a.
( Reflex t
, MonadFix m
, MonadHold t m
, GEq k
)
=> k a
-> Event t (DSum k v)
-> m (Event t (v a), Event t (DSum k (Product v (Compose (Event t) v))))
factorEvent k0 kv' = do
key :: Behavior t (Some k) <- hold (Some.This k0) $ fmapCheap (\(k :=> _) -> Some.This k) kv'
let update = flip push kv' $ \(newKey :=> newVal) -> sample key >>= \case
Some.This oldKey -> case newKey `geq` oldKey of
Just Refl -> return Nothing
Nothing -> do
newInner <- filterEventKey newKey kv'
return $ Just $ newKey :=> Pair newVal (Compose newInner)
eInitial <- filterEventKey k0 kv'
return (eInitial, update)
#if __GLASGOW_HASKELL__ < 802
{-# WARNING accum "ghc < 8.2.1 doesn't seem to be able to specialize functions in this class, which can lead to poor performance" #-}
{-# WARNING accumM "ghc < 8.2.1 doesn't seem to be able to specialize functions in this class, which can lead to poor performance" #-}
{-# WARNING accumMaybe "ghc < 8.2.1 doesn't seem to be able to specialize functions in this class, which can lead to poor performance" #-}
{-# WARNING accumMaybeM "ghc < 8.2.1 doesn't seem to be able to specialize functions in this class, which can lead to poor performance" #-}
#endif
class Reflex t => Accumulator t f | f -> t where
accum :: (MonadHold t m, MonadFix m) => (a -> b -> a) -> a -> Event t b -> m (f a)
accum f = accumMaybe $ \v o -> Just $ f v o
accumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t a) -> a -> Event t b -> m (f a)
accumM f = accumMaybeM $ \v o -> Just <$> f v o
accumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> Maybe a) -> a -> Event t b -> m (f a)
accumMaybe f = accumMaybeM $ \v o -> return $ f v o
accumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a)) -> a -> Event t b -> m (f a)
mapAccum :: (MonadHold t m, MonadFix m) => (a -> b -> (a, c)) -> a -> Event t b -> m (f a, Event t c)
mapAccum f = mapAccumMaybe $ \v o -> bimap Just Just $ f v o
mapAccumM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (a, c)) -> a -> Event t b -> m (f a, Event t c)
mapAccumM f = mapAccumMaybeM $ \v o -> bimap Just Just <$> f v o
mapAccumMaybe :: (MonadHold t m, MonadFix m) => (a -> b -> (Maybe a, Maybe c)) -> a -> Event t b -> m (f a, Event t c)
mapAccumMaybe f = mapAccumMaybeM $ \v o -> return $ f v o
mapAccumMaybeM :: (MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a, Maybe c)) -> a -> Event t b -> m (f a, Event t c)
accumDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> a)
-> a
-> Event t b
-> m (Dynamic t a)
accumDyn f = accumMaybeDyn $ \v o -> Just $ f v o
accumMDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> PushM t a)
-> a
-> Event t b
-> m (Dynamic t a)
accumMDyn f = accumMaybeMDyn $ \v o -> Just <$> f v o
accumMaybeDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> Maybe a)
-> a
-> Event t b
-> m (Dynamic t a)
accumMaybeDyn f = accumMaybeMDyn $ \v o -> return $ f v o
accumMaybeMDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> PushM t (Maybe a))
-> a
-> Event t b
-> m (Dynamic t a)
accumMaybeMDyn f z e = do
rec let e' = flip push e $ \o -> do
v <- sample $ current d'
f v o
d' <- holdDyn z e'
return d'
mapAccumDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> (a, c))
-> a
-> Event t b
-> m (Dynamic t a, Event t c)
mapAccumDyn f = mapAccumMaybeDyn $ \v o -> bimap Just Just $ f v o
mapAccumMDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> PushM t (a, c))
-> a
-> Event t b
-> m (Dynamic t a, Event t c)
mapAccumMDyn f = mapAccumMaybeMDyn $ \v o -> bimap Just Just <$> f v o
mapAccumMaybeDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> (Maybe a, Maybe c))
-> a
-> Event t b
-> m (Dynamic t a, Event t c)
mapAccumMaybeDyn f = mapAccumMaybeMDyn $ \v o -> return $ f v o
mapAccumMaybeMDyn
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> PushM t (Maybe a, Maybe c))
-> a
-> Event t b
-> m (Dynamic t a, Event t c)
mapAccumMaybeMDyn f z e = do
rec let e' = flip push e $ \o -> do
v <- sample $ current d'
result <- f v o
return $ case result of
(Nothing, Nothing) -> Nothing
_ -> Just result
d' <- holdDyn z $ mapMaybe fst e'
return (d', mapMaybe snd e')
{-# INLINE accumB #-}
accumB
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> a)
-> a
-> Event t b
-> m (Behavior t a)
accumB f = accumMaybeB $ \v o -> Just $ f v o
{-# INLINE accumMB #-}
accumMB
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> PushM t a)
-> a
-> Event t b
-> m (Behavior t a)
accumMB f = accumMaybeMB $ \v o -> Just <$> f v o
{-# INLINE accumMaybeB #-}
accumMaybeB
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> Maybe a)
-> a
-> Event t b
-> m (Behavior t a)
accumMaybeB f = accumMaybeMB $ \v o -> return $ f v o
{-# INLINE accumMaybeMB #-}
accumMaybeMB :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a)) -> a -> Event t b -> m (Behavior t a)
accumMaybeMB f z e = do
rec let e' = flip push e $ \o -> do
v <- sample d'
f v o
d' <- hold z e'
return d'
{-# INLINE mapAccumB #-}
mapAccumB
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> (a, c))
-> a
-> Event t b
-> m (Behavior t a, Event t c)
mapAccumB f = mapAccumMaybeB $ \v o -> bimap Just Just $ f v o
{-# INLINE mapAccumMB #-}
mapAccumMB
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> PushM t (a, c))
-> a
-> Event t b
-> m (Behavior t a, Event t c)
mapAccumMB f = mapAccumMaybeMB $ \v o -> bimap Just Just <$> f v o
{-# INLINE mapAccumMaybeB #-}
mapAccumMaybeB
:: (Reflex t, MonadHold t m, MonadFix m)
=> (a -> b -> (Maybe a, Maybe c))
-> a
-> Event t b
-> m (Behavior t a, Event t c)
mapAccumMaybeB f = mapAccumMaybeMB $ \v o -> return $ f v o
{-# INLINE mapAccumMaybeMB #-}
mapAccumMaybeMB :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a, Maybe c)) -> a -> Event t b -> m (Behavior t a, Event t c)
mapAccumMaybeMB f z e = do
rec let e' = flip push e $ \o -> do
v <- sample d'
result <- f v o
return $ case result of
(Nothing, Nothing) -> Nothing
_ -> Just result
d' <- hold z $ mapMaybe fst e'
return (d', mapMaybe snd e')
{-# INLINE mapAccum_ #-}
mapAccum_ :: forall t m a b c. (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> (a, c)) -> a -> Event t b -> m (Event t c)
mapAccum_ f z e = do
(_, result) <- mapAccumB f z e
return result
{-# INLINE mapAccumMaybe_ #-}
mapAccumMaybe_ :: forall t m a b c. (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> (Maybe a, Maybe c)) -> a -> Event t b -> m (Event t c)
mapAccumMaybe_ f z e = do
(_, result) <- mapAccumMaybeB f z e
return result
{-# INLINE mapAccumM_ #-}
mapAccumM_ :: forall t m a b c. (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (a, c)) -> a -> Event t b -> m (Event t c)
mapAccumM_ f z e = do
(_, result) <- mapAccumMB f z e
return result
{-# INLINE mapAccumMaybeM_ #-}
mapAccumMaybeM_ :: forall t m a b c. (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe a, Maybe c)) -> a -> Event t b -> m (Event t c)
mapAccumMaybeM_ f z e = do
(_, result) <- mapAccumMaybeMB f z e
return result
instance Reflex t => Accumulator t (Dynamic t) where
accumMaybeM = accumMaybeMDyn
mapAccumMaybeM = mapAccumMaybeMDyn
instance Reflex t => Accumulator t (Behavior t) where
accumMaybeM = accumMaybeMB
mapAccumMaybeM = mapAccumMaybeMB
instance Reflex t => Accumulator t (Event t) where
accumMaybeM f z e = updated <$> accumMaybeM f z e
mapAccumMaybeM f z e = first updated <$> mapAccumMaybeM f z e
zipListWithEvent :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> c) -> [a] -> Event t b -> m (Event t c)
zipListWithEvent f l e = do
let f' a b = case a of
h:t -> (Just t, Just $ f h b)
_ -> (Nothing, Nothing)
mapAccumMaybe_ f' l e
{-# INLINE numberOccurrences #-}
numberOccurrences :: (Reflex t, MonadHold t m, MonadFix m, Num b) => Event t a -> m (Event t (b, a))
numberOccurrences = numberOccurrencesFrom 0
{-# INLINE numberOccurrencesFrom #-}
numberOccurrencesFrom :: (Reflex t, MonadHold t m, MonadFix m, Num b) => b -> Event t a -> m (Event t (b, a))
numberOccurrencesFrom = mapAccum_ (\n a -> let !next = n + 1 in (next, (n, a)))
{-# INLINE numberOccurrencesFrom_ #-}
numberOccurrencesFrom_ :: (Reflex t, MonadHold t m, MonadFix m, Num b) => b -> Event t a -> m (Event t b)
numberOccurrencesFrom_ = mapAccum_ (\n _ -> let !next = n + 1 in (next, n))
(<@>) :: Reflex t => Behavior t (a -> b) -> Event t a -> Event t b
(<@>) b = push $ \x -> do
f <- sample b
return . Just . f $ x
infixl 4 <@>
(<@) :: (Reflex t) => Behavior t b -> Event t a -> Event t b
(<@) = tag
infixl 4 <@
{-# INLINE pushAlwaysCheap #-}
pushAlwaysCheap :: Reflex t => (a -> PushM t b) -> Event t a -> Event t b
pushAlwaysCheap f = pushCheap (fmap Just . f)
{-# INLINE mapMaybeCheap #-}
mapMaybeCheap :: Reflex t => (a -> Maybe b) -> Event t a -> Event t b
mapMaybeCheap f = pushCheap $ return . f
{-# INLINE fmapMaybeCheap #-}
fmapMaybeCheap :: Reflex t => (a -> Maybe b) -> Event t a -> Event t b
fmapMaybeCheap = mapMaybeCheap
{-# INLINE fforMaybeCheap #-}
fforMaybeCheap :: Reflex t => Event t a -> (a -> Maybe b) -> Event t b
fforMaybeCheap = flip mapMaybeCheap
{-# INLINE fforCheap #-}
fforCheap :: Reflex t => Event t a -> (a -> b) -> Event t b
fforCheap = flip fmapCheap
{-# INLINE fmapCheap #-}
fmapCheap :: Reflex t => (a -> b) -> Event t a -> Event t b
fmapCheap f = pushCheap $ return . Just . f
{-# INLINE tagCheap #-}
tagCheap :: Reflex t => Behavior t b -> Event t a -> Event t b
tagCheap b = pushAlwaysCheap $ \_ -> sample b
{-# INLINE mergeWithCheap #-}
mergeWithCheap :: Reflex t => (a -> a -> a) -> [Event t a] -> Event t a
mergeWithCheap = mergeWithCheap' id
{-# INLINE mergeWithCheap' #-}
mergeWithCheap' :: Reflex t => (a -> b) -> (b -> b -> b) -> [Event t a] -> Event t b
mergeWithCheap' f g = mergeWithFoldCheap' $ foldl1 g . fmap f
{-# INLINE mergeWithFoldCheap' #-}
mergeWithFoldCheap' :: Reflex t => (NonEmpty a -> b) -> [Event t a] -> Event t b
mergeWithFoldCheap' f es =
fmapCheap (f . (\(h : t) -> h :| t) . IntMap.elems)
. mergeInt
. IntMap.fromDistinctAscList
$ zip [0 :: Int ..] es
{-# DEPRECATED switchPromptly "Use 'switchHoldPromptly' instead. The 'switchHold*' naming convention was chosen because those functions are more closely related to each other than they are to 'switch'. " #-}
switchPromptly :: (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a)
switchPromptly = switchHoldPromptly
{-# DEPRECATED switchPromptOnly "Use 'switchHoldPromptOnly' instead. The 'switchHold*' naming convention was chosen because those functions are more closely related to each other than they are to 'switch'. " #-}
switchPromptOnly :: (Reflex t, MonadHold t m) => Event t a -> Event t (Event t a) -> m (Event t a)
switchPromptOnly = switchHoldPromptOnly