Safe Haskell | None |
---|---|
Language | Haskell98 |
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
- type Markup = MarkupM ()
- data Tag
- data Attribute
- data AttributeValue
- dataAttribute :: Tag -> AttributeValue -> Attribute
- customAttribute :: Tag -> AttributeValue -> Attribute
- class ToMarkup a where
- toMarkup :: a -> Markup
- preEscapedToMarkup :: a -> Markup
- text :: Text -> Markup
- preEscapedText :: Text -> Markup
- lazyText :: Text -> Markup
- preEscapedLazyText :: Text -> Markup
- string :: String -> Markup
- preEscapedString :: String -> Markup
- unsafeByteString :: ByteString -> Markup
- unsafeLazyByteString :: ByteString -> Markup
- textComment :: Text -> Markup
- lazyTextComment :: Text -> Markup
- stringComment :: String -> Markup
- unsafeByteStringComment :: ByteString -> Markup
- unsafeLazyByteStringComment :: ByteString -> Markup
- textTag :: Text -> Tag
- stringTag :: String -> Tag
- class ToValue a where
- toValue :: a -> AttributeValue
- preEscapedToValue :: a -> AttributeValue
- textValue :: Text -> AttributeValue
- preEscapedTextValue :: Text -> AttributeValue
- lazyTextValue :: Text -> AttributeValue
- preEscapedLazyTextValue :: Text -> AttributeValue
- stringValue :: String -> AttributeValue
- preEscapedStringValue :: String -> AttributeValue
- unsafeByteStringValue :: ByteString -> AttributeValue
- unsafeLazyByteStringValue :: ByteString -> AttributeValue
- (!) :: Attributable h => h -> Attribute -> h
- (!?) :: Attributable h => h -> (Bool, Attribute) -> h
- contents :: MarkupM a -> MarkupM a
Important types.
Type for an HTML tag. This can be seen as an internal string type used by BlazeMarkup.
Instances
IsString Tag # | |
Defined in Text.Blaze.Internal Methods fromString :: String -> Tag # |
data AttributeValue #
The type for the value part of an attribute.
Instances
IsString AttributeValue # | |
Defined in Text.Blaze.Internal Methods fromString :: String -> AttributeValue # | |
Semigroup AttributeValue # | |
Defined in Text.Blaze.Internal Methods (<>) :: AttributeValue -> AttributeValue -> AttributeValue # sconcat :: NonEmpty AttributeValue -> AttributeValue # stimes :: Integral b => b -> AttributeValue -> AttributeValue # | |
Monoid AttributeValue # | |
Defined in Text.Blaze.Internal Methods mappend :: AttributeValue -> AttributeValue -> AttributeValue # mconcat :: [AttributeValue] -> AttributeValue # | |
ToValue AttributeValue # | |
Defined in Text.Blaze Methods toValue :: AttributeValue -> AttributeValue # |
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 BlazeMarkup using this function. The above fragment could be described using BlazeMarkup with:
p ! dataAttribute "foo" "bar" $ "Hello."
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 allowing us to use a single function for Markup values
Minimal complete definition
Methods
Convert a value to Markup.
preEscapedToMarkup :: a -> Markup #
Convert a value to Markup without escaping
Instances
ToMarkup Bool # | |
Defined in Text.Blaze | |
ToMarkup Char # | |
Defined in Text.Blaze | |
ToMarkup Double # | |
Defined in Text.Blaze | |
ToMarkup Float # | |
Defined in Text.Blaze | |
ToMarkup Int # | |
Defined in Text.Blaze | |
ToMarkup Int32 # | |
Defined in Text.Blaze | |
ToMarkup Int64 # | |
Defined in Text.Blaze | |
ToMarkup Integer # | |
Defined in Text.Blaze | |
ToMarkup Natural # | |
Defined in Text.Blaze | |
ToMarkup Word # | |
Defined in Text.Blaze | |
ToMarkup Word32 # | |
Defined in Text.Blaze | |
ToMarkup Word64 # | |
Defined in Text.Blaze | |
ToMarkup String # | |
Defined in Text.Blaze | |
ToMarkup Text # | |
Defined in Text.Blaze | |
ToMarkup Text # | |
Defined in Text.Blaze | |
ToMarkup Builder # | |
Defined in Text.Blaze | |
ToMarkup Markup # | |
Defined in Text.Blaze | |
ToMarkup [Markup] # | |
Defined in Text.Blaze |
Render text. Functions like these can be used to supply content in HTML.
Render text without escaping.
A variant of preEscapedText
for lazy Text
Create an HTML snippet from a ChoiceString
.
Create an HTML snippet from a ChoiceString
without escaping
Arguments
:: ByteString | Value to insert. |
-> Markup | Resulting HTML fragment. |
Insert a ChoiceString
. This is an unsafe operation:
- The
ChoiceString
could have the wrong encoding. - The
ChoiceString
might contain illegal HTML characters (no escaping is done).
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 #
Create a comment from a ChoiceString
value.
The text should not contain "--"
.
This is not checked by the library.
lazyTextComment :: Text -> Markup #
Create a comment from a Text
value.
The text should not contain "--"
.
This is not checked by the library.
stringComment :: String -> Markup #
Create a comment from a ChoiceString
value.
The text should not contain "--"
.
This is not checked by the library.
unsafeByteStringComment :: ByteString -> Markup #
Create a comment from a ChoiceString
value.
The text should not contain "--"
.
This is not checked by the library.
unsafeLazyByteStringComment :: ByteString -> Markup #
Create a comment from a ByteString
value.
The text should not contain "--"
.
This is not checked by the library.
Creating tags.
Create a Tag
from some ChoiceString
.
Create a Tag
from a ChoiceString
.
Converting values to attribute values.
Class allowing us to use a single function for attribute values
Minimal complete definition
Methods
toValue :: a -> AttributeValue #
Convert a value to an attribute value
preEscapedToValue :: a -> AttributeValue #
Convert a value to an attribute value without escaping
Instances
ToValue Bool # | |
Defined in Text.Blaze | |
ToValue Char # | |
Defined in Text.Blaze | |
ToValue Double # | |
Defined in Text.Blaze | |
ToValue Float # | |
Defined in Text.Blaze | |
ToValue Int # | |
Defined in Text.Blaze | |
ToValue Int32 # | |
Defined in Text.Blaze | |
ToValue Int64 # | |
Defined in Text.Blaze | |
ToValue Integer # | |
Defined in Text.Blaze | |
ToValue Word # | |
Defined in Text.Blaze | |
ToValue Word32 # | |
Defined in Text.Blaze | |
ToValue Word64 # | |
Defined in Text.Blaze | |
ToValue String # | |
Defined in Text.Blaze | |
ToValue Text # | |
Defined in Text.Blaze | |
ToValue Text # | |
Defined in Text.Blaze | |
ToValue Builder # | |
Defined in Text.Blaze | |
ToValue AttributeValue # | |
Defined in Text.Blaze Methods toValue :: AttributeValue -> AttributeValue # |
Arguments
:: Text | The actual value. |
-> AttributeValue | Resulting attribute value. |
Render an attribute value from ChoiceString
.
Arguments
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
Render an attribute value from ChoiceString
without escaping.
Arguments
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
Arguments
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
A variant of preEscapedTextValue
for lazy Text
stringValue :: String -> AttributeValue #
Create an attribute value from a ChoiceString
.
preEscapedStringValue :: String -> AttributeValue #
Create an attribute value from a ChoiceString
without escaping.
Arguments
:: ByteString | ByteString value |
-> AttributeValue | Resulting attribute value |
Create an attribute value from a ChoiceString
. See unsafeByteString
for reasons why this might not be a good idea.
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 #
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 #
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"