Copyright | (c) 2019 ATUM SOLUTIONS AG |
---|---|
License | MIT |
Maintainer | ncrashed@protonmail.com |
Stability | unstable |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Tagless final interface to the retractable stack of widgets. To use the API
drop retractStack
into your code where you want to display widgets with
history. For instance, turn all your frontend into retractable widget:
import Control.Monad import Reflex.Dom import Reflex.Dom.Retractable.Class frontend :: (MonadWidget t m, MonadRetract t m) => m () frontend = void $ retractStack $ pageA 42 pageA :: (MonadWidget t m, MonadRetract t m) => Int -> m () pageA n = do e <- button "Go page B" void $ nextWidget $ ffor e $ const Retractable { retractableNext = pageB $ n + 1 , retractablePrev = Just $ pure $ pageA n } pageB :: (MonadWidget t m, MonadRetract t m) => Int -> m () pageB n = do e <- button "Go page A" void $ nextWidget $ ffor e $ const Retractable { retractableNext = pageA $ n + 1 , retractablePrev = Just $ pure $ pageB n }
Synopsis
- data Retractable t m = Retractable {
- retractableNext :: m ()
- retractablePrev :: Maybe (Dynamic t (m ()))
- morphRetractable :: Reflex t => (forall a. n a -> m a) -> Retractable t n -> Retractable t m
- 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
- retractStack :: forall t m. MonadRetract t m => m () -> m (Event t ())
Documentation
data Retractable t m Source #
Information about widget that attaches information how to return to the widget.
Retractable | |
|
Instances
Generic (Retractable t m) Source # | |
Defined in Reflex.Dom.Retractable.Class type Rep (Retractable t m) :: Type -> Type # from :: Retractable t m -> Rep (Retractable t m) x # to :: Rep (Retractable t m) x -> Retractable t m # | |
type Rep (Retractable t m) Source # | |
Defined in Reflex.Dom.Retractable.Class type Rep (Retractable t m) = D1 (MetaData "Retractable" "Reflex.Dom.Retractable.Class" "reflex-dom-retractable-0.1.7.0-inplace" False) (C1 (MetaCons "Retractable" PrefixI True) (S1 (MetaSel (Just "retractableNext") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (m ())) :*: S1 (MetaSel (Just "retractablePrev") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Dynamic t (m ())))))) |
morphRetractable :: Reflex t => (forall a. n a -> m a) -> Retractable t n -> Retractable t m Source #
Helper to transform underlying monad in Retractable
class (MonadHold t m, MonadFix m, Reflex t, Adjustable t m) => MonadRetract t m where Source #
Defines context of widget that can switch control to next widget and can be returned back with preserving of state.
nextWidget :: Event t (Retractable t m) -> m (Event t ()) Source #
Switch current widget to the next widget. Returns event that fires when the switching is about to happen.
retract :: Event t () -> m (Event t ()) Source #
Switch to previous widget in stack. Returns event that fires when the switchin is about to happen.
wipeRetract :: Event t (Maybe Int) -> m (Event t ()) Source #
Wipe retract history to the given amount of items (or all if Nothing
is passed).
Returns event that fires when the history was changed.
nextWidgetEvent :: m (Event t (Retractable t m)) Source #
Get event that fires when any of input events in nextWidget
is triggered.
It's used for implementation of retractable stack.
retractEvent :: m (Event t ()) Source #
Get event that fires when any of input events in retract
is triggered.
It's used for implementation of retractable stack.
wipeRetractEvent :: m (Event t (Maybe Int)) Source #
Get event that fires when any of input events in wipeRetract
is triggered.
It's used for implementation of retractable stack.
getRetractStack :: m (Dynamic t [Retractable t m]) Source #
Get current stack of widget history
withRetractStack :: Dynamic t [Retractable t m] -> m a -> m a Source #
Execute subcomputation with given widget history. Affects results of getRetractStack
.
Instances
retractStack :: forall t m. MonadRetract t m => m () -> m (Event t ()) Source #
All body of the widget will be rerendered when some subcomputation emits switching event.
Plug the function somewhere close to the root of your reflex frontend and use functions from
MonadRetract
class to control switching content of the widget.