miso-0.1.0.0: Haskell front-end framework

Copyright(C) 2016-2017 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 model 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 model 

Fields

VText :: {..} -> VTree model 

Fields

Instances

Show (VTree model) Source # 

Methods

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

show :: VTree model -> String #

showList :: [VTree model] -> ShowS #

ToHtml (VTree model) Source #

Converting VTree to Lucid's Html

Methods

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

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

newtype View model Source #

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

Constructors

View 

Fields

Instances

Show (View model) Source #

Show View

Methods

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

show :: View model -> String #

showList :: [View model] -> ShowS #

ToHtml (View model) Source #

Converting View to Lucid's Html

Methods

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

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

class ToView v where Source #

Convenience class for using View

Minimal complete definition

toView

Methods

toView :: v -> View model Source #

data Attribute model Source #

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

Smart View constructors

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

VNode creation

text :: ToMisoString str => str -> View model Source #

VText creation

Key patch internals

newtype Key Source #

Key for specific children patch

Constructors

Key MisoString 

Instances

Eq Key Source # 

Methods

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

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

Ord Key Source # 

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 # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

ToKey Key Source #

Identity instance

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

Methods

toKey :: Double -> Key Source #

ToKey Float Source #

Convert Float to Key

Methods

toKey :: Float -> Key Source #

ToKey Int Source #

Convert Int to Key

Methods

toKey :: Int -> Key Source #

ToKey Word Source #

Convert Word to Key

Methods

toKey :: Word -> Key Source #

ToKey String Source #

Convert String to Key

Methods

toKey :: String -> Key Source #

ToKey MisoString Source #

Convert Text to Key

Methods

toKey :: MisoString -> Key Source #

ToKey Key Source #

Identity instance

Methods

toKey :: Key -> Key Source #

Namespace

data NS Source #

Namespace for element creation

Constructors

HTML

HTML Namespace

SVG

SVG Namespace

Instances

Eq NS Source # 

Methods

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

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

Show NS Source # 

Methods

showsPrec :: Int -> NS -> ShowS #

show :: NS -> String #

showList :: [NS] -> ShowS #

Setting properties on virtual DOM nodes

prop :: ToJSON a => MisoString -> a -> Attribute model 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 = on defaultOptions "click" emptyDecoder $ \() -> Action
in button_ [ clickHandler, class_ "add" ] [ text_ "+" ]

String