[web-devel] BlazeHtml: How to write quotation-marks in attributes?
Jasper Van der Jeugt
m at jaspervdj.be
Wed Apr 11 18:52:34 CEST 2012
Hey,
The preEscapedXXX functions make sure no HTML escaping occurs. In this
case, we use preEscapedTextValue: Text, because we're passing Text to
the function, and Value, because it needs to be converted to an HTML
attribute value.
{-# LANGUAGE OverloadedStrings #-}
import Text.Blaze (Html, (!))
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
test :: Html
test = H.body ! A.onload (H.preEscapedTextValue
"javascript:document.getElemByID('q').focus();") $ ""
Hope this helps,
Cheers,
Jasper
On Wed, Apr 11, 2012 at 6:44 PM, Morel Pisum <morel.pisum at googlemail.com> wrote:
> Hi.
>
> How can I write
> <body onload="javascript:document.getElemByID('q').focus();">
> in BlazeHtml?
>
> The problem is that single quotes are always converted to HTML.
>
> I'd appreciate a quick response. Thanks in advance.
>
> --
> Morel Pisum
>
>
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel
More information about the web-devel
mailing list