miso-1.8.1.0: A tasty Haskell front-end framework
Safe HaskellNone
LanguageHaskell2010

Miso.Html.Types

Synopsis

Core types and interface

newtype VTree Source #

Virtual DOM implemented as a JavaScript Object. Used for diffing, patching and event delegation. Not meant to be constructed directly, see View instead.

Constructors

VTree 

Fields

data View action Source #

Core type for constructing a VTree, use this instead of VTree directly.

Constructors

Node NS MisoString (Maybe Key) [Attribute action] [View action] 
Text MisoString 
TextRaw MisoString 

Instances

Instances details
Functor View Source # 
Instance details

Defined in Miso.Html.Types

Methods

fmap :: (a -> b) -> View a -> View b #

(<$) :: a -> View b -> View a #

IsString (View a) Source #

IsString instance

Instance details

Defined in Miso.Html.Types

Methods

fromString :: String -> View a #

ToHtml (View action) Source #

Converting View to Lucid's Html

Instance details

Defined in Miso.Html.Types

Methods

toHtml :: forall (m :: Type -> Type). Monad m => View action -> HtmlT m () #

toHtmlRaw :: forall (m :: Type -> Type). Monad m => View action -> HtmlT m () #

HasLink (View a :: Type) Source #

For constructing type-safe links

Instance details

Defined in Miso.Html.Types

Associated Types

type MkLink (View a) a #

Methods

toLink :: (Link -> a0) -> Proxy (View a) -> Link -> MkLink (View a) a0 #

HasRouter (View a :: Type) Source #

View

Instance details

Defined in Miso.Router

Associated Types

type RouteT (View a) a Source #

Methods

mkRouter :: Proxy (View a) -> Proxy a0 -> RouteT (View a) a0 -> Router a0

type MkLink (View a :: Type) b Source # 
Instance details

Defined in Miso.Html.Types

type MkLink (View a :: Type) b = MkLink (Get ('[] :: [Type]) ()) b
type RouteT (View a :: Type) x Source # 
Instance details

Defined in Miso.Router

type RouteT (View a :: Type) x = x

class ToView v where Source #

Convenience class for using View

Methods

toView :: v -> View action Source #

View runner

runView :: View action -> Sink action -> JSM VTree Source #

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.

textRaw :: MisoString -> View action Source #

TextRaw creation. Don't use directly

rawHtml :: MisoString -> View action Source #

Create a new Miso.Html.Types.TextRaw.

expandable a rawHtml node takes raw HTML and attempts to convert it to a VTree at runtime. This is a way to dynamically populate the virtual DOM from HTML received at runtime. If rawHtml cannot parse the HTML it will not render.

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) 

Instances

Instances details
Functor Attribute Source # 
Instance details

Defined in Miso.Html.Types

Methods

fmap :: (a -> b) -> Attribute a -> Attribute b #

(<$) :: a -> Attribute b -> Attribute a #

Key patch internals

newtype Key Source #

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 

Instances

Instances details
ToJSVal Key Source # 
Instance details

Defined in Miso.Html.Types

ToKey Key Source #

Identity instance

Instance details

Defined in Miso.Html.Types

Methods

toKey :: Key -> Key Source #

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.

Methods

toKey :: key -> Key Source #

Instances

Instances details
ToKey Double Source #

Convert Double to Key

Instance details

Defined in Miso.Html.Types

Methods

toKey :: Double -> Key Source #

ToKey Float Source #

Convert Float to Key

Instance details

Defined in Miso.Html.Types

Methods

toKey :: Float -> Key Source #

ToKey Int Source #

Convert Int to Key

Instance details

Defined in Miso.Html.Types

Methods

toKey :: Int -> Key Source #

ToKey Word Source #

Convert Word to Key

Instance details

Defined in Miso.Html.Types

Methods

toKey :: Word -> Key Source #

ToKey String Source #

Convert String to Key

Instance details

Defined in Miso.Html.Types

Methods

toKey :: String -> Key Source #

ToKey Text Source #

Convert Text to Key

Instance details

Defined in Miso.Html.Types

Methods

toKey :: Text -> Key Source #

ToKey JSString Source #

Convert MisoString to Key

Instance details

Defined in Miso.Html.Types

Methods

toKey :: JSString -> Key Source #

ToKey Key Source #

Identity instance

Instance details

Defined in Miso.Html.Types

Methods

toKey :: Key -> Key Source #

Namespace

data NS Source #

Namespace of DOM elements.

Constructors

HTML

HTML Namespace

SVG

SVG Namespace

MATHML

MATHML Namespace

Instances

Instances details
Eq NS Source # 
Instance details

Defined in Miso.Html.Types

Methods

(==) :: NS -> NS -> Bool #

(/=) :: NS -> NS -> Bool #

Show NS Source # 
Instance details

Defined in Miso.Html.Types

Methods

showsPrec :: Int -> NS -> ShowS #

show :: NS -> String #

showList :: [NS] -> ShowS #

ToJSVal NS Source # 
Instance details

Defined in Miso.Html.Types

Methods

toJSVal :: NS -> JSM JSVal #

toJSValListOf :: [NS] -> JSM JSVal #

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" ] [ ]

https://developer.mozilla.org/en-US/docs/Web/CSS

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!