Safe Haskell | None |
---|---|
Language | Haskell98 |
- (=:) :: k -> a -> Map k a
- keycodeEnter :: Int
- keycodeEscape :: Int
- class (Reflex t, MonadHold t m, MonadIO m, MonadAsyncException m, Functor m, MonadReflexCreateTrigger t m, HasDocument m, HasWebView m, HasWebView (WidgetHost m), HasWebView (GuiAction m), MonadIO (WidgetHost m), MonadAsyncException (WidgetHost m), MonadIO (GuiAction m), MonadAsyncException (GuiAction m), Functor (WidgetHost m), MonadSample t (WidgetHost m), HasPostGui t (GuiAction m) (WidgetHost m), HasPostGui t (GuiAction m) m, HasPostGui t (GuiAction m) (GuiAction m), MonadRef m, MonadRef (WidgetHost m), Ref m ~ Ref IO, Ref (WidgetHost m) ~ Ref IO, MonadFix m) => MonadWidget t m | m -> t where
- type WidgetHost m :: * -> *
- type GuiAction m :: * -> *
- askParent :: m Node
- subWidget :: Node -> m a -> m a
- subWidgetWithVoidActions :: Node -> m a -> m (a, Event t (WidgetHost m ()))
- liftWidgetHost :: WidgetHost m a -> m a
- schedulePostBuild :: WidgetHost m () -> m ()
- addVoidAction :: Event t (WidgetHost m ()) -> m ()
- getRunWidget :: IsNode n => m (n -> m a -> WidgetHost m (a, WidgetHost m (), Event t (WidgetHost m ())))
- class Monad m => HasDocument m where
- askDocument :: m HTMLDocument
- class Monad m => HasWebView m where
- askWebView :: m WebView
- newtype Restore m = Restore {}
- class Monad m => MonadIORestore m where
- askRestore :: m (Restore m)
- class (MonadRef h, Ref h ~ Ref m, MonadRef m) => HasPostGui t h m | m -> t h where
- askPostGui :: m (h () -> IO ())
- askRunWithActions :: m ([DSum (EventTrigger t)] -> h ())
- runFrameWithTriggerRef :: (HasPostGui t h m, MonadRef m, MonadIO m) => Ref m (Maybe (EventTrigger t a)) -> a -> m ()
- performEvent_ :: MonadWidget t m => Event t (WidgetHost m ()) -> m ()
- performEvent :: (MonadWidget t m, Ref m ~ Ref IO) => Event t (WidgetHost m a) -> m (Event t a)
- performEventAsync :: forall t m a. MonadWidget t m => Event t ((a -> IO ()) -> WidgetHost m ()) -> m (Event t a)
- getPostBuild :: MonadWidget t m => m (Event t ())
Documentation
class (Reflex t, MonadHold t m, MonadIO m, MonadAsyncException m, Functor m, MonadReflexCreateTrigger t m, HasDocument m, HasWebView m, HasWebView (WidgetHost m), HasWebView (GuiAction m), MonadIO (WidgetHost m), MonadAsyncException (WidgetHost m), MonadIO (GuiAction m), MonadAsyncException (GuiAction m), Functor (WidgetHost m), MonadSample t (WidgetHost m), HasPostGui t (GuiAction m) (WidgetHost m), HasPostGui t (GuiAction m) m, HasPostGui t (GuiAction m) (GuiAction m), MonadRef m, MonadRef (WidgetHost m), Ref m ~ Ref IO, Ref (WidgetHost m) ~ Ref IO, MonadFix m) => MonadWidget t m | m -> t where Source
type WidgetHost m :: * -> * Source
subWidget :: Node -> m a -> m a Source
subWidgetWithVoidActions :: Node -> m a -> m (a, Event t (WidgetHost m ())) Source
liftWidgetHost :: WidgetHost m a -> m a Source
schedulePostBuild :: WidgetHost m () -> m () Source
addVoidAction :: Event t (WidgetHost m ()) -> m () Source
getRunWidget :: IsNode n => m (n -> m a -> WidgetHost m (a, WidgetHost m (), Event t (WidgetHost m ()))) Source
MonadWidget t m => MonadWidget t (ReaderT r m) Source | |
(MonadRef m, (~) (* -> *) (Ref m) (Ref IO), MonadRef h, (~) (* -> *) (Ref h) (Ref IO), MonadIO m, MonadAsyncException m, MonadIO h, MonadAsyncException h, Functor m, ReflexHost t, MonadReflexCreateTrigger t m, MonadSample t m, MonadHold t m, MonadFix m, HasWebView h, HasPostGui t h h) => MonadWidget t (Widget t (Gui t h m)) Source |
class Monad m => HasDocument m where Source
HasDocument m => HasDocument (ReaderT r m) Source | |
HasDocument m => HasDocument (StateT r m) Source | |
HasDocument m => HasDocument (Widget t m) Source | |
Monad m => HasDocument (Gui t h m) Source |
class Monad m => HasWebView m where Source
askWebView :: m WebView Source
Monad m => HasWebView (WithWebView m) Source | |
HasWebView m => HasWebView (ReaderT r m) Source | |
HasWebView m => HasWebView (StateT r m) Source | |
HasWebView m => HasWebView (Widget t m) Source | |
Monad m => HasWebView (Gui t h m) Source |
class Monad m => MonadIORestore m where Source
askRestore :: m (Restore m) Source
MonadIORestore m => MonadIORestore (ReaderT r m) Source | |
MonadIORestore m => MonadIORestore (Gui t h m) Source |
class (MonadRef h, Ref h ~ Ref m, MonadRef m) => HasPostGui t h m | m -> t h where Source
askPostGui :: m (h () -> IO ()) Source
askRunWithActions :: m ([DSum (EventTrigger t)] -> h ()) Source
HasPostGui t h m => HasPostGui t h (ReaderT r m) Source | |
HasPostGui t h m => HasPostGui t h (Widget t m) Source | |
(MonadRef h, (~) (* -> *) (Ref h) (Ref m), MonadRef m) => HasPostGui t h (Gui t h m) Source | |
HasPostGui t h m => HasPostGui t (WithWebView h) (WithWebView m) Source |
runFrameWithTriggerRef :: (HasPostGui t h m, MonadRef m, MonadIO m) => Ref m (Maybe (EventTrigger t a)) -> a -> m () Source
performEvent_ :: MonadWidget t m => Event t (WidgetHost m ()) -> m () Source
performEvent :: (MonadWidget t m, Ref m ~ Ref IO) => Event t (WidgetHost m a) -> m (Event t a) Source
performEventAsync :: forall t m a. MonadWidget t m => Event t ((a -> IO ()) -> WidgetHost m ()) -> m (Event t a) Source
getPostBuild :: MonadWidget t m => m (Event t ()) Source