blazeT-0.0.6: A true monad (transformer) version of the blaze-markup and blaze-html libraries
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.BlazeT.Internal

Synopsis

Entities exported only by the blazeT version of this module

newtype MarkupT m a Source #

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

Instances details
MonadTrans MarkupT Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

lift :: Monad m => m a -> MarkupT m a #

Monad m => MonadWriter Markup (MarkupT m) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

writer :: (a, Markup) -> MarkupT m a #

tell :: Markup -> MarkupT m () #

listen :: MarkupT m a -> MarkupT m (a, Markup) #

pass :: MarkupT m (a, Markup -> Markup) -> MarkupT m a #

Applicative m => Applicative (MarkupT m) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

pure :: a -> MarkupT m a #

(<*>) :: MarkupT m (a -> b) -> MarkupT m a -> MarkupT m b #

liftA2 :: (a -> b -> c) -> MarkupT m a -> MarkupT m b -> MarkupT m c #

(*>) :: MarkupT m a -> MarkupT m b -> MarkupT m b #

(<*) :: MarkupT m a -> MarkupT m b -> MarkupT m a #

Functor m => Functor (MarkupT m) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

fmap :: (a -> b) -> MarkupT m a -> MarkupT m b #

(<$) :: a -> MarkupT m b -> MarkupT m a #

Monad m => Monad (MarkupT m) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

(>>=) :: MarkupT m a -> (a -> MarkupT m b) -> MarkupT m b #

(>>) :: MarkupT m a -> MarkupT m b -> MarkupT m b #

return :: a -> MarkupT m a #

Monad m => IsString (MarkupT m ()) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

fromString :: String -> MarkupT m () #

(Monad m, Semigroup a) => Semigroup (MarkupT m a) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

(<>) :: MarkupT m a -> MarkupT m a -> MarkupT m a #

sconcat :: NonEmpty (MarkupT m a) -> MarkupT m a #

stimes :: Integral b => b -> MarkupT m a -> MarkupT m a #

Monad m => Attributable (MarkupT m a) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

(!) :: MarkupT m a -> Attribute -> MarkupT m a #

Monad m => Attributable (a -> MarkupT m b) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

(!) :: (a -> MarkupT m b) -> Attribute -> a -> MarkupT m b #

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

type MarkupM a = forall m. Monad m => MarkupT m a Source #

type Markup2 = forall m. Monad m => MarkupT m () -> MarkupT m () Source #

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

execWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m c Source #

Wrappers

wrapMarkupT :: Monad m => Markup -> MarkupT m () Source #

Wrapper for Markup is simply tell

wrapMarkupT2 :: Monad m => (Markup -> Markup) -> MarkupT m a -> MarkupT m a Source #

Wrapper for functions that modify Markup is simply censor

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

data StaticString #

A static string that supports efficient output to all possible backends.

Constructors

StaticString 

Fields

Instances

Instances details
IsString StaticString 
Instance details

Defined in Text.Blaze.Internal

data Tag #

Type for an HTML tag. This can be seen as an internal string type used by BlazeMarkup.

Instances

Instances details
IsString Tag 
Instance details

Defined in Text.Blaze.Internal

Methods

fromString :: String -> Tag #

data Attribute #

Type for an attribute.

Instances

Instances details
Monoid Attribute 
Instance details

Defined in Text.Blaze.Internal

Semigroup Attribute 
Instance details

Defined in Text.Blaze.Internal

Creating custom tags and attributes.

attribute #

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.

dataAttribute #

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."

customAttribute #

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.

unsafeLazyByteString 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

Converting values to tags.

textTag #

Arguments

:: Text

Text to create a tag from

-> Tag

Resulting tag

Create a Tag from some ChoiceString.

stringTag #

Arguments

:: String

String to create a tag from

-> Tag

Resulting tag

Create a Tag from a ChoiceString.

Converting values to attribute values.

textValue #

Arguments

:: Text

The actual value.

-> AttributeValue

Resulting attribute value.

Render an attribute value from ChoiceString.

preEscapedTextValue #

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

Render an attribute value from ChoiceString without escaping.

lazyTextValue #

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of textValue for lazy Text

preEscapedLazyTextValue #

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of preEscapedTextValue for lazy Text

textBuilderValue #

Arguments

:: Builder

The actual value

-> AttributeValue

Resulting attribute value

A variant of textValue for text Builder

preEscapedTextBuilderValue #

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.

unsafeByteStringValue #

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.

unsafeLazyByteStringValue #

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

Instances details
Attributable (MarkupM a) 
Instance details

Defined in Text.Blaze.Internal

Methods

(!) :: MarkupM a -> Attribute -> MarkupM a #

Monad m => Attributable (MarkupT m a) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

(!) :: MarkupT m a -> Attribute -> MarkupT m a #

Attributable (MarkupM a -> MarkupM b) 
Instance details

Defined in Text.Blaze.Internal

Methods

(!) :: (MarkupM a -> MarkupM b) -> Attribute -> MarkupM a -> MarkupM b #

Monad m => Attributable (a -> MarkupT m b) Source # 
Instance details

Defined in Text.BlazeT.Internal

Methods

(!) :: (a -> MarkupT m b) -> Attribute -> a -> MarkupT m b #

(!) :: 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

contents :: Monad m => MarkupT m a -> MarkupT m a Source #

external :: Monad m => MarkupT m a -> MarkupT m a Source #

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

Expand

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