Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- text :: DomBuilder t m => Text -> m ()
- dynText :: forall t m. (PostBuild t m, DomBuilder t m) => Dynamic t Text -> m ()
- comment :: DomBuilder t m => Text -> m ()
- dynComment :: forall t m. (PostBuild t m, DomBuilder t m) => Dynamic t Text -> m ()
- display :: (PostBuild t m, DomBuilder t m, Show a) => Dynamic t a -> m ()
- button :: DomBuilder t m => Text -> m (Event t ())
- dyn :: (Adjustable t m, NotReady t m, PostBuild t m) => Dynamic t (m a) -> m (Event t a)
- dyn_ :: (Adjustable t m, NotReady t m, PostBuild t m) => Dynamic t (m a) -> m ()
- widgetHold :: (Adjustable t m, MonadHold t m) => m a -> Event t (m a) -> m (Dynamic t a)
- widgetHold_ :: (Adjustable t m, MonadHold t m) => m a -> Event t (m a) -> m ()
- el :: forall t m a. DomBuilder t m => Text -> m a -> m a
- elAttr :: forall t m a. DomBuilder t m => Text -> Map Text Text -> m a -> m a
- elClass :: forall t m a. DomBuilder t m => Text -> Text -> m a -> m a
- elDynAttr :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t (Map Text Text) -> m a -> m a
- elDynClass :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t Text -> m a -> m a
- elDynAttrNS :: forall t m a. (DomBuilder t m, PostBuild t m) => Maybe Text -> Text -> Dynamic t (Map Text Text) -> m a -> m a
- el' :: forall t m a. DomBuilder t m => Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a)
- elAttr' :: forall t m a. DomBuilder t m => Text -> Map Text Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a)
- elClass' :: forall t m a. DomBuilder t m => Text -> Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a)
- elDynAttr' :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t (Map Text Text) -> m a -> m (Element EventResult (DomBuilderSpace m) t, a)
- elDynClass' :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a)
- elDynAttrNS' :: forall t m a. (DomBuilder t m, PostBuild t m) => Maybe Text -> Text -> Dynamic t (Map Text Text) -> m a -> m (Element EventResult (DomBuilderSpace m) t, a)
- dynamicAttributesToModifyAttributes :: (Ord k, PostBuild t m) => Dynamic t (Map k Text) -> m (Event t (Map k (Maybe Text)))
- dynamicAttributesToModifyAttributesWithInitial :: (Ord k, PostBuild t m) => Map k Text -> Dynamic t (Map k Text) -> m (Event t (Map k (Maybe Text)))
- newtype Link t = Link {
- _link_clicked :: Event t ()
- linkClass :: DomBuilder t m => Text -> Text -> m (Link t)
- link :: DomBuilder t m => Text -> m (Link t)
- divClass :: forall t m a. DomBuilder t m => Text -> m a -> m a
- dtdd :: forall t m a. DomBuilder t m => Text -> m a -> m a
- blank :: forall m. Monad m => m ()
- tableDynAttr :: forall t m r k v. (Ord k, DomBuilder t m, MonadHold t m, PostBuild t m, MonadFix m) => Text -> [(Text, k -> Dynamic t r -> m v)] -> Dynamic t (Map k r) -> (k -> m (Dynamic t (Map Text Text))) -> m (Dynamic t (Map k (Element EventResult (DomBuilderSpace m) t, [v])))
- tabDisplay :: forall t m k. (MonadFix m, DomBuilder t m, MonadHold t m, PostBuild t m, Ord k) => Text -> Text -> Map k (Text, m ()) -> m ()
- class HasAttributes a where
- type Attrs a :: *
- attributes :: Lens' a (Attrs a)
- module Data.Map.Misc
- module Reflex.Collection
- module Reflex.Workflow
- partitionMapBySetLT :: forall k v. Ord k => Set k -> Map k v -> Map (Either k ()) (Map k v)
Displaying Values
text :: DomBuilder t m => Text -> m () Source #
comment :: DomBuilder t m => Text -> m () Source #
dynComment :: forall t m. (PostBuild t m, DomBuilder t m) => Dynamic t Text -> m () Source #
dyn :: (Adjustable t m, NotReady t m, PostBuild t m) => Dynamic t (m a) -> m (Event t a) Source #
Given a Dynamic of widget-creating actions, create a widget that is recreated whenever the Dynamic updates.
The returned Event occurs whenever the child widget is updated, which is
at post-build in addition to the times at which the input Dynamic is
updated, and its value is the result of running the widget.
Note: Often, the type a
is an Event
, in which case the return value is an Event-of-Events that would typically be flattened (via switchHold
).
dyn_ :: (Adjustable t m, NotReady t m, PostBuild t m) => Dynamic t (m a) -> m () Source #
Like dyn
but discards result.
widgetHold :: (Adjustable t m, MonadHold t m) => m a -> Event t (m a) -> m (Dynamic t a) Source #
Given an initial widget and an Event of widget-creating actions, create a widget that is recreated whenever the Event fires.
The returned Dynamic of widget results occurs when the Event does.
Note: Often, the type a
is an Event, in which case the return value is a Dynamic-of-Events that would typically be flattened (via switchDyn
).
widgetHold_ :: (Adjustable t m, MonadHold t m) => m a -> Event t (m a) -> m () Source #
Like widgetHold
but discards result.
Creating DOM Elements
el :: forall t m a. DomBuilder t m => Text -> m a -> m a Source #
Create a DOM element
>>>
el "div" (text "Hello World")
<div>Hello World</div>
elAttr :: forall t m a. DomBuilder t m => Text -> Map Text Text -> m a -> m a Source #
Create a DOM element with attributes
>>>
elAttr "a" ("href" =: "https://reflex-frp.org") (text "Reflex-FRP!")
<a href="https://reflex-frp.org">Reflex-FRP!</a>
elClass :: forall t m a. DomBuilder t m => Text -> Text -> m a -> m a Source #
Create a DOM element with classes
>>>
elClass "div" "row" (return ())
<div class="row"></div>
elDynAttr :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t (Map Text Text) -> m a -> m a Source #
Create a DOM element with Dynamic Attributes
>>>
elClass "div" (constDyn ("class" =: "row")) (return ())
<div class="row"></div>
elDynClass :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t Text -> m a -> m a Source #
Create a DOM element with a Dynamic Class
>>>
elDynClass "div" (constDyn "row") (return ())
<div class="row"></div>
elDynAttrNS :: forall t m a. (DomBuilder t m, PostBuild t m) => Maybe Text -> Text -> Dynamic t (Map Text Text) -> m a -> m a Source #
With Element Results
el' :: forall t m a. DomBuilder t m => Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a) Source #
Create a DOM element and return the element
do (e, _) <- el' "div" (text Click) return $ domEvent Click e
elAttr' :: forall t m a. DomBuilder t m => Text -> Map Text Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a) Source #
Create a DOM element with attributes and return the element
elClass' :: forall t m a. DomBuilder t m => Text -> Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a) Source #
Create a DOM element with a class and return the element
elDynAttr' :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t (Map Text Text) -> m a -> m (Element EventResult (DomBuilderSpace m) t, a) Source #
Create a DOM element with Dynamic Attributes and return the element
elDynClass' :: forall t m a. (DomBuilder t m, PostBuild t m) => Text -> Dynamic t Text -> m a -> m (Element EventResult (DomBuilderSpace m) t, a) Source #
Create a DOM element with a Dynamic class and return the element
elDynAttrNS' :: forall t m a. (DomBuilder t m, PostBuild t m) => Maybe Text -> Text -> Dynamic t (Map Text Text) -> m a -> m (Element EventResult (DomBuilderSpace m) t, a) Source #
dynamicAttributesToModifyAttributes :: (Ord k, PostBuild t m) => Dynamic t (Map k Text) -> m (Event t (Map k (Maybe Text))) Source #
dynamicAttributesToModifyAttributesWithInitial :: (Ord k, PostBuild t m) => Map k Text -> Dynamic t (Map k Text) -> m (Event t (Map k (Maybe Text))) Source #
Specific DOM Elements
Link | |
|
divClass :: forall t m a. DomBuilder t m => Text -> m a -> m a Source #
dtdd :: forall t m a. DomBuilder t m => Text -> m a -> m a Source #
Deprecated: Use an application specific widget generating function
Tables and Lists
:: (Ord k, DomBuilder t m, MonadHold t m, PostBuild t m, MonadFix m) | |
=> Text | Class applied to table element |
-> [(Text, k -> Dynamic t r -> m v)] | Columns of (header, row key -> row value -> child widget) |
-> Dynamic t (Map k r) | Map from row key to row value |
-> (k -> m (Dynamic t (Map Text Text))) | Function to compute tr element attributes from row key |
-> m (Dynamic t (Map k (Element EventResult (DomBuilderSpace m) t, [v]))) | Map from row key to (El, list of widget return values) |
Deprecated: Use an application specific widget generating function
A widget to display a table with static columns and dynamic rows.
class HasAttributes a where Source #
attributes :: Lens' a (Attrs a) Source #
Instances
module Data.Map.Misc
module Reflex.Collection
module Reflex.Workflow
partitionMapBySetLT :: forall k v. Ord k => Set k -> Map k v -> Map (Either k ()) (Map k v) Source #
Deprecated: This will be removed in future releases.
Breaks the given Map into pieces based on the given Set. Each piece will contain only keys that are less than the key of the piece, and greater than or equal to the key of the piece with the next-smaller key. There will be one additional piece containing all keys from the original Map that are larger or equal to the largest key in the Set. Either k () is used instead of Maybe k so that the resulting map of pieces is sorted so that the additional piece has the largest key. No empty pieces will be included in the output.