Text.Blaze
Contents
Description
BlazeHtml is an HTML combinator library. It provides a way to embed HTML in Haskell in an efficient and convenient way, with a light-weight syntax.
To use the library, one needs to import a set of HTML combinators. For example, you can use HTML 4 Strict.
 {-# LANGUAGE OverloadedStrings #-}
 import Prelude hiding (head, id, div)
 import Text.Blaze.Html4.Strict hiding (map)
 import Text.Blaze.Html4.Strict.Attributes hiding (title)
To render the page later on, you need a so called Renderer. The recommended renderer is an UTF-8 renderer which produces a lazy bytestring.
import Text.Blaze.Renderer.Utf8 (renderHtml)
Now, you can describe pages using the imported combinators.
page1 :: Html page1 = html $ do head $ do title "Introduction page." link ! rel "stylesheet" ! type_ "text/css" ! href "screen.css" body $ do div ! id "header" $ "Syntax" p "This is an example of BlazeHtml syntax." ul $ forM_ [1, 2, 3] (li . string . show)
The resulting HTML can now be extracted using:
renderHtml page1
- type Html = HtmlM ()
 - data Tag
 - data Attribute
 - data AttributeValue
 - dataAttribute :: Tag -> AttributeValue -> Attribute
 - text :: Text -> Html
 - preEscapedText :: Text -> Html
 - string :: String -> Html
 - preEscapedString :: String -> Html
 - showHtml :: Show a => a -> Html
 - preEscapedShowHtml :: Show a => a -> Html
 - unsafeByteString :: ByteString -> Html
 - textTag :: Text -> Tag
 - stringTag :: String -> Tag
 - textValue :: Text -> AttributeValue
 - preEscapedTextValue :: Text -> AttributeValue
 - stringValue :: String -> AttributeValue
 - preEscapedStringValue :: String -> AttributeValue
 - unsafeByteStringValue :: ByteString -> AttributeValue
 - (!) :: Attributable h => h -> Attribute -> h
 
Important types.
Type for an HTML tag. This can be seen as an internal string type used by BlazeHtml.
Creating attributes.
Arguments
| :: Tag | Name of the attribute.  | 
| -> AttributeValue | Value for the attribute.  | 
| -> Attribute | Resulting HTML attribute.  | 
From HTML 5 onwards, the user is able to specify custom data attributes.
An example:
<p data-foo="bar">Hello.</p>
We support this in BlazeHtml using this funcion. The above fragment could be described using BlazeHtml with:
p ! dataAttribute "foo" "bar" $ "Hello."
Converting values to HTML.
Render text. Functions like these can be used to supply content in HTML.
Create an HTML snippet from a String.
Create an HTML snippet from a String without escaping
Create an HTML snippet from a datatype that instantiates Show.
Create an HTML snippet from a datatype that instantiates Show. This
 function will not do any HTML entity escaping.
Arguments
| :: ByteString | Value to insert.  | 
| -> Html | Resulting HTML fragment.  | 
Insert a ByteString. This is an unsafe operation:
-  The 
ByteStringcould have the wrong encoding. -  The 
ByteStringmight contain illegal HTML characters (no escaping is done). 
Creating tags.
Converting values to attribute values.
Arguments
| :: Text | The actual value.  | 
| -> AttributeValue | Resulting attribute value.  | 
Render an attribute value from Text.
Arguments
| :: Text | Text to insert.  | 
| -> AttributeValue | 
Render an attribute value from Text without escaping.
stringValue :: String -> AttributeValueSource
Create an attribute value from a String.
preEscapedStringValue :: String -> AttributeValueSource
Create an attribute value from a String without escaping.
Arguments
| :: ByteString | ByteString value  | 
| -> AttributeValue | Resulting attribute value  | 
Create an attribute value from a ByteString. See unsafeByteString
 for reasons why this might not be a good idea.