| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Text.BlazeT
Contents
- type Markup = MarkupM ()
- 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- 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 :: Monad m => MarkupT m a -> MarkupT m a
- newtype MarkupT m a = MarkupT {- fromMarkupT :: WriterT Markup m a
 
- type MarkupI a = MarkupT Identity a
- mapMarkupT :: (m (a, Markup) -> n (b, Markup)) -> MarkupT m a -> MarkupT n b
- type MarkupM a = forall m. Monad m => MarkupT m a
- type Markup2 = forall m. Monad m => MarkupT m () -> MarkupT m ()
- runMarkupT :: MarkupT m a -> m (a, Markup)
- runMarkup :: MarkupI a -> (a, Markup)
- runWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m (a, c)
- execMarkupT :: Monad m => MarkupT m a -> m Markup
- execMarkup :: MarkupI a -> Markup
- execWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m c
DO NOT READ THIS. READ Text.BlazeT.Internal INSTEAD
Due due a Haddock bug, this documentation is misleading. Please read Text.BlazeT.Internal instead.
(The bug shows both Text.Blaze.Markup and Text.BlazeT.Markup as
 Markup.)
Use this documentation only to see which entities are exported by this module.
DO NOT READ THIS
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.
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"
preEscapedText :: Text -> Markup Source #
preEscapedLazyText :: Text -> Markup Source #
preEscapedString :: String -> Markup Source #
unsafeByteString :: ByteString -> Markup Source #
Arguments
| :: ByteString | Value to insert | 
| -> Markup | Resulting HTML fragment | 
Insert a lazy ByteString. See unsafeByteString for reasons why this
 is an unsafe operation.
textComment :: Text -> Markup Source #
lazyTextComment :: Text -> Markup Source #
stringComment :: String -> Markup Source #
Class allowing us to use a single function for attribute values
Minimal complete definition
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 | 
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 String.
preEscapedStringValue :: String -> AttributeValue #
Create an attribute value from a String without escaping.
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.
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.
(!) :: 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"
Everything is build around the simple newtype definition of the
MarkupT transformer, which makes use the Monoid instance of Blaze
Markup and is simply a WriterT writing Blaze
Markup:
Constructors
| MarkupT | |
| Fields 
 | |
Instances
| 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 # | |
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
runMarkupT :: MarkupT m a -> m (a, Markup) Source #
runWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m (a, c) Source #
run the MarkupT and return a pair consisting of the result of the
 computation and the blaze markup rendered with a blaze renderer
 like renderHtml
execMarkup :: MarkupI a -> Markup Source #