ghcjs-perch-0.3.3.2: GHCJS version of Perch library.

Copyright(c) Athur S. Fayzrakhmanov 2015
Alberto G. Corona 2015
LicenseMIT
Maintainerheraldhoi@gmail.com
Stabilityexperimental
PortabilityAny
Safe HaskellNone
LanguageHaskell2010

GHCJS.Perch

Contents

Description

Monad and Monoid instances for a builder that hang DOM elements from the current parent element.

Synopsis

Perch DOM Builder

newtype PerchM a Source #

Constructors

Perch 

Fields

Instances

Monad PerchM Source # 

Methods

(>>=) :: PerchM a -> (a -> PerchM b) -> PerchM b #

(>>) :: PerchM a -> PerchM b -> PerchM b #

return :: a -> PerchM a #

fail :: String -> PerchM a #

Functor PerchM Source # 

Methods

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

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

IsString Perch Source # 

Methods

fromString :: String -> Perch #

Applicative PerchM Source # 

Methods

pure :: a -> PerchM a #

(<*>) :: PerchM (a -> b) -> PerchM a -> PerchM b #

(*>) :: PerchM a -> PerchM b -> PerchM b #

(<*) :: PerchM a -> PerchM b -> PerchM a #

MonadIO PerchM Source # 

Methods

liftIO :: IO a -> PerchM a #

Attributable Perch Source # 

Methods

(!) :: Perch -> Attribute -> Perch Source #

Monoid (PerchM a) Source # 

Methods

mempty :: PerchM a #

mappend :: PerchM a -> PerchM a -> PerchM a #

mconcat :: [PerchM a] -> PerchM a #

ToElem (PerchM a) Source # 

Methods

toElem :: PerchM a -> Perch Source #

ToElem a => Attributable (a -> Perch) Source # 

Methods

(!) :: (a -> Perch) -> Attribute -> a -> Perch Source #

type Perch = PerchM () Source #

class ToElem a where Source #

Minimal complete definition

toElem

Methods

toElem :: a -> Perch Source #

Instances

Show a => ToElem a Source # 

Methods

toElem :: a -> Perch Source #

ToElem (PerchM a) Source # 

Methods

toElem :: PerchM a -> Perch Source #

class Attributable h where Source #

Minimal complete definition

(!)

Methods

(!) :: h -> Attribute -> h Source #

Instances

Attributable Perch Source # 

Methods

(!) :: Perch -> Attribute -> Perch Source #

ToElem a => Attributable (a -> Perch) Source # 

Methods

(!) :: (a -> Perch) -> Attribute -> a -> Perch Source #

DOM Tree Building

attr :: forall a. PerchM a -> (PropId, JSString) -> PerchM a Source #

nelem :: JSString -> Perch Source #

child Source #

Arguments

:: ToElem a 
=> Perch

parent

-> a

child

-> Perch 

Build an element as child of another one. Child element becomes new continuation for monadic expression.

setHtml :: Perch -> JSString -> Perch Source #

addEvent :: NamedEvent e => Perch -> e -> Callback (JSVal -> IO ()) -> Perch Source #

Build perch and attach an event handler to its element.

Event handler should be an IO action wrapped by GHCJS' Callback taking one argument, that is an actual JavaScript event object baked in JSVal.

addEvent' :: NamedEvent e => Perch -> e -> (JSVal -> IO ()) -> Perch Source #

Build perch and attach an event handler to its element. Use this function only when you are sure that you won't detach handler during application run.

remEvent :: NamedEvent e => Perch -> e -> Callback (JSVal -> IO ()) -> Perch Source #

Build perch and remove an event handler from it.

Note, you still have to release callback manually.

Leaf DOM Nodes

Parent DOM Nodes

a :: ToElem a => a -> Perch Source #

abbr :: ToElem a => a -> Perch Source #

address :: ToElem a => a -> Perch Source #

article :: ToElem a => a -> Perch Source #

aside :: ToElem a => a -> Perch Source #

audio :: ToElem a => a -> Perch Source #

b :: ToElem a => a -> Perch Source #

bdo :: ToElem a => a -> Perch Source #

body :: ToElem a => a -> Perch Source #

button :: ToElem a => a -> Perch Source #

canvas :: ToElem a => a -> Perch Source #

caption :: ToElem a => a -> Perch Source #

center :: ToElem a => a -> Perch Source #

cite :: ToElem a => a -> Perch Source #

code :: ToElem a => a -> Perch Source #

command :: ToElem a => a -> Perch Source #

dd :: ToElem a => a -> Perch Source #

del :: ToElem a => a -> Perch Source #

details :: ToElem a => a -> Perch Source #

dfn :: ToElem a => a -> Perch Source #

div :: ToElem a => a -> Perch Source #

dl :: ToElem a => a -> Perch Source #

dt :: ToElem a => a -> Perch Source #

em :: ToElem a => a -> Perch Source #

figure :: ToElem a => a -> Perch Source #

footer :: ToElem a => a -> Perch Source #

form :: ToElem a => a -> Perch Source #

h1 :: ToElem a => a -> Perch Source #

h2 :: ToElem a => a -> Perch Source #

h3 :: ToElem a => a -> Perch Source #

h4 :: ToElem a => a -> Perch Source #

h5 :: ToElem a => a -> Perch Source #

h6 :: ToElem a => a -> Perch Source #

head :: ToElem a => a -> Perch Source #

header :: ToElem a => a -> Perch Source #

hgroup :: ToElem a => a -> Perch Source #

html :: ToElem a => a -> Perch Source #

i :: ToElem a => a -> Perch Source #

iframe :: ToElem a => a -> Perch Source #

ins :: ToElem a => a -> Perch Source #

kbd :: ToElem a => a -> Perch Source #

label :: ToElem a => a -> Perch Source #

legend :: ToElem a => a -> Perch Source #

li :: ToElem a => a -> Perch Source #

map :: ToElem a => a -> Perch Source #

mark :: ToElem a => a -> Perch Source #

menu :: ToElem a => a -> Perch Source #

meter :: ToElem a => a -> Perch Source #

nav :: ToElem a => a -> Perch Source #

object :: ToElem a => a -> Perch Source #

ol :: ToElem a => a -> Perch Source #

option :: ToElem a => a -> Perch Source #

output :: ToElem a => a -> Perch Source #

p :: ToElem a => a -> Perch Source #

pre :: ToElem a => a -> Perch Source #

q :: ToElem a => a -> Perch Source #

rp :: ToElem a => a -> Perch Source #

rt :: ToElem a => a -> Perch Source #

ruby :: ToElem a => a -> Perch Source #

samp :: ToElem a => a -> Perch Source #

script :: ToElem a => a -> Perch Source #

section :: ToElem a => a -> Perch Source #

select :: ToElem a => a -> Perch Source #

small :: ToElem a => a -> Perch Source #

span :: ToElem a => a -> Perch Source #

strong :: ToElem a => a -> Perch Source #

sub :: ToElem a => a -> Perch Source #

summary :: ToElem a => a -> Perch Source #

sup :: ToElem a => a -> Perch Source #

table :: ToElem a => a -> Perch Source #

tbody :: ToElem a => a -> Perch Source #

td :: ToElem a => a -> Perch Source #

tfoot :: ToElem a => a -> Perch Source #

th :: ToElem a => a -> Perch Source #

thead :: ToElem a => a -> Perch Source #

time :: ToElem a => a -> Perch Source #

title :: ToElem a => a -> Perch Source #

tr :: ToElem a => a -> Perch Source #

ul :: ToElem a => a -> Perch Source #

var :: ToElem a => a -> Perch Source #

video :: ToElem a => a -> Perch Source #

ctag :: ToElem b => JSString -> b -> Perch Source #

HTML4 Support

DOM Tree Navigation & Manipulation

Attributes

atr :: String -> JSString -> Attribute Source #

id :: JSString -> Attribute Source #

height :: JSString -> Attribute Source #

href :: JSString -> Attribute Source #

src :: JSString -> Attribute Source #

style :: JSString -> Attribute Source #

width :: JSString -> Attribute Source #

Traversal

this :: Perch Source #

Return the current node.

goParent :: Perch -> Perch -> Perch Source #

Goes to the parent node of the first and execute the second.

Manipulation

delete :: Perch Source #

Delete the current node and return the parent.

clear :: Perch Source #

Delete all children of the current node.

outer :: Perch -> Perch -> Perch Source #

Replace the current node with a new one

forElems :: JSString -> Perch -> Perch Source #

JQuery-like DOM manipulation. It applies the Perch DOM manipulation for each found element using querySelectorAll function.

forElems_ :: JSString -> Perch -> IO () Source #

Like forElems, but works in IO monad. Example:

import GHCJS.Foreign.Callback (asyncCallback1)

main = do
  body <- getBody
  makeRed <- asyncCallback1 (\ _ -> do
    forElems_ ".changeable" $
      this ! style "color:red")
  (flip build) body . div $ do
     div ! atr "class" "changeable" $ "Changeable"
     div "Static"
     div ! atr "class" "changeable" $ "Changeable"
     addEvent this Click makeRed

withElems :: Perch -> JSString -> Perch Source #

Decalarative synonym for flip forElems.

Examples:

doAction `withElems` ".item"
forElems ".item" doAction

withElems_ :: Perch -> JSString -> IO () Source #

A declarative synonym of flip forElements.

forElemId :: JSString -> Perch -> Perch Source #

Apply action to perch with given identifier.

forElemId_ :: JSString -> Perch -> IO () Source #

IO version of forElemId_.

withElemId :: Perch -> JSString -> Perch Source #

A synonym to flip forElemId.

withElemId_ :: Perch -> JSString -> IO () Source #

A synonym to flip forElemId_.

withPerch :: (Elem -> IO a) -> Elem -> IO Elem Source #

withPerchBuild :: PerchM a -> (Elem -> IO b) -> Elem -> IO Elem Source #

Types

type PropId = JSString Source #

type Attribute = (JSString, JSString) Source #

class NamedEvent a where Source #

Minimal complete definition

eventName

Methods

eventName :: a -> String Source #

Instances

Show a => NamedEvent a Source # 

Methods

eventName :: a -> String Source #

Internal API

data Callback a Source #

Constructors

Callback a 

newElem :: JSString -> IO Elem Source #

newTextElem :: JSString -> IO Elem Source #

addChild Source #

Arguments

:: Elem

child element to append

-> Elem

parent element

-> IO () 

Appends one element to another.

removeChild Source #

Arguments

:: Elem

child to remove

-> Elem

parent node

-> IO () 

Remove child from parent.

setAttr :: Elem -> PropId -> JSString -> IO () Source #

setInnerHTML :: Elem -> JSString -> IO () Source #

getElemById :: JSString -> IO Elem Source #

queryAll :: JSString -> IO [Elem] Source #

onEvent :: NamedEvent e => Elem -> e -> Callback (JSVal -> IO ()) -> IO (IO ()) Source #

Attach an event listener to element.

Returns an action removing listener, though you still have to release callback manually.

If you are sure that you do not want to remove handler consider using onEvent'.

onEvent' :: NamedEvent e => Elem -> e -> (JSVal -> IO ()) -> IO () Source #

Attach endless event listener to element.

Use this function to attach event handlers which supposed not to be removed during application run.

removeEvent :: NamedEvent e => Elem -> e -> Callback (JSVal -> IO ()) -> IO () Source #

Remove attached event listener.

Normally you can use action returned by onEvent to detach event listener, however you can also use this function directly.