{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, QuasiQuotes, TypeSynonymInstances, OverloadedStrings, TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- | This module provides support for: -- -- 1. embedding Javascript generated by JMacro into HSX. -- -- 2. turning XML generated by HSX into a DOM node in Javascript -- -- It provides the following instances: -- -- > instance (XMLGenerator m, IntegerSupply m) => EmbedAsChild m JStat -- > instance (IntegerSupply m, IsName n, EmbedAsAttr m (Attr Name String)) => EmbedAsAttr m (Attr n JStat) -- > instance ToJExpr XML -- > instance ToJExpr DOMNode -- > instance ToJExpr XMLToInnerHTML -- > instance ToJExpr XMLToDOM -- -- In order to ensure that each embedded 'JStat' block has unique -- variable names, the monad must supply a source of unique -- names. This is done by adding an instance of 'IntegerSupply' for -- the monad being used with 'XMLGenerator'. -- -- For example, we can use 'StateT' to provide an 'IntegerSupply' instance for 'ServerPartT': -- -- > instance IntegerSupply (ServerPartT (StateT Integer IO)) where -- > nextInteger = nextInteger' -- -- Alternatively, we can exploit the IO monad to provide an 'IntegerSupply' instance for 'ServerPartT': -- -- > instance IntegerSupply (ServerPartT IO) where -- > nextInteger = fmap (fromIntegral . (`mod` 1024) . hashUnique) (liftIO newUnique) -- -- The @ToJExpr XML@ instance allows you to splice in XML lifted out of an -- arbitrary monad to generate DOM nodes with JMacro antiquotation: -- -- > js = do html <- unXMLGenT

I'm in a Monad!

-- > return [jmacro| document.getElementById("messages").appendChild(`(html)`); |] -- -- The @ToJExpr DOMNode@ instance allows you to run HSP in the Identity -- monad to render JMacro in pure code: -- -- > html :: DOMNode -- > html =

I'm using JavaScript!

-- > js = [jmacro| var language = `(html)`.getElementsByTagName("em")[0].textContent; |] -- -- You can see here that you get an actual DOM tree in JavaScript. This is -- also compatible with libraries such as jQuery and YUI which are able to -- wrap DOM nodes in their own type, for example with jQuery: -- -- > js = [jmacro| var languages = $(`(html)`).find("em").text(); |] -- -- Or with YUI: -- -- > js = [jmacro| var languages = Y.one(`(html)`).one("em").get("text"); |] -- -- There are two ways to turn HTML into a a DOM node in the -- browser. One way is to render the HTML to a string, and pass the -- string to @element.innerHTML@. The other way is to us the use the -- DOM functions like @createElement@, @setAttribute@, to -- programatically create the DOM on the client. -- -- In webkit-based browsers like Chrome and Safari, the DOM method -- appears to be slightly faster. In other browsers, the @innerHTML@ -- method appears to be faster. The @innerHTML@ method will almost -- always required fewer bytes to be transmitted. Additionally, if -- your XML/HTML contains pre-escaped content, you are required to use -- @innerHTML@ anyway. -- -- So, by default the 'ToJExpr' 'XML' instance uses the @innerHTML@ -- method. Though, that could change in the future. If you care about -- using one method over the other you can use the @newtype@ wrappers -- 'XMLToInnerHTML' or 'XMLToDOM' to select which method to use. module HSP.JMacro where import Control.Monad.Identity import Control.Monad.Trans (lift) import Control.Monad.State (MonadState(get,put)) import Data.Text.Lazy (Text, unpack) import HSP.XML import HSP.HTML4 (renderAsHTML) import HSP.XMLGenerator import HSP.Monad (HSPT(..)) import Language.Javascript.JMacro (JStat(..), JExpr(..), JVal(..), Ident(..), ToJExpr(..), toStat, jmacroE, jLam, jVarTy, jsToDoc, jsSaturate, renderPrefixJs) import Text.PrettyPrint.Leijen.Text (Doc, displayT, renderOneLine) -- | This class provides a monotonically increasing supply of non-duplicate 'Integer' values class IntegerSupply m where nextInteger :: m Integer -- | This help function allows you to easily create an 'IntegerSupply' -- instance for monads that have a 'MonadState' 'Integer' instance. -- -- For example: -- -- > instance IntegerSupply (ServerPartT (StateT Integer IO)) where -- > nextInteger = nextInteger' nextInteger' :: (MonadState Integer m) => m Integer nextInteger' = do i <- get put (succ i) return i instance (XMLGenerator m, IntegerSupply m, EmbedAsChild m Text, StringType m ~ Text) => EmbedAsChild m JStat where asChild jstat = do i <- lift nextInteger asChild $ genElement (Nothing, fromStringLit "script") [asAttr ((fromStringLit "type" := fromStringLit "text/javascript") :: Attr Text Text)] [asChild (displayT $ renderOneLine $ renderPrefixJs (show i) jstat)] instance (IntegerSupply m, EmbedAsAttr m (Attr n Text)) => EmbedAsAttr m (Attr n JStat) where asAttr (n := jstat) = do i <- lift nextInteger asAttr $ (n := (displayT $ renderOneLine $ renderPrefixJs (show i) jstat)) -- | Provided for convenience since @Ident@ is exported by both -- @HSP.Identity@ and @JMacro@. Using this you can avoid the need for an -- extra and qualified import. type DOMNode = HSPT XML Identity XML instance ToJExpr DOMNode where toJExpr = toJExpr . runIdentity . unHSPT -- | newtype which can be used with 'toJExpr' to specify that the XML -- should be converted to a DOM in javascript by using 'innerHTML' newtype XMLToInnerHTML = XMLToInnerHTML XML instance ToJExpr XMLToInnerHTML where toJExpr (XMLToInnerHTML xml) = [jmacroE| (function { var node = document.createElement('div') ; node.innerHTML = `(unpack $ renderAsHTML xml)` ; return node.childNodes[0] })() |] -- | newtype which can be used with 'toJExpr' to specify that the XML -- should be converted to a DOM in javascript by using -- @createElement@, @appendChild@, and other DOM functions. -- -- WARNING: @CDATA FALSE@ values are assumed to be pre-escaped HTML and will be converted to a DOM node by using @innerHTML@. Additionally, if the call to @innerHTML@ returns more than one node, only the first node is used. newtype XMLToDOM = XMLToDOM XML instance ToJExpr XMLToDOM where toJExpr (XMLToDOM (Element (dm', n') attrs children)) = let dm = fmap unpack dm' n = unpack n' in [jmacroE| (function { var node = `(createElement (dm) (n))` ; `(map (setAttribute node) attrs)` ; `(map (appendChild node . XMLToDOM) children)` ; return node })() |] where createElement Nothing n = [jmacroE| document.createElement(`(n)`) |] createElement (Just ns) n = [jmacroE| document.createElementNS(`(ns)`, `(n)`) |] appendChild node c' = [jmacroE| (function () { var c = `(c')`; if (Object.prototype.toString.call(c) === '[object Array]') { for (var i = 0; i < c.length; i++) `(node)`.appendChild(c[i]); } else { `(node)`.appendChild(`(c)`); } })() |] setAttribute node (MkAttr ((Nothing, nm'), (Value True val'))) = let nm = unpack nm' val = unpack val' in [jmacroE| `(node)`.setAttribute(`(nm)`, `(val)`) |] setAttribute node (MkAttr ((Just ns', nm'), (Value True val'))) = let ns = unpack ns' nm = unpack nm' val = unpack val' in [jmacroE| `(node)`.setAttributeNS(`(ns)`, `(nm)`, `(val)`) |] toJExpr (XMLToDOM (CDATA True txt')) = let txt = unpack txt' in [jmacroE| document.createTextNode(`(txt)`) |] toJExpr (XMLToDOM (CDATA False txt')) = let txt = unpack txt' in [jmacroE| (function { var node = document.createElement('div') ; node.innerHTML = `(txt)` ; return node })() |] instance ToJExpr XML where toJExpr = toJExpr . XMLToInnerHTML