blaze-markup-0.6.3.0: A blazingly fast markup combinator library for Haskell

Safe HaskellNone
LanguageHaskell98

Text.Blaze

Contents

Description

BlazeMarkup is a markup combinator library. It provides a way to embed markup languages like HTML and SVG in Haskell in an efficient and convenient way, with a light-weight syntax.

To use the library, one needs to import a set of combinators. For example, you can use HTML 4 Strict from BlazeHtml package.

{-# 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 (renderMarkup)

Now, you can describe pages using the imported combinators.

page1 :: Markup
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 BlazeMarkup syntax."
        ul $ mapM_ (li . toMarkup . show) [1, 2, 3]

The resulting HTML can now be extracted using:

renderMarkup page1

Synopsis

Important types.

type Markup = MarkupM () Source

Simplification of the MarkupM datatype.

data Tag Source

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

Instances

data Attribute Source

Type for an attribute.

Instances

data AttributeValue Source

The type for the value part of an attribute.

Creating attributes.

dataAttribute Source

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 BlazeMarkup using this funcion. The above fragment could be described using BlazeMarkup with:

p ! dataAttribute "foo" "bar" $ "Hello."

customAttribute Source

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

class ToMarkup a where Source

Class allowing us to use a single function for Markup values

Minimal complete definition

toMarkup

Methods

toMarkup :: a -> Markup Source

Convert a value to Markup.

preEscapedToMarkup :: a -> Markup Source

Convert a value to Markup without escaping

text Source

Arguments

:: Text

Text to render.

-> Markup

Resulting HTML fragment.

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

preEscapedText Source

Arguments

:: Text

Text to insert

-> Markup

Resulting HTML fragment

Render text without escaping.

lazyText Source

Arguments

:: Text

Text to insert

-> Markup

Resulting HTML fragment

A variant of text for lazy Text.

preEscapedLazyText Source

Arguments

:: Text

Text to insert

-> Markup

Resulting HTML fragment

A variant of preEscapedText for lazy Text

string Source

Arguments

:: String

String to insert.

-> Markup

Resulting HTML fragment.

Create an HTML snippet from a String.

preEscapedString Source

Arguments

:: String

String to insert.

-> Markup

Resulting HTML fragment.

Create an HTML snippet from a String without escaping

unsafeByteString Source

Arguments

:: ByteString

Value to insert.

-> Markup

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

unsafeLazyByteString Source

Arguments

:: ByteString

Value to insert

-> Markup

Resulting HTML fragment

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

Comments

textComment :: Text -> Markup Source

Create a comment from a Text value. The text should not contain "--". This is not checked by the library.

lazyTextComment :: Text -> Markup Source

Create a comment from a Text value. The text should not contain "--". This is not checked by the library.

stringComment :: String -> Markup Source

Create a comment from a String value. The text should not contain "--". This is not checked by the library.

unsafeByteStringComment :: ByteString -> Markup Source

Create a comment from a ByteString value. The text should not contain "--". This is not checked by the library.

unsafeLazyByteStringComment :: ByteString -> Markup Source

Create a comment from a ByteString value. The text should not contain "--". This is not checked by the library.

Creating tags.

textTag Source

Arguments

:: Text

Text to create a tag from

-> Tag

Resulting tag

Create a Tag from some Text.

stringTag Source

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 where Source

Class allowing us to use a single function for attribute values

Minimal complete definition

toValue

Methods

toValue :: a -> AttributeValue Source

Convert a value to an attribute value

preEscapedToValue :: a -> AttributeValue Source

Convert a value to an attribute value without escaping

textValue Source

Arguments

:: Text

The actual value.

-> AttributeValue

Resulting attribute value.

Render an attribute value from Text.

preEscapedTextValue Source

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

Render an attribute value from Text without escaping.

lazyTextValue Source

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of textValue for lazy Text

preEscapedLazyTextValue Source

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of preEscapedTextValue for lazy Text

stringValue :: String -> AttributeValue Source

Create an attribute value from a String.

preEscapedStringValue :: String -> AttributeValue Source

Create an attribute value from a String without escaping.

unsafeByteStringValue Source

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.

unsafeLazyByteStringValue Source

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 -> h Source

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>

(!?) :: Attributable h => h -> (Bool, Attribute) -> h Source

Shorthand for setting an attribute depending on a conditional.

Example:

p !? (isBig, A.class "big") $ "Hello"

Gives the same result as:

(if isBig then p ! A.class "big" else p) "Hello"

Modifiying Markup trees

contents :: MarkupM a -> MarkupM b Source

Take only the text content of an HTML tree.

contents $ do
    p ! $ "Hello "
    p ! $ "Word!"

Result:

Hello World!