blaze-html-0.4.3.3: A blazingly fast HTML combinator library for Haskell

Safe HaskellSafe-Infered

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 $ mapM_ (li . toHtml . show) [1, 2, 3]

The resulting HTML can now be extracted using:

 renderHtml page1

Synopsis

Important types.

type Html = HtmlM ()Source

Simplification of the HtmlM datatype.

data Tag Source

Type for an HTML tag. This can be seen as an internal string type used by BlazeHtml.

Instances

data Attribute Source

Type for an attribute.

Instances

data AttributeValue Source

The type for the value part of an attribute.

Creating attributes.

dataAttributeSource

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."

customAttributeSource

Arguments

:: Tag

Name of the attribute

-> AttributeValue

Value for the attribute

-> Attribute

Resulting HTML attribtue

Create a custom attribute. This is not specified in the HTML spec, but some JavaScript libraries rely on it.

An example:

 <select dojoType="select">foo</select>

Can be produced using:

 select ! customAttribute "dojoType" "select" $ "foo"

Converting values to HTML.

class ToHtml a whereSource

Class allowing us to use a single function for HTML values

Methods

toHtml :: a -> HtmlSource

Convert a value to HTML.

textSource

Arguments

:: Text

Text to render.

-> Html

Resulting HTML fragment.

Render text. Functions like these can be used to supply content in HTML.

preEscapedTextSource

Arguments

:: Text

Text to insert

-> Html

Resulting HTML fragment

Render text without escaping.

lazyTextSource

Arguments

:: Text

Text to insert

-> Html

Resulting HTML fragment

A variant of text for lazy Text.

preEscapedLazyTextSource

Arguments

:: Text

Text to insert

-> Html

Resulting HTML fragment

A variant of preEscapedText for lazy Text

stringSource

Arguments

:: String

String to insert.

-> Html

Resulting HTML fragment.

Create an HTML snippet from a String.

preEscapedStringSource

Arguments

:: String

String to insert.

-> Html

Resulting HTML fragment.

Create an HTML snippet from a String without escaping

unsafeByteStringSource

Arguments

:: ByteString

Value to insert.

-> Html

Resulting HTML fragment.

Insert a ByteString. This is an unsafe operation:

  • The ByteString could have the wrong encoding.
  • The ByteString might contain illegal HTML characters (no escaping is done).

unsafeLazyByteStringSource

Arguments

:: ByteString

Value to insert

-> Html

Resulting HTML fragment

Insert a lazy ByteString. See unsafeByteString for reasons why this is an unsafe operation.

Creating tags.

textTagSource

Arguments

:: Text

Text to create a tag from

-> Tag

Resulting tag

Create a Tag from some Text.

stringTagSource

Arguments

:: String

String to create a tag from

-> Tag

Resulting tag

Create a Tag from a String.

Converting values to attribute values.

class ToValue a whereSource

Class allowing us to use a single function for attribute values

Methods

toValue :: a -> AttributeValueSource

Convert a value to an HTML attribute value

textValueSource

Arguments

:: Text

The actual value.

-> AttributeValue

Resulting attribute value.

Render an attribute value from Text.

preEscapedTextValueSource

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

Render an attribute value from Text without escaping.

lazyTextValueSource

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of textValue for lazy Text

preEscapedLazyTextValueSource

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of preEscapedTextValue for lazy Text

stringValue :: String -> AttributeValueSource

Create an attribute value from a String.

preEscapedStringValue :: String -> AttributeValueSource

Create an attribute value from a String without escaping.

unsafeByteStringValueSource

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.

unsafeLazyByteStringValueSource

Arguments

:: ByteString

ByteString value

-> AttributeValue

Resulting attribute value

Create an attribute value from a lazy ByteString. See unsafeByteString for reasons why this might not be a good idea.

Setting attributes

(!) :: Attributable h => h -> Attribute -> hSource

Apply an attribute to an element.

Example:

 img ! src "foo.png"

Result:

 <img src="foo.png" />

This can be used on nested elements as well.

Example:

 p ! style "float: right" $ "Hello!"

Result:

 <p style="float: right">Hello!</p>