module Reflex.Dom.Retractable.Class(
Retractable(..)
, morphRetractable
, MonadRetract(..)
, retractStack
) where
import Control.Monad.Fix
import Control.Monad.Reader
import Data.Sequence (Seq)
import GHC.Generics (Generic)
import Reflex
import Reflex.Network
import qualified Data.Sequence as S
data Retractable t m = Retractable {
retractableNext :: m ()
, retractablePrev :: Maybe (Dynamic t (m ()))
} deriving (Generic)
morphRetractable :: Reflex t => (forall a . n a -> m a) -> Retractable t n -> Retractable t m
morphRetractable f (Retractable next prev) = Retractable (f next) (fmap f <$> prev)
class (MonadHold t m, MonadFix m, Reflex t, Adjustable t m) => MonadRetract t m where
nextWidget :: Event t (Retractable t m) -> m (Event t ())
retract :: Event t () -> m (Event t ())
wipeRetract :: Event t (Maybe Int) -> m (Event t ())
nextWidgetEvent :: m (Event t (Retractable t m))
retractEvent :: m (Event t ())
wipeRetractEvent :: m (Event t (Maybe Int))
getRetractStack :: m (Dynamic t [Retractable t m])
withRetractStack :: Dynamic t [Retractable t m] -> m a -> m a
data StackAction t m = StackPush (Retractable t m) | StackPop | StackWipe (Maybe Int)
retractStack :: forall t m . MonadRetract t m => m () -> m (Event t ())
retractStack ma = do
nextE <- fmap StackPush <$> nextWidgetEvent
backE <- fmap (const StackPop) <$> retractEvent
wipeE <- fmap StackWipe <$> wipeRetractEvent
let actionE = leftmost [nextE, backE, wipeE]
let go :: StackAction t m -> [Retractable t m] -> [Retractable t m]
go a rs = case a of
StackPush r -> maybe rs (const $ r : rs) $ retractablePrev r
StackPop -> drop 1 rs
StackWipe Nothing -> []
StackWipe (Just i) -> drop i rs
stackD :: Dynamic t [Retractable t m] <- foldDyn go [] actionE
resD <- withRetractStack stackD $ networkHold ma $ flip push actionE $ \case
StackPush r -> pure . Just $ retractableNext r
StackPop -> do
rs <- sample . current $ stackD
case rs of
(r : _) | Just maD <- retractablePrev r -> fmap Just . sample . current $ maD
_ -> pure . Just $ ma
StackWipe _ -> pure Nothing
pure $ updated resD
instance MonadRetract t m => MonadRetract t (ReaderT r m) where
nextWidget e = do
r <- ask
lift $ nextWidget (morphRetractable (flip runReaderT r) <$> e)
{-# INLINE nextWidget #-}
retract = lift . retract
{-# INLINE retract #-}
wipeRetract = lift . wipeRetract
{-# INLINE wipeRetract #-}
nextWidgetEvent = do
e <- lift nextWidgetEvent
pure $ morphRetractable lift <$> e
{-# INLINE nextWidgetEvent #-}
retractEvent = lift retractEvent
{-# INLINE retractEvent #-}
wipeRetractEvent = lift wipeRetractEvent
{-# INLINE wipeRetractEvent #-}
getRetractStack = do
st <- lift getRetractStack
pure $ fmap (morphRetractable lift) <$> st
{-# INLINE getRetractStack #-}
withRetractStack st ma = do
r <- ask
let st' = fmap (morphRetractable (flip runReaderT r)) <$> st
lift $ withRetractStack st' (runReaderT ma r)
{-# INLINE withRetractStack #-}