{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#ifdef USE_REFLEX_OPTIMIZER
{-# OPTIONS_GHC -fplugin=Reflex.Optimizer #-}
#endif
module Reflex.Dynamic
(
Dynamic
, current
, updated
, holdDyn
, mapDynM
, forDynM
, constDyn
, count
, toggle
, switchDyn
, switchPromptlyDyn
, tagPromptlyDyn
, attachPromptlyDyn
, attachPromptlyDynWith
, attachPromptlyDynWithMaybe
, maybeDyn
, eitherDyn
, factorDyn
, scanDyn
, scanDynMaybe
, holdUniqDyn
, holdUniqDynBy
, improvingMaybe
, foldDyn
, foldDynM
, foldDynMaybe
, foldDynMaybeM
, joinDynThroughMap
, traceDyn
, traceDynWith
, splitDynPure
, distributeMapOverDynPure
, distributeDMapOverDynPure
, distributeListOverDynPure
, Demux
, demux
, demuxed
, HList (..)
, FHList (..)
, collectDynPure
, RebuildSortedHList (..)
, IsHList (..)
, AllAreFunctors (..)
, HListPtr (..)
, distributeFHListOverDynPure
, unsafeDynamic
) where
import Data.Functor.Compose
import Data.Functor.Misc
import Reflex.Class
import Control.Monad
import Control.Monad.Fix
import Control.Monad.Identity
import Data.Align
import Data.Dependent.Map (DMap)
import qualified Data.Dependent.Map as DMap
import Data.Dependent.Sum (DSum (..))
import Data.GADT.Compare ((:~:) (..), GCompare (..), GEq (..), GOrdering (..))
import Data.Map (Map)
import Data.Maybe
import Data.Monoid ((<>))
import Data.These
import Debug.Trace
mapDynM :: forall t m a b. (Reflex t, MonadHold t m) => (forall m'. MonadSample t m' => a -> m' b) -> Dynamic t a -> m (Dynamic t b)
mapDynM f d = buildDynamic (f =<< sample (current d)) $ pushAlways f (updated d)
forDynM :: forall t m a b. (Reflex t, MonadHold t m) => Dynamic t a -> (forall m'. MonadSample t m' => a -> m' b) -> m (Dynamic t b)
forDynM d f = mapDynM f d
holdUniqDyn :: (Reflex t, MonadHold t m, MonadFix m, Eq a) => Dynamic t a -> m (Dynamic t a)
holdUniqDyn = holdUniqDynBy (==)
holdUniqDynBy :: (Reflex t, MonadHold t m, MonadFix m) => (a -> a -> Bool) -> Dynamic t a -> m (Dynamic t a)
holdUniqDynBy eq = scanDynMaybe id (\new old -> if new `eq` old then Nothing else Just new)
improvingMaybe :: (Reflex t, MonadHold t m, MonadFix m) => Dynamic t (Maybe a) -> m (Dynamic t (Maybe a))
improvingMaybe = scanDynMaybe id (\new _ -> if isJust new then Just new else Nothing)
scanDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b) -> (a -> b -> b) -> Dynamic t a -> m (Dynamic t b)
scanDyn z f = scanDynMaybe z (\a b -> Just $ f a b)
scanDynMaybe :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b) -> (a -> b -> Maybe b) -> Dynamic t a -> m (Dynamic t b)
scanDynMaybe z f d = do
rec d' <- buildDynamic (z <$> sample (current d)) $ flip push (updated d) $ \a -> do
b <- sample $ current d'
return $ f a b
return d'
foldDyn :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> b) -> b -> Event t a -> m (Dynamic t b)
foldDyn = accumDyn . flip
foldDynM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t b) -> b -> Event t a -> m (Dynamic t b)
foldDynM = accumMDyn . flip
foldDynMaybe :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> Maybe b) -> b -> Event t a -> m (Dynamic t b)
foldDynMaybe = accumMaybeDyn . flip
foldDynMaybeM :: (Reflex t, MonadHold t m, MonadFix m) => (a -> b -> PushM t (Maybe b)) -> b -> Event t a -> m (Dynamic t b)
foldDynMaybeM = accumMaybeMDyn . flip
count :: (Reflex t, MonadHold t m, MonadFix m, Num b) => Event t a -> m (Dynamic t b)
count e = holdDyn 0 =<< zipListWithEvent const (iterate (+1) 1) e
toggle :: (Reflex t, MonadHold t m, MonadFix m) => Bool -> Event t a -> m (Dynamic t Bool)
toggle = foldDyn (const not)
switchDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a
switchDyn d = switch (current d)
switchPromptlyDyn :: forall t a. Reflex t => Dynamic t (Event t a) -> Event t a
switchPromptlyDyn de =
let eLag = switch $ current de
eCoincidences = coincidence $ updated de
in leftmost [eCoincidences, eLag]
splitDynPure :: Reflex t => Dynamic t (a, b) -> (Dynamic t a, Dynamic t b)
splitDynPure d = (fmap fst d, fmap snd d)
distributeMapOverDynPure :: (Reflex t, Ord k) => Map k (Dynamic t v) -> Dynamic t (Map k v)
distributeMapOverDynPure = fmap dmapToMap . distributeDMapOverDynPure . mapWithFunctorToDMap
{-# DEPRECATED distributeListOverDynPure "Use 'distributeListOverDyn' instead" #-}
distributeListOverDynPure :: Reflex t => [Dynamic t v] -> Dynamic t [v]
distributeListOverDynPure = distributeListOverDyn
joinDynThroughMap :: forall t k a. (Reflex t, Ord k) => Dynamic t (Map k (Dynamic t a)) -> Dynamic t (Map k a)
joinDynThroughMap = (distributeMapOverDynPure =<<)
traceDyn :: (Reflex t, Show a) => String -> Dynamic t a -> Dynamic t a
traceDyn s = traceDynWith $ \x -> s <> ": " <> show x
traceDynWith :: Reflex t => (a -> String) -> Dynamic t a -> Dynamic t a
traceDynWith f d =
let e' = traceEventWith f $ updated d
getV0 = do
x <- sample $ current d
trace (f x) $ return x
in unsafeBuildDynamic getV0 e'
tagPromptlyDyn :: Reflex t => Dynamic t a -> Event t b -> Event t a
tagPromptlyDyn = attachPromptlyDynWith const
attachPromptlyDyn :: Reflex t => Dynamic t a -> Event t b -> Event t (a, b)
attachPromptlyDyn = attachPromptlyDynWith (,)
attachPromptlyDynWith :: Reflex t => (a -> b -> c) -> Dynamic t a -> Event t b -> Event t c
attachPromptlyDynWith f = attachPromptlyDynWithMaybe $ \a b -> Just $ f a b
attachPromptlyDynWithMaybe :: Reflex t => (a -> b -> Maybe c) -> Dynamic t a -> Event t b -> Event t c
attachPromptlyDynWithMaybe f d e =
let e' = attach (current d) e
in fforMaybe (align e' $ updated d) $ \case
This (a, b) -> f a b
These (_, b) a -> f a b
That _ -> Nothing
maybeDyn :: forall t a m. (Reflex t, MonadFix m, MonadHold t m) => Dynamic t (Maybe a) -> m (Dynamic t (Maybe (Dynamic t a)))
maybeDyn = fmap (fmap unpack) . eitherDyn . fmap pack
where pack = \case
Nothing -> Left ()
Just a -> Right a
unpack = \case
Left _ -> Nothing
Right a -> Just a
eitherDyn :: forall t a b m. (Reflex t, MonadFix m, MonadHold t m) => Dynamic t (Either a b) -> m (Dynamic t (Either (Dynamic t a) (Dynamic t b)))
eitherDyn = fmap (fmap unpack) . factorDyn . fmap eitherToDSum
where unpack :: DSum (EitherTag a b) (Compose (Dynamic t) Identity) -> Either (Dynamic t a) (Dynamic t b)
unpack = \case
LeftTag :=> Compose a -> Left $ coerceDynamic a
RightTag :=> Compose b -> Right $ coerceDynamic b
factorDyn :: forall t m k v. (Reflex t, MonadHold t m, GEq k)
=> Dynamic t (DSum k v) -> m (Dynamic t (DSum k (Compose (Dynamic t) v)))
factorDyn d = buildDynamic (sample (current d) >>= holdKey) update where
update :: Event t (DSum k (Compose (Dynamic t) v))
update = flip push (updated d) $ \(newKey :=> newVal) -> do
(oldKey :=> _) <- sample (current d)
case newKey `geq` oldKey of
Just Refl -> return Nothing
Nothing -> Just <$> holdKey (newKey :=> newVal)
holdKey (k :=> v) = do
inner' <- filterEventKey k (updated d)
inner <- holdDyn v inner'
return $ k :=> Compose inner
data Demux t k = Demux { demuxValue :: Behavior t k
, demuxSelector :: EventSelector t (Const2 k Bool)
}
demux :: (Reflex t, Ord k) => Dynamic t k -> Demux t k
demux k = Demux (current k)
(fan $ attachWith (\k0 k1 -> if k0 == k1
then DMap.empty
else DMap.fromList [Const2 k0 :=> Identity False,
Const2 k1 :=> Identity True])
(current k) (updated k))
demuxed :: (Reflex t, Eq k) => Demux t k -> k -> Dynamic t Bool
demuxed d k =
let e = select (demuxSelector d) (Const2 k)
in unsafeBuildDynamic (fmap (==k) $ sample $ demuxValue d) e
data HList (l::[*]) where
HNil :: HList '[]
HCons :: e -> HList l -> HList (e ': l)
infixr 2 `HCons`
type family HRevApp (l1 :: [k]) (l2 :: [k]) :: [k]
type instance HRevApp '[] l = l
type instance HRevApp (e ': l) l' = HRevApp l (e ': l')
hRevApp :: HList l1 -> HList l2 -> HList (HRevApp l1 l2)
hRevApp HNil l = l
hRevApp (HCons x l) l' = hRevApp l (HCons x l')
hReverse :: HList l -> HList (HRevApp l '[])
hReverse l = hRevApp l HNil
hBuild :: (HBuild' '[] r) => r
hBuild = hBuild' HNil
class HBuild' l r where
hBuild' :: HList l -> r
instance (l' ~ HRevApp l '[])
=> HBuild' l (HList l') where
hBuild' = hReverse
instance HBuild' (a ': l) r
=> HBuild' l (a->r) where
hBuild' l x = hBuild' (HCons x l)
data FHList f l where
FHNil :: FHList f '[]
FHCons :: f e -> FHList f l -> FHList f (e ': l)
instance GEq (HListPtr l) where
HHeadPtr `geq` HHeadPtr = Just Refl
HHeadPtr `geq` HTailPtr _ = Nothing
HTailPtr _ `geq` HHeadPtr = Nothing
HTailPtr a `geq` HTailPtr b = a `geq` b
instance GCompare (HListPtr l) where
HHeadPtr `gcompare` HHeadPtr = GEQ
HHeadPtr `gcompare` HTailPtr _ = GLT
HTailPtr _ `gcompare` HHeadPtr = GGT
HTailPtr a `gcompare` HTailPtr b = a `gcompare` b
data HListPtr l a where
HHeadPtr :: HListPtr (h ': t) h
HTailPtr :: HListPtr t a -> HListPtr (h ': t) a
deriving instance Eq (HListPtr l a)
deriving instance Ord (HListPtr l a)
fhlistToDMap :: forall (f :: * -> *) l. FHList f l -> DMap (HListPtr l) f
fhlistToDMap = DMap.fromList . go
where go :: forall l'. FHList f l' -> [DSum (HListPtr l') f]
go = \case
FHNil -> []
FHCons h t -> (HHeadPtr :=> h) : map (\(p :=> v) -> HTailPtr p :=> v) (go t)
class RebuildSortedHList l where
rebuildSortedFHList :: [DSum (HListPtr l) f] -> FHList f l
rebuildSortedHList :: [DSum (HListPtr l) Identity] -> HList l
instance RebuildSortedHList '[] where
rebuildSortedFHList l = case l of
[] -> FHNil
_ : _ -> error "rebuildSortedFHList{'[]}: empty list expected"
rebuildSortedHList l = case l of
[] -> HNil
_ : _ -> error "rebuildSortedHList{'[]}: empty list expected"
instance RebuildSortedHList t => RebuildSortedHList (h ': t) where
rebuildSortedFHList l = case l of
((HHeadPtr :=> h) : t) -> FHCons h . rebuildSortedFHList . map (\(HTailPtr p :=> v) -> p :=> v) $ t
_ -> error "rebuildSortedFHList{h':t}: non-empty list with HHeadPtr expected"
rebuildSortedHList l = case l of
((HHeadPtr :=> Identity h) : t) -> HCons h . rebuildSortedHList . map (\(HTailPtr p :=> v) -> p :=> v) $ t
_ -> error "rebuildSortedHList{h':t}: non-empty list with HHeadPtr expected"
dmapToHList :: forall l. RebuildSortedHList l => DMap (HListPtr l) Identity -> HList l
dmapToHList = rebuildSortedHList . DMap.toList
distributeFHListOverDynPure :: (Reflex t, RebuildSortedHList l) => FHList (Dynamic t) l -> Dynamic t (HList l)
distributeFHListOverDynPure l = fmap dmapToHList $ distributeDMapOverDynPure $ fhlistToDMap l
class AllAreFunctors (f :: a -> *) (l :: [a]) where
type FunctorList f l :: [*]
toFHList :: HList (FunctorList f l) -> FHList f l
fromFHList :: FHList f l -> HList (FunctorList f l)
instance AllAreFunctors f '[] where
type FunctorList f '[] = '[]
toFHList l = case l of
HNil -> FHNil
#if !defined(__GLASGOW_HASKELL__) || __GLASGOW_HASKELL__ < 800
_ -> error "toFHList: impossible"
#endif
fromFHList FHNil = HNil
instance AllAreFunctors f t => AllAreFunctors f (h ': t) where
type FunctorList f (h ': t) = f h ': FunctorList f t
toFHList l = case l of
a `HCons` b -> a `FHCons` toFHList b
#if !defined(__GLASGOW_HASKELL__) || __GLASGOW_HASKELL__ < 800
_ -> error "toFHList: impossible"
#endif
fromFHList (a `FHCons` b) = a `HCons` fromFHList b
collectDynPure :: ( RebuildSortedHList (HListElems b)
, IsHList a, IsHList b
, AllAreFunctors (Dynamic t) (HListElems b)
, Reflex t
, HListElems a ~ FunctorList (Dynamic t) (HListElems b)
) => a -> Dynamic t b
collectDynPure ds = fmap fromHList $ distributeFHListOverDynPure $ toFHList $ toHList ds
class IsHList a where
type HListElems a :: [*]
toHList :: a -> HList (HListElems a)
fromHList :: HList (HListElems a) -> a
instance IsHList (a, b) where
type HListElems (a, b) = [a, b]
toHList (a, b) = hBuild a b
fromHList l = case l of
a `HCons` b `HCons` HNil -> (a, b)
#if !defined(__GLASGOW_HASKELL__) || __GLASGOW_HASKELL__ < 800
_ -> error "fromHList: impossible"
#endif
instance IsHList (a, b, c, d) where
type HListElems (a, b, c, d) = [a, b, c, d]
toHList (a, b, c, d) = hBuild a b c d
fromHList l = case l of
a `HCons` b `HCons` c `HCons` d `HCons` HNil -> (a, b, c, d)
#if !defined(__GLASGOW_HASKELL__) || __GLASGOW_HASKELL__ < 800
_ -> error "fromHList: impossible"
#endif
instance IsHList (a, b, c, d, e, f) where
type HListElems (a, b, c, d, e, f) = [a, b, c, d, e, f]
toHList (a, b, c, d, e, f) = hBuild a b c d e f
fromHList l = case l of
a `HCons` b `HCons` c `HCons` d `HCons` e `HCons` f `HCons` HNil -> (a, b, c, d, e, f)
#if !defined(__GLASGOW_HASKELL__) || __GLASGOW_HASKELL__ < 800
_ -> error "fromHList: impossible"
#endif