Safe Haskell | None |
---|---|
Language | Haskell98 |
- newtype MarkupT m a = MarkupT {
- fromMarkupT :: WriterT Text.Blaze.Markup m a
- type MarkupI a = MarkupT Identity a
- mapMarkupT :: (m (a, Text.Blaze.Markup) -> n (b, Text.Blaze.Markup)) -> MarkupT m a -> MarkupT n b
- type MarkupM a = forall m. Monad m => MarkupT m a
- type Markup = MarkupM ()
- type Markup2 = forall m. Monad m => MarkupT m () -> MarkupT m ()
- runMarkupT :: MarkupT m a -> m (a, Text.Blaze.Markup)
- runMarkup :: MarkupI a -> (a, Text.Blaze.Markup)
- runWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m (a, c)
- execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup
- execMarkup :: MarkupI a -> Text.Blaze.Markup
- execWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m c
- wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m ()
- wrapMarkupT2 :: Monad m => (Text.Blaze.Markup -> Text.Blaze.Markup) -> MarkupT m a -> MarkupT m a
- wrapMarkup :: Text.Blaze.Markup -> Markup
- wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2
- data ChoiceString :: *
- data StaticString :: * = StaticString {
- getString :: String -> String
- getUtf8ByteString :: BS.ByteString
- getText :: T.Text
- data Tag :: *
- data Attribute :: *
- data AttributeValue :: *
- customParent :: Tag -> Markup2
- customLeaf :: Tag -> Bool -> Markup
- attribute :: Tag -> Tag -> AttributeValue -> Attribute
- dataAttribute :: Tag -> AttributeValue -> Attribute
- customAttribute :: Tag -> AttributeValue -> Attribute
- text :: T.Text -> Markup
- preEscapedText :: T.Text -> Markup
- lazyText :: LT.Text -> Markup
- preEscapedLazyText :: LT.Text -> Markup
- textBuilder :: LTB.Builder -> Markup
- preEscapedTextBuilder :: LTB.Builder -> Markup
- string :: String -> Markup
- preEscapedString :: String -> Markup
- unsafeByteString :: BS.ByteString -> Markup
- unsafeLazyByteString :: BL.ByteString -> Markup
- textComment :: T.Text -> Markup
- lazyTextComment :: LT.Text -> Markup
- stringComment :: String -> Markup
- unsafeByteStringComment :: BS.ByteString -> Markup
- unsafeLazyByteStringComment :: BL.ByteString -> Markup
- textTag :: T.Text -> Tag
- stringTag :: String -> Tag
- textValue :: T.Text -> AttributeValue
- preEscapedTextValue :: T.Text -> AttributeValue
- lazyTextValue :: LT.Text -> AttributeValue
- preEscapedLazyTextValue :: LT.Text -> AttributeValue
- textBuilderValue :: LTB.Builder -> AttributeValue
- preEscapedTextBuilderValue :: LTB.Builder -> AttributeValue
- stringValue :: String -> AttributeValue
- preEscapedStringValue :: String -> AttributeValue
- unsafeByteStringValue :: BS.ByteString -> AttributeValue
- unsafeLazyByteStringValue :: BL.ByteString -> AttributeValue
- class Attributable h where
- (!) :: Attributable h => h -> Attribute -> h
- (!?) :: Attributable h => h -> (Bool, Attribute) -> h
- contents :: Monad m => MarkupT m a -> MarkupT m a
- external :: Monad m => MarkupT m a -> MarkupT m a
- null :: Foldable t => forall a. t a -> Bool
Entities exported only by the blazeT
version of this module
Everything is build around the simple newtype
definition of the
MarkupT
transformer, which makes use the Monoid
instance of Blaze
Text.Blaze.Markup
and is simply a WriterT
writing Blaze
Text.Blaze.Markup
:
MonadTrans MarkupT Source # | |
Monad m => MonadWriter Text.Blaze.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, Text.Blaze.Markup) -> n (b, Text.Blaze.Markup)) -> MarkupT m a -> MarkupT n b Source #
Map both the return value and markup of a computation using the given function
Specializations for blaze-markup
backwards compatibility
Running
runMarkupT :: MarkupT m a -> m (a, Text.Blaze.Markup) Source #
runMarkup :: MarkupI a -> (a, Text.Blaze.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
Executing
execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup Source #
execMarkup :: MarkupI a -> Text.Blaze.Markup Source #
Wrappers
wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m () Source #
Wrapper for Text.Blaze.Markup
is simply
tell
wrapMarkupT2 :: Monad m => (Text.Blaze.Markup -> Text.Blaze.Markup) -> MarkupT m a -> MarkupT m a Source #
Wrapper for functions that modify Text.Blaze.Markup
is simply
censor
wrapMarkup :: Text.Blaze.Markup -> Markup Source #
wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2 Source #
Entities exported also by Text.Blaze.Internal
The following is an adaptation of all Text.Blaze.Internal exports to
blazeT
types.
Entities that are reexported from Text.Blaze.Internal have the original documentation attached to them.
Entities that had to be adapted are tagged with "(Adapted)". For their documentation consult the Text.Blaze.Internal documentation.
Important types.
data ChoiceString :: * #
A string denoting input from different string representations.
Static ~StaticString | Static data |
String String | A Haskell String |
Text T.Text | A Text value |
ByteString BS.ByteString | An encoded bytestring |
PreEscaped ChoiceString | A pre-escaped string |
External ChoiceString | External data in style/script tags, should be checked for validity |
AppendChoiceString ChoiceString ChoiceString | Concatenation |
EmptyChoiceString | Empty string |
data StaticString :: * #
A static string that supports efficient output to all possible backends.
StaticString | |
|
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 custom tags and attributes.
customParent :: Tag -> Markup2 Source #
:: Tag | Raw key |
-> Tag | Shared key string for the HTML attribute. |
-> AttributeValue | Value for the HTML attribute. |
-> Attribute | Resulting HTML attribute. |
Create an HTML attribute that can be applied to an HTML element later using
the !
operator.
:: 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 :: T.Text -> Markup Source #
preEscapedLazyText :: LT.Text -> Markup Source #
textBuilder :: LTB.Builder -> Markup Source #
preEscapedString :: String -> Markup Source #
:: BL.ByteString | Value to insert |
-> Markup | Resulting HTML fragment |
Insert a lazy BL.ByteString
. See unsafeByteString
for reasons why this
is an unsafe operation.
Comments
textComment :: T.Text -> Markup Source #
lazyTextComment :: LT.Text -> Markup Source #
stringComment :: String -> Markup Source #
Converting values to tags.
Converting values to attribute values.
:: T.Text | The actual value. |
-> AttributeValue | Resulting attribute value. |
Render an attribute value from T.Text
.
:: T.Text | The actual value |
-> AttributeValue | Resulting attribute value |
Render an attribute value from T.Text
without escaping.
:: LT.Text | The actual value |
-> AttributeValue | Resulting attribute value |
:: LT.Text | The actual value |
-> AttributeValue | Resulting attribute value |
A variant of preEscapedTextValue
for lazy LT.Text
:: LTB.Builder | The actual value |
-> AttributeValue | Resulting attribute value |
A variant of textValue
for text LTB.Builder
:: LTB.Builder | The actual value |
-> AttributeValue | Resulting attribute value |
A variant of preEscapedTextValue
for text LTB.Builder
stringValue :: String -> AttributeValue #
Create an attribute value from a String
.
preEscapedStringValue :: String -> AttributeValue #
Create an attribute value from a String
without escaping.
:: BS.ByteString | ByteString value |
-> AttributeValue | Resulting attribute value |
Create an attribute value from a BS.ByteString
. See Text.Blaze.unsafeByteString
for reasons why this might not be a good idea.
:: BL.ByteString | ByteString value |
-> AttributeValue | Resulting attribute value |
Create an attribute value from a lazy BL.ByteString
. See
Text.Blaze.unsafeByteString
for reasons why this might not be a good idea.
Setting attributes
class Attributable h where #
Used for applying attributes. You should not define your own instances of this class.
Attributable (Text.Blaze.MarkupM a) | |
Monad m => Attributable (a -> MarkupT m b) # | |
Attributable (Text.Blaze.MarkupM a -> Text.Blaze.MarkupM b) | |
Monad m => Attributable (MarkupT m a) # | |
(!) :: 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"