blazeT-0.0.3: A true monad (transformer) version of the blaze-markup and blaze-html libraries

Safe HaskellNone
LanguageHaskell98

Text.BlazeT

Contents

Synopsis

reexports from Text.Blaze

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

data Tag :: * #

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

Instances

data Attribute :: * #

Type for an attribute.

Creating attributes.

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.

class ToMarkup a where Source #

Minimal complete definition

toMarkup, preEscapedToMarkup

Instances

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

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.

textTag #

Arguments

:: Text

Text to create a tag from

-> Tag

Resulting tag

Create a Tag from some Text.

stringTag #

Arguments

:: String

String to create a tag from

-> Tag

Resulting tag

Create a Tag from a String.

Converting values to attribute values.

class ToValue a where #

Class allowing us to use a single function for attribute values

Minimal complete definition

toValue

Instances

ToValue Bool 
ToValue Char 
ToValue Double 
ToValue Float 
ToValue Int 
ToValue Int32 
ToValue Int64 
ToValue Integer 
ToValue Word 
ToValue Word32 
ToValue Word64 
ToValue String 
ToValue Text 
ToValue Text 
ToValue AttributeValue 
ToValue Builder 

textValue #

Arguments

:: Text

The actual value.

-> AttributeValue

Resulting attribute value.

Render an attribute value from Text.

preEscapedTextValue #

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

Render an attribute value from Text 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

stringValue :: String -> AttributeValue #

Create an attribute value from a String.

preEscapedStringValue :: String -> AttributeValue #

Create an attribute value from a String without escaping.

unsafeByteStringValue #

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.

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

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

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

reexports from Text.Blaze.Html

toHtml :: ToMarkup a => a -> Html Source #

reexports from Text.Blaze.Internal

Important types.

Creating custom tags and attributes.

Converting values to Markup.

Setting attributes

class Attributable h where #

Used for applying attributes. You should not define your own instances of this class.

Instances

Attributable (MarkupM a) 

Methods

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

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

Methods

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

Attributable (MarkupM a -> MarkupM b) 

Methods

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

Monad m => Attributable (MarkupT m a) # 

Methods

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

Modifying Markup elements

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

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

type Markup2 = forall m. Monad m => MarkupT m () -> MarkupT m () 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

data MarkupT m a Source #

Instances

MonadTrans MarkupT Source # 

Methods

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

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

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 #

Monad m => Monad (MarkupT m) Source # 

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 #

fail :: String -> MarkupT m a #

Functor m => Functor (MarkupT m) Source # 

Methods

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

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

Applicative m => Applicative (MarkupT m) Source # 

Methods

pure :: a -> MarkupT m a #

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

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

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

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

Methods

fromString :: String -> MarkupT m () #

(Monad m, Monoid a) => Monoid (MarkupT m a) Source # 

Methods

mempty :: MarkupT m a #

mappend :: MarkupT m a -> MarkupT m a -> MarkupT m a #

mconcat :: [MarkupT m a] -> MarkupT m a #

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

Methods

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

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

Methods

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

runMarkupT :: MarkupT m a -> m (a, Markup) Source #

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