miso-0.21.2.0: A tasty Haskell front-end framework

Copyright(C) 2016-2018 David M. Johnson
LicenseBSD3-style (see the file LICENSE)
MaintainerDavid M. Johnson <djohnson.m@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Miso.Html

Contents

Description

Example usage:

import Miso

data IntAction = Add | Subtract

intView :: Int -> View IntAction
intView n = div_ [ class_ "main" ] [
   btn_ [ onClick Add ] [ text_ "+" ]
 , text_ $ pack (show n)
 , btn_ [ onClick Subtract ] [ text_ "-" ]
 ]

More information on how to use miso is available on GitHub

http://github.com/dmjio/miso

Synopsis

Documentation

Core types and interface

data VTree action where Source #

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

Constructors

VNode :: {..} -> VTree action 

Fields

VText :: {..} -> VTree action 

Fields

Instances
Functor VTree Source # 
Instance details

Defined in Miso.Html.Internal

Methods

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

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

Show (VTree action) Source # 
Instance details

Defined in Miso.Html.Internal

Methods

showsPrec :: Int -> VTree action -> ShowS #

show :: VTree action -> String #

showList :: [VTree action] -> ShowS #

ToHtml (VTree action) Source #

Converting VTree to Lucid's Html

Instance details

Defined in Miso.Html.Internal

Methods

toHtml :: Monad m => VTree action -> HtmlT m () #

toHtmlRaw :: Monad m => VTree action -> HtmlT m () #

newtype View action Source #

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

Constructors

View 

Fields

Instances
Functor View Source # 
Instance details

Defined in Miso.Html.Internal

Methods

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

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

Show (View action) Source #

Show View

Instance details

Defined in Miso.Html.Internal

Methods

showsPrec :: Int -> View action -> ShowS #

show :: View action -> String #

showList :: [View action] -> ShowS #

IsString (View a) Source #

IsString instance

Instance details

Defined in Miso.Html.Internal

Methods

fromString :: String -> View a #

ToHtml (View action) Source #

Converting View to Lucid's Html

Instance details

Defined in Miso.Html.Internal

Methods

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

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

HasLink (View a :: *) Source #

For constructing type-safe links

Instance details

Defined in Miso.Html.Internal

Associated Types

type MkLink (View a) a :: * #

Methods

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

HasRouter (View a :: *) 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 :: *) b Source # 
Instance details

Defined in Miso.Html.Internal

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

Defined in Miso.Router

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

class ToView v where Source #

Convenience class for using View

Minimal complete definition

toView

Methods

toView :: v -> View action Source #

data Attribute action Source #

View Attributes to annotate DOM, converted into Events, Props, Attrs and CSS

Constructors

P MisoString Value 
E () 
Instances
Eq (Attribute action) Source # 
Instance details

Defined in Miso.Html.Internal

Methods

(==) :: Attribute action -> Attribute action -> Bool #

(/=) :: Attribute action -> Attribute action -> Bool #

Show (Attribute action) Source # 
Instance details

Defined in Miso.Html.Internal

Methods

showsPrec :: Int -> Attribute action -> ShowS #

show :: Attribute action -> String #

showList :: [Attribute action] -> ShowS #

Smart View constructors

node :: NS -> MisoString -> Maybe Key -> [Attribute action] -> [View action] -> View action Source #

VNode creation

text :: MisoString -> View action Source #

VText creation

Key patch internals

newtype Key Source #

Key for specific children patch

Constructors

Key MisoString 
Instances
Eq Key Source # 
Instance details

Defined in Miso.Html.Internal

Methods

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

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

Ord Key Source # 
Instance details

Defined in Miso.Html.Internal

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Miso.Html.Internal

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

ToKey Key Source #

Identity instance

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: Key -> Key Source #

class ToKey key where Source #

Convert type into Key, ensure Key is unique

Minimal complete definition

toKey

Methods

toKey :: key -> Key Source #

Instances
ToKey Double Source #

Convert Double to Key

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: Double -> Key Source #

ToKey Float Source #

Convert Float to Key

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: Float -> Key Source #

ToKey Int Source #

Convert Int to Key

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: Int -> Key Source #

ToKey Word Source #

Convert Word to Key

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: Word -> Key Source #

ToKey String Source #

Convert String to Key

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: String -> Key Source #

ToKey MisoString Source #

Convert Text to Key

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: MisoString -> Key Source #

ToKey Key Source #

Identity instance

Instance details

Defined in Miso.Html.Internal

Methods

toKey :: Key -> Key Source #

Namespace

data NS Source #

Namespace for element creation

Constructors

HTML

HTML Namespace

SVG

SVG Namespace

MATHML

MATHML Namespace

Instances
Eq NS Source # 
Instance details

Defined in Miso.Html.Internal

Methods

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

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

Show NS Source # 
Instance details

Defined in Miso.Html.Internal

Methods

showsPrec :: Int -> NS -> ShowS #

show :: NS -> String #

showList :: [NS] -> ShowS #

Setting properties on virtual DOM nodes

prop :: ToJSON a => MisoString -> a -> Attribute action Source #

Constructs a property on a VNode, used to set fields on a DOM Node

Setting CSS

style_ :: Map MisoString MisoString -> Attribute action Source #

Constructs CSS for a DOM Element

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 #

For defining delegated events

let clickHandler = on "click" emptyDecoder $ \() -> Action
in button_ [ clickHandler, class_ "add" ] [ text_ "+" ]

onWithOptions :: Options -> MisoString -> Decoder r -> (r -> action) -> Attribute action Source #

For defining delegated events with options

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.

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.

boolProp :: MisoString -> Bool -> Attribute action Source #

Set field to Bool value

stringProp :: MisoString -> String -> Attribute action Source #

Set field to String value

textProp :: MisoString -> MisoString -> Attribute action Source #

Set field to Text value

intProp :: MisoString -> Int -> Attribute action Source #

Set field to Int value

integerProp :: MisoString -> Int -> Attribute action Source #

Set field to Integer value

doubleProp :: MisoString -> Double -> Attribute action Source #

Set field to Double value

classList_ :: [(MisoString, Bool)] -> Attribute action Source #

Define multiple classes conditionally

div_ [ classList_ [ ("empty", null items) ] [ ]