| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Text.BlazeT.Internal
Synopsis
- 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 Markup = MarkupM ()
- 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
- wrapMarkupT :: Monad m => Markup -> MarkupT m ()
- wrapMarkupT2 :: Monad m => (Markup -> Markup) -> MarkupT m a -> MarkupT m a
- wrapMarkup :: Markup -> Markup
- wrapMarkup2 :: (Markup -> Markup) -> Markup2
- data ChoiceString
- data StaticString = StaticString {
- getString :: String -> String
- getUtf8ByteString :: ByteString
- getText :: 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 :: Text -> Markup
- preEscapedText :: Text -> Markup
- lazyText :: Text -> Markup
- preEscapedLazyText :: Text -> Markup
- textBuilder :: Builder -> Markup
- preEscapedTextBuilder :: Builder -> 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
- textValue :: Text -> AttributeValue
- preEscapedTextValue :: Text -> AttributeValue
- lazyTextValue :: Text -> AttributeValue
- preEscapedLazyTextValue :: Text -> AttributeValue
- textBuilderValue :: Builder -> AttributeValue
- preEscapedTextBuilderValue :: Builder -> AttributeValue
- stringValue :: String -> AttributeValue
- preEscapedStringValue :: String -> AttributeValue
- unsafeByteStringValue :: ByteString -> AttributeValue
- unsafeLazyByteStringValue :: ByteString -> AttributeValue
- class Attributable h
- (!) :: 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 => 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
Markup and is simply a WriterT writing Blaze
Markup:
Constructors
| MarkupT | |
Fields
| |
Instances
| MonadTrans MarkupT Source # | |
Defined in Text.BlazeT.Internal | |
| Monad m => MonadWriter Markup (MarkupT m) Source # | |
| Applicative m => Applicative (MarkupT m) Source # | |
| Functor m => Functor (MarkupT m) Source # | |
| Monad m => Monad (MarkupT m) Source # | |
| Monad m => IsString (MarkupT m ()) Source # | |
Defined in Text.BlazeT.Internal Methods fromString :: String -> MarkupT m () # | |
| (Monad m, Semigroup a) => Semigroup (MarkupT m a) Source # | |
| Monad m => Attributable (MarkupT m a) Source # | |
| Monad m => Attributable (a -> MarkupT m b) 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
Specializations for blaze-markup backwards compatibility
Running
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
Executing
execMarkup :: MarkupI a -> Markup Source #
Wrappers
wrapMarkup :: Markup -> Markup 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.
Constructors
| Static !StaticString | Static data |
| String String | A Haskell String |
| Text Text | A Text value |
| ByteString 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 |
Instances
| IsString ChoiceString | |
Defined in Text.Blaze.Internal Methods fromString :: String -> ChoiceString # | |
| Monoid ChoiceString | |
Defined in Text.Blaze.Internal Methods mempty :: ChoiceString # mappend :: ChoiceString -> ChoiceString -> ChoiceString # mconcat :: [ChoiceString] -> ChoiceString # | |
| Semigroup ChoiceString | |
Defined in Text.Blaze.Internal Methods (<>) :: ChoiceString -> ChoiceString -> ChoiceString # sconcat :: NonEmpty ChoiceString -> ChoiceString # stimes :: Integral b => b -> ChoiceString -> ChoiceString # | |
data StaticString #
A static string that supports efficient output to all possible backends.
Constructors
| StaticString | |
Fields
| |
Instances
| IsString StaticString | |
Defined in Text.Blaze.Internal Methods fromString :: String -> StaticString # | |
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 # | |
| Monoid AttributeValue | |
Defined in Text.Blaze.Internal Methods mappend :: AttributeValue -> AttributeValue -> AttributeValue # mconcat :: [AttributeValue] -> AttributeValue # | |
| Semigroup AttributeValue | |
Defined in Text.Blaze.Internal Methods (<>) :: AttributeValue -> AttributeValue -> AttributeValue # sconcat :: NonEmpty AttributeValue -> AttributeValue # stimes :: Integral b => b -> AttributeValue -> AttributeValue # | |
| ToValue AttributeValue | |
Defined in Text.Blaze Methods toValue :: AttributeValue -> AttributeValue # | |
Creating custom tags and attributes.
customParent :: Tag -> Markup2 Source #
Arguments
| :: 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.
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.
preEscapedText :: Text -> Markup Source #
preEscapedLazyText :: Text -> Markup Source #
textBuilder :: Builder -> 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.
Comments
textComment :: Text -> Markup Source #
lazyTextComment :: Text -> Markup Source #
stringComment :: String -> Markup Source #
Converting values to tags.
Create a Tag from some ChoiceString.
Create a Tag from a ChoiceString.
Converting values to attribute values.
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
Arguments
| :: Builder | The actual value |
| -> AttributeValue | Resulting attribute value |
Arguments
| :: Builder | The actual value |
| -> AttributeValue | Resulting attribute value |
A variant of preEscapedTextValue for text Builder
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
class Attributable h #
Used for applying attributes. You should not define your own instances of this class.
Minimal complete definition
Instances
| Attributable (MarkupM a) | |
| Monad m => Attributable (MarkupT m a) Source # | |
| Attributable (MarkupM a -> MarkupM b) | |
| Monad m => Attributable (a -> MarkupT m b) Source # | |
(!) :: 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"
Modifying Markup elements
Querying Markup elements
null :: Foldable t => t a -> Bool #
Test whether the structure is empty. The default implementation is Left-associative and lazy in both the initial element and the accumulator. Thus optimised for structures where the first element can be accessed in constant time. Structures where this is not the case should have a non-default implementation.
Examples
Basic usage:
>>>null []True
>>>null [1]False
null is expected to terminate even for infinite structures.
The default implementation terminates provided the structure
is bounded on the left (there is a leftmost element).
>>>null [1..]False
Since: base-4.8.0.0