| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Text.Blaze.Front.Internal
Contents
Description
The BlazeMarkup core, consisting of functions that offer the power to
generate custom markup elements. It also offers user-centric functions,
which are exposed through Blaze.
While this module is exported, usage of it is not recommended, unless you know what you are doing. This module might undergo changes at any time.
Synopsis
- data ChoiceString
- data StaticString = StaticString {
- getString :: String -> String
- getUtf8ByteString :: ByteString
- getText :: Text
- data MarkupM act a
- = MapActions (act' -> act) (MarkupM act' a)
- | OnEvent (EventHandler act) (MarkupM act a)
- | Parent StaticString StaticString StaticString (MarkupM act a)
- | CustomParent ChoiceString (MarkupM act a)
- | Leaf StaticString StaticString StaticString
- | CustomLeaf ChoiceString Bool
- | Content ChoiceString
- | Append (MarkupM act b) (MarkupM act c)
- | AddAttribute StaticString StaticString ChoiceString (MarkupM act a)
- | AddCustomAttribute ChoiceString ChoiceString (MarkupM act a)
- | Empty
- type Markup e = MarkupM e ()
- data Tag
- newtype Attribute ev = Attribute (forall a. MarkupM ev a -> MarkupM ev a)
- newtype AttributeValue = AttributeValue {}
- customParent :: Tag -> Markup ev -> Markup ev
- customLeaf :: Tag -> Bool -> Markup ev
- attribute :: Tag -> Tag -> AttributeValue -> Attribute ev
- dataAttribute :: Tag -> AttributeValue -> Attribute ev
- customAttribute :: Tag -> AttributeValue -> Attribute ev
- text :: Text -> Markup ev
- preEscapedText :: Text -> Markup ev
- lazyText :: Text -> Markup ev
- preEscapedLazyText :: Text -> Markup ev
- string :: String -> Markup ev
- preEscapedString :: String -> Markup ev
- unsafeByteString :: ByteString -> Markup ev
- unsafeLazyByteString :: ByteString -> Markup ev
- textTag :: Text -> Tag
- stringTag :: String -> Tag
- textValue :: Text -> AttributeValue
- preEscapedTextValue :: Text -> AttributeValue
- lazyTextValue :: Text -> AttributeValue
- preEscapedLazyTextValue :: Text -> AttributeValue
- stringValue :: String -> AttributeValue
- preEscapedStringValue :: String -> AttributeValue
- unsafeByteStringValue :: ByteString -> AttributeValue
- unsafeLazyByteStringValue :: ByteString -> AttributeValue
- class Attributable h ev | h -> ev
- (!) :: Attributable h ev => h -> Attribute ev -> h
- (!?) :: Attributable h ev => h -> (Bool, Attribute ev) -> h
- contents :: MarkupM ev a -> MarkupM ev' b
- external :: MarkupM ev a -> MarkupM ev a
- null :: MarkupM ev a -> Bool
Important types.
data ChoiceString #
Constructors
| Static !StaticString | |
| String String | |
| Text Text | |
| ByteString ByteString | |
| PreEscaped ChoiceString | |
| External ChoiceString | |
| AppendChoiceString ChoiceString ChoiceString | |
| EmptyChoiceString |
Instances
| IsString ChoiceString | |
Methods fromString :: String -> ChoiceString # | |
| Semigroup ChoiceString | |
Methods (<>) :: ChoiceString -> ChoiceString -> ChoiceString # sconcat :: NonEmpty ChoiceString -> ChoiceString # stimes :: Integral b => b -> ChoiceString -> ChoiceString # | |
| Monoid ChoiceString | |
Methods mempty :: ChoiceString # mappend :: ChoiceString -> ChoiceString -> ChoiceString # mconcat :: [ChoiceString] -> ChoiceString # | |
data StaticString #
Constructors
| StaticString | |
Fields
| |
Instances
| IsString StaticString | |
Methods fromString :: String -> StaticString # | |
The core Markup datatype. The ev type-parameter tracks the type of
events that can be raised when this Markup is rendered.
Constructors
| MapActions (act' -> act) (MarkupM act' a) | Map all actions created by the inner Html. |
| OnEvent (EventHandler act) (MarkupM act a) | Install event handlers for the given event on all immediate children. |
| Parent StaticString StaticString StaticString (MarkupM act a) | Tag, open tag, end tag, content |
| CustomParent ChoiceString (MarkupM act a) | Custom parent |
| Leaf StaticString StaticString StaticString | Tag, open tag, end tag |
| CustomLeaf ChoiceString Bool | Custom leaf |
| Content ChoiceString | HTML content |
| Append (MarkupM act b) (MarkupM act c) | Concatenation of two HTML pieces |
| AddAttribute StaticString StaticString ChoiceString (MarkupM act a) | Add an attribute to the inner HTML. Raw key, key, value, HTML to receive the attribute. |
| AddCustomAttribute ChoiceString ChoiceString (MarkupM act a) | Add a custom attribute to the inner HTML. |
| Empty | Empty HTML. |
Instances
| Monad (MarkupM ev) Source # | |
| Functor (MarkupM ev) Source # | |
| Applicative (MarkupM ev) Source # | |
| IsString (MarkupM ev a) Source # | |
Methods fromString :: String -> MarkupM ev a # | |
| Semigroup a => Semigroup (MarkupM ev a) Source # | |
| Monoid a => Monoid (MarkupM ev a) Source # | |
| Attributable (MarkupM ev a -> MarkupM ev b) ev Source # | |
| Attributable (MarkupM ev a) ev Source # | |
Type for an HTML tag. This can be seen as an internal string type used by BlazeMarkup.
newtype AttributeValue Source #
The type for the value part of an attribute.
Constructors
| AttributeValue | |
Fields | |
Instances
| IsString AttributeValue Source # | |
Methods fromString :: String -> AttributeValue # | |
| Semigroup AttributeValue Source # | |
Methods (<>) :: AttributeValue -> AttributeValue -> AttributeValue # sconcat :: NonEmpty AttributeValue -> AttributeValue # stimes :: Integral b => b -> AttributeValue -> AttributeValue # | |
| Monoid AttributeValue Source # | |
Methods mappend :: AttributeValue -> AttributeValue -> AttributeValue # mconcat :: [AttributeValue] -> AttributeValue # | |
| ToValue AttributeValue Source # | |
Methods toValue :: AttributeValue -> AttributeValue Source # preEscapedToValue :: AttributeValue -> AttributeValue Source # | |
Creating custom tags and attributes.
Create a custom parent element
Create a custom leaf element
Arguments
| :: Tag | Raw key |
| -> Tag | Shared key string for the HTML attribute. |
| -> AttributeValue | Value for the HTML attribute. |
| -> Attribute ev | Resulting HTML attribute. |
Create an HTML attribute that can be applied to an HTML element later using
the ! operator.
Arguments
| :: Tag | Name of the attribute. |
| -> AttributeValue | Value for the attribute. |
| -> Attribute ev | 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."
Arguments
| :: Tag | Name of the attribute |
| -> AttributeValue | Value for the attribute |
| -> Attribute ev | 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.
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 String.
Create an HTML snippet from a String without escaping
Arguments
| :: ByteString | Value to insert. |
| -> Markup ev | 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).
Arguments
| :: ByteString | Value to insert |
| -> Markup ev | Resulting HTML fragment |
Insert a lazy ByteString. See unsafeByteString for reasons why this
is an unsafe operation.
Converting values to tags.
Converting values to attribute values.
Arguments
| :: Text | The actual value. |
| -> AttributeValue | Resulting attribute value. |
Render an attribute value from Text.
Arguments
| :: Text | The actual value |
| -> AttributeValue | Resulting attribute value |
Render an attribute value from Text without escaping.
Arguments
| :: Text | The actual value |
| -> AttributeValue | Resulting attribute value |
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
class Attributable h ev | h -> ev Source #
Used for applying attributes. You should not define your own instances of this class.
Minimal complete definition
(!) :: Attributable h ev => h -> Attribute ev -> 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 ev => h -> (Bool, Attribute ev) -> 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"
Modifying Markup elements
contents :: MarkupM ev a -> MarkupM ev' b Source #
Take only the text content of an HTML tree.
contents $ do
p ! $ "Hello "
p ! $ "Word!"Result:
Hello World!