Safe Haskell | None |
---|---|
Language | Haskell98 |
- reexports from Text.Blaze
- Creating attributes.
- Converting values to Markup.
- Comments
- Creating tags.
- Converting values to attribute values.
- Setting attributes
- Modifiying Markup trees
- reexports from Text.Blaze.Html
- reexports from Text.Blaze.Internal
- Important types.
- Creating custom tags and attributes.
- Converting values to Markup.
- Setting attributes
- Modifying Markup elements
- Querying Markup elements
- BlazeT new stuff
- type Markup = forall m. Monad m => MarkupT m ()
- data Tag :: *
- data Attribute :: *
- data AttributeValue :: *
- dataAttribute :: Tag -> AttributeValue -> Attribute
- customAttribute :: Tag -> AttributeValue -> Attribute
- class ToMarkup a where
- 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
- 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 :: Monad m => MarkupT m a -> MarkupT m a
- type Html = Markup
- toHtml :: ToMarkup a => a -> Html
- preEscapedToHtml :: ToMarkup a => a -> Html
- type MarkupM = MarkupT Identity
- customParent :: Tag -> Markup2
- customLeaf :: Tag -> Bool -> Markup
- textBuilder :: Builder -> Markup
- preEscapedTextBuilder :: Builder -> Markup
- class Attributable h where
- external :: Monad m => MarkupT m a -> MarkupT m a
- null :: Foldable t => forall a. t a -> Bool
- type HtmlM = MarkupM
- type HtmlT = MarkupT
- type Markup2 = forall m. Monad m => MarkupT m () -> MarkupT m ()
- mapMarkupT :: (m (a, Markup) -> n (b, Markup)) -> MarkupT m a -> MarkupT n b
- data MarkupT m a
- runMarkup :: MarkupM a -> (a, Markup)
- runMarkupT :: MarkupT m a -> m (a, Markup)
- execMarkup :: MarkupM a -> Markup
- execMarkupT :: Monad m => MarkupT m a -> m Markup
- wrapMarkup :: Markup -> Markup
- wrapMarkupT :: Monad m => Markup -> MarkupT m ()
- wrapMarkup2 :: (Markup -> Markup) -> Markup2
- wrapMarkupT2 :: Monad m => (Markup -> Markup) -> MarkupT m a -> MarkupT m a
reexports from Text.Blaze
Type for an HTML tag. This can be seen as an internal string type used by BlazeMarkup.
data AttributeValue :: * #
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 function. 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 Markup.
preEscapedText :: Text -> Markup Source #
preEscapedLazyText :: Text -> Markup Source #
preEscapedString :: String -> Markup Source #
unsafeByteString :: ByteString -> Markup Source #
:: 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 Text
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 String
value.
The text should not contain "--"
.
This is not checked by the library.
unsafeByteStringComment :: ByteString -> Markup #
Create a comment from a ByteString
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.
Converting values to attribute values.
Class allowing us to use a single function for attribute values
toValue :: a -> AttributeValue #
Convert a value to an attribute value
preEscapedToValue :: a -> AttributeValue #
Convert a value to an attribute value without escaping
:: Text | The actual value. |
-> AttributeValue | Resulting attribute value. |
Render an attribute value from Text
.
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
Render an attribute value from Text
without escaping.
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
:: Text | The actual value |
-> AttributeValue | Resulting attribute value |
A variant of preEscapedTextValue
for lazy Text
stringValue :: String -> AttributeValue #
Create an attribute value from a String
.
preEscapedStringValue :: String -> AttributeValue #
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.
:: 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"
Modifiying Markup trees
reexports from Text.Blaze.Html
preEscapedToHtml :: ToMarkup a => a -> Html Source #
reexports from Text.Blaze.Internal
Important types.
Creating custom tags and attributes.
customParent :: Tag -> Markup2 Source #
Converting values to Markup.
textBuilder :: Builder -> Markup Source #
Setting attributes
class Attributable h where #
Used for applying attributes. You should not define your own instances of this class.
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 (MarkupM a) | |
Monad m => Attributable (a -> MarkupT m b) # | |
Attributable (MarkupM a -> MarkupM b) | |
Monad m => Attributable (MarkupT m a) # | |
Modifying Markup elements
Querying Markup elements
null :: Foldable t => forall a. t a -> Bool #
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
BlazeT new stuff
mapMarkupT :: (m (a, Markup) -> n (b, Markup)) -> MarkupT m a -> MarkupT n b Source #
Map both the return value and markup of a computation using the given function
MonadTrans MarkupT Source # | |
Monad m => MonadWriter Markup (MarkupT m) Source # | |
Monad m => Monad (MarkupT m) Source # | |
Functor m => Functor (MarkupT m) Source # | |
Applicative m => Applicative (MarkupT m) Source # | |
Monad m => IsString (MarkupT m ()) Source # | |
(Monad m, Monoid a) => Monoid (MarkupT m a) Source # | |
Monad m => Attributable (a -> MarkupT m b) Source # | |
Monad m => Attributable (MarkupT m a) Source # | |
runMarkupT :: MarkupT m a -> m (a, Markup) Source #
execMarkup :: MarkupM a -> Markup Source #
wrapMarkup :: Markup -> Markup Source #