reflex-dom-0.2: Glitch-free Functional Reactive Web Apps

Safe HaskellNone
LanguageHaskell98

Reflex.Dom.Widget.Basic

Synopsis

Documentation

data El t Source

Instances

class Attributes m a where Source

Methods

addAttributes :: IsElement e => a -> e -> m () Source

buildElement :: (MonadWidget t m, Attributes m attrs) => String -> attrs -> m a -> m (HTMLElement, a) Source

text :: MonadWidget t m => String -> m () Source

display :: (MonadWidget t m, Show a) => Dynamic t a -> m () Source

dyn :: MonadWidget t m => Dynamic t (m a) -> m (Event t a) Source

widgetHold :: MonadWidget t m => m a -> Event t (m a) -> m (Dynamic t a) Source

listWithKey :: (Ord k, MonadWidget t m) => Dynamic t (Map k v) -> (k -> Dynamic t v -> m a) -> m (Dynamic t (Map k a)) Source

listWithKey' :: forall t m k v a. (Ord k, MonadWidget t m) => Map k v -> Event t (Map k (Maybe v)) -> (k -> v -> Event t v -> m a) -> m (Dynamic t (Map k a)) Source

listViewWithKey :: (Ord k, MonadWidget t m) => Dynamic t (Map k v) -> (k -> Dynamic t v -> m (Event t a)) -> m (Event t (Map k a)) Source

listViewWithKey' :: (Ord k, MonadWidget t m) => Dynamic t (Map k v) -> (k -> Dynamic t v -> m a) -> m (Behavior t (Map k a)) Source

selectViewListWithKey_ :: forall t m k v a. (MonadWidget t m, Ord k) => Dynamic t k -> Dynamic t (Map k v) -> (k -> Dynamic t v -> Dynamic t Bool -> m (Event t a)) -> m (Event t k) Source

deleteBetweenExclusive :: (IsNode start, IsNode end) => start -> end -> IO () Source

s and e must both be children of the same node and s must precede e

deleteBetweenInclusive :: (IsNode start, IsNode end) => start -> end -> IO () Source

s and e must both be children of the same node and s must precede e

wrapDomEvent :: (Functor (Event t), MonadIO m, MonadSample t m, MonadReflexCreateTrigger t m, Reflex t, HasPostGui t h m) => e -> (e -> EventM event e () -> IO (IO ())) -> EventM event e a -> m (Event t a) Source

wrapDomEventMaybe :: (Functor (Event t), MonadIO m, MonadSample t m, MonadReflexCreateTrigger t m, Reflex t, HasPostGui t h m) => e -> (e -> EventM event e () -> IO (IO ())) -> EventM event e (Maybe a) -> m (Event t a) Source

data EventName :: EventTag -> * where Source

type family EventType en Source

onEventName :: IsElement e => EventName en -> e -> EventM (EventType en) e () -> IO (IO ()) Source

newtype EventResult en Source

Constructors

EventResult 

wrapElement :: forall t h m. (Functor (Event t), MonadIO m, MonadSample t m, MonadReflexCreateTrigger t m, Reflex t, HasPostGui t h m) => HTMLElement -> m (El t) Source

elDynAttr' :: forall t m a. MonadWidget t m => String -> Dynamic t (Map String String) -> m a -> m (El t, a) Source

elAttr :: forall t m a. MonadWidget t m => String -> Map String String -> m a -> m a Source

el' :: forall t m a. MonadWidget t m => String -> m a -> m (El t, a) Source

elAttr' :: forall t m a. MonadWidget t m => String -> Map String String -> m a -> m (El t, a) Source

elDynAttr :: forall t m a. MonadWidget t m => String -> Dynamic t (Map String String) -> m a -> m a Source

el :: forall t m a. MonadWidget t m => String -> m a -> m a Source

elClass :: forall t m a. MonadWidget t m => String -> String -> m a -> m a Source

list :: (MonadWidget t m, Ord k) => Dynamic t (Map k v) -> (Dynamic t v -> m a) -> m (Dynamic t (Map k a)) Source

simpleList :: MonadWidget t m => Dynamic t [v] -> (Dynamic t v -> m a) -> m (Dynamic t [a]) Source

data Link t Source

Constructors

Link 

Fields

_link_clicked :: Event t ()
 

class HasDomEvent t a where Source

Methods

domEvent :: EventName en -> a -> Event t (EventResultType en) Source

Instances

link :: MonadWidget t m => String -> m (Link t) Source

button :: MonadWidget t m => String -> m (Event t ()) Source

newtype Workflow t m a Source

Constructors

Workflow 

Fields

unWorkflow :: m (a, Event t (Workflow t m a))
 

workflow :: forall t m a. MonadWidget t m => Workflow t m a -> m (Dynamic t a) Source

workflowView :: forall t m a. MonadWidget t m => Workflow t m a -> m (Event t a) Source

divClass :: forall t m a. MonadWidget t m => String -> m a -> m a Source

dtdd :: forall t m a. MonadWidget t m => String -> m a -> m a Source

blank :: forall t m. MonadWidget t m => m () Source

tableDynAttr :: forall t m r k v. (MonadWidget t m, Show k, Ord k) => String -> [(String, k -> Dynamic t r -> m v)] -> Dynamic t (Map k r) -> (k -> m (Dynamic t (Map String String))) -> m (Dynamic t (Map k (El t, [v]))) Source

tabDisplay :: forall t m k. (MonadFix m, MonadWidget t m, Show k, Ord k) => String -> String -> Map k (String, m ()) -> m () Source

unsafePlaceElement :: MonadWidget t m => HTMLElement -> m (El t) Source

Place an element into the DOM and wrap it with Reflex event handlers. Note: undefined behavior may result if the element is placed multiple times, removed from the DOM after being placed, or in other situations. Don't use this unless you understand the internals of MonadWidget.

_el_clicked :: Reflex t => El t -> Event t () Source

Deprecated: Use `domEvent Click` instead

_el_keypress :: Reflex t => El t -> Event t Int Source

Deprecated: Use `domEvent Keypress` instead

_el_scrolled :: Reflex t => El t -> Event t Int Source

Deprecated: Use `domEvent Scroll` instead