Safe Haskell | Safe-Infered |
---|
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
- type Markup = MarkupM ()
- data Tag
- data Attribute
- data AttributeValue
- dataAttribute :: Tag -> AttributeValue -> Attribute
- customAttribute :: Tag -> AttributeValue -> Attribute
- class ToMarkup a where
- preEscapedText :: Text -> Markup
- preEscapedLazyText :: Text -> Markup
- preEscapedString :: String -> Markup
- unsafeByteString :: ByteString -> Markup
- unsafeLazyByteString :: ByteString -> Markup
- textTag :: Text -> Tag
- stringTag :: String -> Tag
- class ToValue a where
- toValue :: a -> AttributeValue
- preEscapedTextValue :: Text -> AttributeValue
- preEscapedLazyTextValue :: Text -> AttributeValue
- preEscapedStringValue :: String -> AttributeValue
- unsafeByteStringValue :: ByteString -> AttributeValue
- unsafeLazyByteStringValue :: 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 BlazeMarkup.
data AttributeValue Source
The type for the value part of an attribute.
Creating attributes.
:: 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."
:: 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 allowing us to use a single function for Markup values
Render text without escaping.
A variant of preEscapedText
for lazy Text
Create an HTML snippet from a String
without escaping
:: 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).
:: ByteString | Value to insert |
-> Markup | Resulting HTML fragment |
Insert a lazy ByteString
. See unsafeByteString
for reasons why this
is an unsafe operation.
Creating tags.
Converting values to attribute values.
Class allowing us to use a single function for attribute values
toValue :: a -> AttributeValueSource
Convert a value to an attribute value
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
Render an attribute value from Text
without escaping.
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
A variant of preEscapedTextValue
for lazy Text
preEscapedStringValue :: String -> AttributeValueSource
Create an attribute value from a String
without escaping.
:: 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
:: 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>