Copyright | (c) Athur S. Fayzrakhmanov 2015 Alberto G. Corona 2015 |
---|---|
License | MIT |
Maintainer | heraldhoi@gmail.com |
Stability | experimental |
Portability | Any |
Safe Haskell | None |
Language | Haskell2010 |
Monad and Monoid instances for a builder that hang DOM elements from the current parent element.
- pack :: a
- newtype PerchM a = Perch {}
- type Perch = PerchM ()
- class ToElem a where
- class Attributable h where
- attr :: forall a. PerchM a -> (PropId, JSString) -> PerchM a
- nelem :: JSString -> Perch
- child :: ToElem a => Perch -> a -> Perch
- setHtml :: Perch -> JSString -> Perch
- addEvent :: NamedEvent e => Perch -> e -> Callback (JSVal -> IO ()) -> Perch
- addEvent' :: NamedEvent e => Perch -> e -> (JSVal -> IO ()) -> Perch
- remEvent :: NamedEvent e => Perch -> e -> Callback (JSVal -> IO ()) -> Perch
- area :: Perch
- base :: Perch
- br :: Perch
- col :: Perch
- embed :: Perch
- hr :: Perch
- img :: Perch
- input :: Perch
- keygen :: Perch
- link :: Perch
- menuitem :: Perch
- meta :: Perch
- param :: Perch
- source :: Perch
- track :: Perch
- wbr :: Perch
- a :: ToElem a => a -> Perch
- abbr :: ToElem a => a -> Perch
- address :: ToElem a => a -> Perch
- article :: ToElem a => a -> Perch
- aside :: ToElem a => a -> Perch
- audio :: ToElem a => a -> Perch
- b :: ToElem a => a -> Perch
- bdo :: ToElem a => a -> Perch
- blockquote :: ToElem a => a -> Perch
- body :: ToElem a => a -> Perch
- button :: ToElem a => a -> Perch
- canvas :: ToElem a => a -> Perch
- caption :: ToElem a => a -> Perch
- center :: ToElem a => a -> Perch
- cite :: ToElem a => a -> Perch
- code :: ToElem a => a -> Perch
- colgroup :: ToElem a => a -> Perch
- command :: ToElem a => a -> Perch
- datalist :: ToElem a => a -> Perch
- dd :: ToElem a => a -> Perch
- del :: ToElem a => a -> Perch
- details :: ToElem a => a -> Perch
- dfn :: ToElem a => a -> Perch
- div :: ToElem a => a -> Perch
- dl :: ToElem a => a -> Perch
- dt :: ToElem a => a -> Perch
- em :: ToElem a => a -> Perch
- fieldset :: ToElem a => a -> Perch
- figcaption :: ToElem a => a -> Perch
- figure :: ToElem a => a -> Perch
- footer :: ToElem a => a -> Perch
- form :: ToElem a => a -> Perch
- h1 :: ToElem a => a -> Perch
- h2 :: ToElem a => a -> Perch
- h3 :: ToElem a => a -> Perch
- h4 :: ToElem a => a -> Perch
- h5 :: ToElem a => a -> Perch
- h6 :: ToElem a => a -> Perch
- head :: ToElem a => a -> Perch
- header :: ToElem a => a -> Perch
- hgroup :: ToElem a => a -> Perch
- html :: ToElem a => a -> Perch
- i :: ToElem a => a -> Perch
- iframe :: ToElem a => a -> Perch
- ins :: ToElem a => a -> Perch
- kbd :: ToElem a => a -> Perch
- label :: ToElem a => a -> Perch
- legend :: ToElem a => a -> Perch
- li :: ToElem a => a -> Perch
- map :: ToElem a => a -> Perch
- mark :: ToElem a => a -> Perch
- menu :: ToElem a => a -> Perch
- meter :: ToElem a => a -> Perch
- nav :: ToElem a => a -> Perch
- noscript :: ToElem a => a -> Perch
- object :: ToElem a => a -> Perch
- ol :: ToElem a => a -> Perch
- optgroup :: ToElem a => a -> Perch
- option :: ToElem a => a -> Perch
- output :: ToElem a => a -> Perch
- p :: ToElem a => a -> Perch
- pre :: ToElem a => a -> Perch
- progress :: ToElem a => a -> Perch
- q :: ToElem a => a -> Perch
- rp :: ToElem a => a -> Perch
- rt :: ToElem a => a -> Perch
- ruby :: ToElem a => a -> Perch
- samp :: ToElem a => a -> Perch
- script :: ToElem a => a -> Perch
- section :: ToElem a => a -> Perch
- select :: ToElem a => a -> Perch
- small :: ToElem a => a -> Perch
- span :: ToElem a => a -> Perch
- strong :: ToElem a => a -> Perch
- sub :: ToElem a => a -> Perch
- summary :: ToElem a => a -> Perch
- sup :: ToElem a => a -> Perch
- table :: ToElem a => a -> Perch
- tbody :: ToElem a => a -> Perch
- td :: ToElem a => a -> Perch
- textarea :: ToElem a => a -> Perch
- tfoot :: ToElem a => a -> Perch
- th :: ToElem a => a -> Perch
- thead :: ToElem a => a -> Perch
- time :: ToElem a => a -> Perch
- title :: ToElem a => a -> Perch
- tr :: ToElem a => a -> Perch
- ul :: ToElem a => a -> Perch
- var :: ToElem a => a -> Perch
- video :: ToElem a => a -> Perch
- ctag :: ToElem b => JSString -> b -> Perch
- noHtml :: Perch
- atr :: String -> JSString -> Attribute
- id :: JSString -> Attribute
- height :: JSString -> Attribute
- href :: JSString -> Attribute
- src :: JSString -> Attribute
- style :: JSString -> Attribute
- width :: JSString -> Attribute
- this :: Perch
- goParent :: Perch -> Perch -> Perch
- delete :: Perch
- clear :: Perch
- outer :: Perch -> Perch -> Perch
- forElems :: JSString -> Perch -> Perch
- forElems_ :: JSString -> Perch -> IO ()
- withElems :: Perch -> JSString -> Perch
- withElems_ :: Perch -> JSString -> IO ()
- forElemId :: JSString -> Perch -> Perch
- forElemId_ :: JSString -> Perch -> IO ()
- withElemId :: Perch -> JSString -> Perch
- withElemId_ :: Perch -> JSString -> IO ()
- withPerch :: (Elem -> IO a) -> Elem -> IO Elem
- withPerchBuild :: PerchM a -> (Elem -> IO b) -> Elem -> IO Elem
- data Elem
- type PropId = JSString
- type Attribute = (JSString, JSString)
- class NamedEvent a where
- data JsEvent
- data Callback a = Callback a
- notImplemented :: a
- getDocument :: IO Elem
- getBody :: IO Elem
- newElem :: JSString -> IO Elem
- newTextElem :: JSString -> IO Elem
- parent :: Elem -> IO Elem
- addChild :: Elem -> Elem -> IO ()
- removeChild :: Elem -> Elem -> IO ()
- clearChildren :: Elem -> IO ()
- replace :: Elem -> Elem -> IO Elem
- setAttr :: Elem -> PropId -> JSString -> IO ()
- setInnerHTML :: Elem -> JSString -> IO ()
- getElemById :: JSString -> IO Elem
- queryAll :: JSString -> IO [Elem]
- onEvent :: NamedEvent e => Elem -> e -> Callback (JSVal -> IO ()) -> IO (IO ())
- onEvent' :: NamedEvent e => Elem -> e -> (JSVal -> IO ()) -> IO ()
- removeEvent :: NamedEvent e => Elem -> e -> Callback (JSVal -> IO ()) -> IO ()
Perch DOM Builder
class Attributable h where Source #
Attributable Perch Source # | |
ToElem a => Attributable (a -> Perch) Source # | |
DOM Tree Building
Build an element as child of another one. Child element becomes new continuation for monadic expression.
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
blockquote :: ToElem a => a -> Perch Source #
figcaption :: ToElem a => a -> Perch Source #
HTML4 Support
DOM Tree Navigation & Manipulation
Attributes
Traversal
goParent :: Perch -> Perch -> Perch Source #
Goes to the parent node of the first and execute the second.
Manipulation
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 -> IO () Source #
A declarative synonym of flip forElements
.
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_
.
Types
class NamedEvent a where Source #
Show a => NamedEvent a Source # | |
Internal API
notImplemented :: a Source #
getDocument :: IO Elem Source #
newTextElem :: JSString -> IO Elem Source #
Appends one element to another.
clearChildren :: Elem -> IO () Source #
setInnerHTML :: Elem -> JSString -> IO () Source #
getElemById :: 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.