reflex-dom-0.3: Functional Reactive Web Apps with Reflex

Safe HaskellNone
LanguageHaskell98

Reflex.Dom.Widget.Basic

Synopsis

Documentation

data ElConfig attrs Source

Instances

(~) * attrs (Map String String) => Default (ElConfig attrs) Source 
HasNamespace (ElConfig attrs) Source 
HasAttributes (ElConfig attrs) Source 
type Attrs (ElConfig attrs) = attrs Source 

elConfig_namespace :: forall attrs. Lens' (ElConfig attrs) (Maybe String) Source

elConfig_attributes :: forall attrs attrs. Lens (ElConfig attrs) (ElConfig attrs) attrs attrs Source

data El t Source

Instances

class Attributes m a where Source

Methods

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

buildEmptyElement :: (MonadWidget t m, Attributes m attrs) => String -> attrs -> m Element Source

buildElementNS :: (MonadWidget t m, Attributes m attrs) => Maybe String -> String -> attrs -> m a -> m (Element, a) Source

buildElement :: (MonadWidget t m, Attributes m attrs) => String -> attrs -> m a -> m (Element, 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

Given a Dynamic of widget-creating actions, create a widget that is recreated whenever the Dynamic updates. The returned Event of widget results occurs when the Dynamic does. Note: Often, the type a is an Event, in which case the return value is an Event-of-Events that would typically be flattened.

widgetHold :: MonadWidget 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.

widgetHoldInternal :: MonadWidget t m => m a -> Event t (m b) -> m (a, Event t b) Source

diffMapNoEq :: Ord k => Map k v -> Map k v -> Map k (Maybe v) Source

applyMap :: Ord k => Map k v -> Map k (Maybe v) -> Map k v Source

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

listWithKey' :: (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

Deprecated: listWithKey' has been renamed to listWithKeyShallowDiff; also, its behavior has changed to fix a bug where children were always rebuilt (never updated)

listWithKeyShallowDiff :: (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

Display the given map of items (in key order) using the builder function provided, and update it with the given event. Nothing update entries will delete the corresponding children, and Just entries will create them if they do not exist or send an update event to them if they do.

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

Display the given map of items using the builder function provided, and update it with the given event. Nothing entries will delete the corresponding children, and Just entries will create or replace them. Since child events do not take any signal arguments, they are always rebuilt. To update a child without rebuilding, either embed signals in the map's values, or refer to them directly in the builder function.

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

Create a dynamically-changing set of Event-valued widgets. This is like listWithKey, specialized for widgets returning (Event t a). listWithKey would return 'Dynamic t (Map k (Event t a))' in this scenario, but listViewWithKey flattens this to 'Event t (Map k a)' via switch.

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 Source

Arguments

:: (MonadWidget t m, Ord k) 
=> Dynamic t k

Current selection key

-> Dynamic t (Map k v)

Dynamic key/value map

-> (k -> Dynamic t v -> Dynamic t Bool -> m (Event t a))

Function to create a widget for a given key from Dynamic value and Dynamic Bool indicating if this widget is currently selected

-> m (Event t (k, a))

Event that fires when any child's return Event fires. Contains key of an arbitrary firing widget.

Create a dynamically-changing set of widgets, one of which is selected at any time.

selectViewListWithKey_ Source

Arguments

:: (MonadWidget t m, Ord k) 
=> Dynamic t k

Current selection key

-> Dynamic t (Map k v)

Dynamic key/value map

-> (k -> Dynamic t v -> Dynamic t Bool -> m (Event t a))

Function to create a widget for a given key from Dynamic value and Dynamic Bool indicating if this widget is currently selected

-> m (Event t k)

Event that fires when any child's return Event fires. Contains key of an arbitrary firing widget.

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

nodeClear :: IsNode self => self -> IO () Source

wrapDomEvent :: (Functor (Event t), MonadIO m, MonadSample t m, MonadReflexCreateTrigger t m, Reflex t, HasPostGui t h m) => e -> (e -> EventM e event () -> IO (IO ())) -> EventM e event 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 e event () -> IO (IO ())) -> EventM e event (Maybe a) -> m (Event t a) Source

data EventName :: EventTag -> * where Source

Constructors

Abort :: EventName AbortTag 
Blur :: EventName BlurTag 
Change :: EventName ChangeTag 
Click :: EventName ClickTag 
Contextmenu :: EventName ContextmenuTag 
Dblclick :: EventName DblclickTag 
Drag :: EventName DragTag 
Dragend :: EventName DragendTag 
Dragenter :: EventName DragenterTag 
Dragleave :: EventName DragleaveTag 
Dragover :: EventName DragoverTag 
Dragstart :: EventName DragstartTag 
Drop :: EventName DropTag 
Error :: EventName ErrorTag 
Focus :: EventName FocusTag 
Input :: EventName InputTag 
Invalid :: EventName InvalidTag 
Keydown :: EventName KeydownTag 
Keypress :: EventName KeypressTag 
Keyup :: EventName KeyupTag 
Load :: EventName LoadTag 
Mousedown :: EventName MousedownTag 
Mouseenter :: EventName MouseenterTag 
Mouseleave :: EventName MouseleaveTag 
Mousemove :: EventName MousemoveTag 
Mouseout :: EventName MouseoutTag 
Mouseover :: EventName MouseoverTag 
Mouseup :: EventName MouseupTag 
Mousewheel :: EventName MousewheelTag 
Scroll :: EventName ScrollTag 
Select :: EventName SelectTag 
Submit :: EventName SubmitTag 
Wheel :: EventName WheelTag 
Beforecut :: EventName BeforecutTag 
Cut :: EventName CutTag 
Beforecopy :: EventName BeforecopyTag 
Copy :: EventName CopyTag 
Beforepaste :: EventName BeforepasteTag 
Paste :: EventName PasteTag 
Reset :: EventName ResetTag 
Search :: EventName SearchTag 
Selectstart :: EventName SelectstartTag 
Touchstart :: EventName TouchstartTag 
Touchmove :: EventName TouchmoveTag 
Touchend :: EventName TouchendTag 
Touchcancel :: EventName TouchcancelTag 

type family EventType en Source

Equations

EventType AbortTag = UIEvent 
EventType BlurTag = FocusEvent 
EventType ChangeTag = Event 
EventType ClickTag = MouseEvent 
EventType ContextmenuTag = MouseEvent 
EventType DblclickTag = MouseEvent 
EventType DragTag = MouseEvent 
EventType DragendTag = MouseEvent 
EventType DragenterTag = MouseEvent 
EventType DragleaveTag = MouseEvent 
EventType DragoverTag = MouseEvent 
EventType DragstartTag = MouseEvent 
EventType DropTag = MouseEvent 
EventType ErrorTag = UIEvent 
EventType FocusTag = FocusEvent 
EventType InputTag = Event 
EventType InvalidTag = Event 
EventType KeydownTag = KeyboardEvent 
EventType KeypressTag = KeyboardEvent 
EventType KeyupTag = KeyboardEvent 
EventType LoadTag = UIEvent 
EventType MousedownTag = MouseEvent 
EventType MouseenterTag = MouseEvent 
EventType MouseleaveTag = MouseEvent 
EventType MousemoveTag = MouseEvent 
EventType MouseoutTag = MouseEvent 
EventType MouseoverTag = MouseEvent 
EventType MouseupTag = MouseEvent 
EventType MousewheelTag = MouseEvent 
EventType ScrollTag = UIEvent 
EventType SelectTag = UIEvent 
EventType SubmitTag = Event 
EventType WheelTag = WheelEvent 
EventType BeforecutTag = Event 
EventType CutTag = Event 
EventType BeforecopyTag = Event 
EventType CopyTag = Event 
EventType BeforepasteTag = Event 
EventType PasteTag = Event 
EventType ResetTag = Event 
EventType SearchTag = Event 
EventType SelectstartTag = Event 
EventType TouchstartTag = TouchEvent 
EventType TouchmoveTag = TouchEvent 
EventType TouchendTag = TouchEvent 
EventType TouchcancelTag = TouchEvent 

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

newtype EventResult en Source

Constructors

EventResult 

type family EventResultType en :: * Source

Equations

EventResultType ClickTag = () 
EventResultType DblclickTag = () 
EventResultType KeypressTag = Int 
EventResultType KeydownTag = Int 
EventResultType KeyupTag = Int 
EventResultType ScrollTag = Int 
EventResultType MousemoveTag = (Int, Int) 
EventResultType MousedownTag = (Int, Int) 
EventResultType MouseupTag = (Int, Int) 
EventResultType MouseenterTag = () 
EventResultType MouseleaveTag = () 
EventResultType FocusTag = () 
EventResultType BlurTag = () 
EventResultType ChangeTag = () 
EventResultType DragTag = () 
EventResultType DragendTag = () 
EventResultType DragenterTag = () 
EventResultType DragleaveTag = () 
EventResultType DragoverTag = () 
EventResultType DragstartTag = () 
EventResultType DropTag = () 
EventResultType AbortTag = () 
EventResultType ContextmenuTag = () 
EventResultType ErrorTag = () 
EventResultType InputTag = () 
EventResultType InvalidTag = () 
EventResultType LoadTag = () 
EventResultType MouseoutTag = () 
EventResultType MouseoverTag = () 
EventResultType SelectTag = () 
EventResultType SubmitTag = () 
EventResultType BeforecutTag = () 
EventResultType CutTag = () 
EventResultType BeforecopyTag = () 
EventResultType CopyTag = () 
EventResultType BeforepasteTag = () 
EventResultType PasteTag = () 
EventResultType ResetTag = () 
EventResultType SearchTag = () 
EventResultType SelectstartTag = () 
EventResultType TouchstartTag = () 
EventResultType TouchmoveTag = () 
EventResultType TouchendTag = () 
EventResultType TouchcancelTag = () 
EventResultType MousewheelTag = () 
EventResultType WheelTag = () 

wrapElement :: forall t h m. (Functor (Event t), MonadIO m, MonadSample t m, MonadReflexCreateTrigger t m, Reflex t, HasPostGui t h m) => (forall en. Element -> EventName en -> EventM Element (EventType en) (Maybe (EventResult en))) -> Element -> m (El t) Source

elWith :: (MonadWidget t m, Attributes m attrs) => String -> ElConfig attrs -> m a -> m a Source

elWith' :: (MonadWidget t m, Attributes m attrs) => String -> ElConfig attrs -> m a -> m (El t, a) Source

emptyElWith :: (MonadWidget t m, Attributes m attrs) => String -> ElConfig attrs -> m () Source

emptyElWith' :: (MonadWidget t m, Attributes m attrs) => String -> ElConfig attrs -> m (El t) Source

elDynAttrNS' :: forall t m a. MonadWidget t m => Maybe String -> String -> Dynamic t (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 (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

Create a dynamically-changing set of widgets from a Dynamic key/value map. Unlike the withKey variants, the child widgets are insensitive to which key they're associated with.

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

Create a dynamically-changing set of widgets from a Dynamic list.

data Link t Source

Constructors

Link 

Fields

_link_clicked :: Event t ()
 

class HasNamespace a where Source

Instances

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

mapWorkflow :: MonadWidget t m => (a -> b) -> Workflow t m a -> Workflow t m b 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 Source

Arguments

:: (MonadWidget t m, Show k, Ord k) 
=> String

Class applied to table element

-> [(String, 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 String String)))

Function to compute tr element attributes from row key

-> m (Dynamic t (Map k (El t, [v])))

Map from row key to (El, list of widget return values)

A widget to display a table with static columns and dynamic rows.

tabDisplay Source

Arguments

:: (MonadFix m, MonadWidget t m, Show k, Ord k) 
=> String

Class applied to ul element

-> String

Class applied to currently active li element

-> Map k (String, m ())

Map from (arbitrary) key to (tab label, child widget)

-> m () 

A widget to construct a tabbed view that shows only one of its child widgets at a time. Creates a header bar containing a ul with one li per child; clicking a li displays the corresponding child and hides all others.

unsafePlaceElement :: MonadWidget t m => Element -> 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