| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Miso.Html.Types
Synopsis
- newtype VTree = VTree {}
- data View action
- = Node NS MisoString (Maybe Key) [Attribute action] [View action]
- | Text MisoString
- | TextRaw MisoString
- class ToView v where
- runView :: View action -> Sink action -> JSM VTree
- node :: NS -> MisoString -> Maybe Key -> [Attribute action] -> [View action] -> View action
- text :: MisoString -> View action
- textRaw :: MisoString -> View action
- rawHtml :: MisoString -> View action
- data Attribute action
- = P MisoString Value
- | E (Sink action -> Object -> JSM ())
- | S (Map MisoString MisoString)
- newtype Key = Key MisoString
- class ToKey key where
- data NS
- prop :: ToJSON a => MisoString -> a -> Attribute action
- style_ :: Map MisoString MisoString -> Attribute action
- on :: MisoString -> Decoder r -> (r -> action) -> Attribute action
- onWithOptions :: Options -> MisoString -> Decoder r -> (r -> action) -> Attribute action
- onCreated :: action -> Attribute action
- onDestroyed :: action -> Attribute action
- onBeforeDestroyed :: action -> Attribute action
Core types and interface
Constructors
| Node NS MisoString (Maybe Key) [Attribute action] [View action] | |
| Text MisoString | |
| TextRaw MisoString |
Instances
| Functor View Source # | |
| IsString (View a) Source # |
|
Defined in Miso.Html.Types Methods fromString :: String -> View a # | |
| ToHtml (View action) Source # | |
| HasLink (View a :: Type) Source # | For constructing type-safe links |
| HasRouter (View a :: Type) Source # | View |
| type MkLink (View a :: Type) b Source # | |
| type RouteT (View a :: Type) x Source # | |
Defined in Miso.Router | |
Convenience class for using View
View runner
Smart View constructors
node :: NS -> MisoString -> Maybe Key -> [Attribute action] -> [View action] -> View action Source #
Create a new Miso.Html.Types.Node.
node ns tag key attrs children creates a new node with tag tag
and Key key in the namespace ns. All attrs are called when
the node is created and its children are initialized to children.
text :: MisoString -> View action Source #
Create a new Text with the given content.
rawHtml :: MisoString -> View action Source #
Core types and interface
data Attribute action Source #
Attribute of a vnode in a View.
The Sink callback can be used to dispatch actions which are fed back to
the update function. This is especially useful for event handlers
like the onclick attribute. The second argument represents the
vnode the attribute is attached to.
Constructors
| P MisoString Value | |
| E (Sink action -> Object -> JSM ()) | |
| S (Map MisoString MisoString) |
Key patch internals
A unique key for a dom node.
This key is only used to speed up diffing the children of a DOM node, the actual content is not important. The keys of the children of a given DOM node must be unique. Failure to satisfy this invariant gives undefined behavior at runtime.
Constructors
| Key MisoString |
class ToKey key where Source #
Convert custom key types to Key.
Instances of this class do not have to guarantee uniqueness of the
generated keys, it is up to the user to do so. toKey must be an
injective function.
Namespace
Setting properties on virtual DOM nodes
prop :: ToJSON a => MisoString -> a -> Attribute action Source #
prop k v is an attribute that will set the attribute k of the DOM node associated with the vnode
to v.
Setting css
style_ :: Map MisoString MisoString -> Attribute action Source #
style_ attrs is an attribute that will set the style
attribute of the associated DOM node to attrs.
style attributes not contained in attrs will be deleted.
import qualified Data.Map as M div_ [ style_ $ M.singleton "background" "red" ] [ ]
Handling events
on :: MisoString -> Decoder r -> (r -> action) -> Attribute action Source #
Convenience wrapper for onWithOptions defaultOptions.
let clickHandler = on "click" emptyDecoder $ \() -> Action in button_ [ clickHandler, class_ "add" ] [ text_ "+" ]
onWithOptions :: Options -> MisoString -> Decoder r -> (r -> action) -> Attribute action Source #
onWithOptions opts eventName decoder toAction is an attribute
that will set the event handler of the associated DOM node to a function that
decodes its argument using decoder, converts it to an action
using toAction and then feeds that action back to the update function.
opts can be used to disable further event propagation.
let clickHandler = onWithOptions defaultOptions "click" emptyDecoder $ \() -> Action in button_ [ clickHandler, class_ "add" ] [ text_ "+" ]
Life cycle events
onCreated :: action -> Attribute action Source #
onCreated action is an event that gets called after the actual DOM
element is created.
Important note: Any node that uses this event MUST have a unique Key,
otherwise the event may not be reliably called!
onDestroyed :: action -> Attribute action Source #
onDestroyed action is an event that gets called after the DOM element
is removed from the DOM. The action is given the DOM element that was
removed from the DOM tree.
Important note: Any node that uses this event MUST have a unique Key,
otherwise the event may not be reliably called!
onBeforeDestroyed :: action -> Attribute action Source #
onBeforeDestroyed action is an event that gets called before the DOM element
is removed from the DOM. The action is given the DOM element that was
removed from the DOM tree.
Important note: Any node that uses this event MUST have a unique Key,
otherwise the event may not be reliably called!