front-0.0.0.1: A reactive frontend web framework

Safe HaskellNone
LanguageHaskell2010

Text.Blaze.Front.Internal

Contents

Description

The BlazeMarkup core, consisting of functions that offer the power to generate custom markup elements. It also offers user-centric functions, which are exposed through Blaze.

While this module is exported, usage of it is not recommended, unless you know what you are doing. This module might undergo changes at any time.

Synopsis

Important types.

data StaticString #

Instances
IsString StaticString 
Instance details

data MarkupM act a Source #

The core Markup datatype. The ev type-parameter tracks the type of events that can be raised when this Markup is rendered.

Constructors

MapActions (act' -> act) (MarkupM act' a)

Map all actions created by the inner Html.

OnEvent (EventHandler act) (MarkupM act a)

Install event handlers for the given event on all immediate children.

Parent StaticString StaticString StaticString (MarkupM act a)

Tag, open tag, end tag, content

CustomParent ChoiceString (MarkupM act a)

Custom parent

Leaf StaticString StaticString StaticString

Tag, open tag, end tag

CustomLeaf ChoiceString Bool

Custom leaf

Content ChoiceString

HTML content

Append (MarkupM act b) (MarkupM act c)

Concatenation of two HTML pieces

AddAttribute StaticString StaticString ChoiceString (MarkupM act a)

Add an attribute to the inner HTML. Raw key, key, value, HTML to receive the attribute.

AddCustomAttribute ChoiceString ChoiceString (MarkupM act a)

Add a custom attribute to the inner HTML.

Empty

Empty HTML.

Instances
Monad (MarkupM ev) Source # 
Instance details

Methods

(>>=) :: MarkupM ev a -> (a -> MarkupM ev b) -> MarkupM ev b #

(>>) :: MarkupM ev a -> MarkupM ev b -> MarkupM ev b #

return :: a -> MarkupM ev a #

fail :: String -> MarkupM ev a #

Functor (MarkupM ev) Source # 
Instance details

Methods

fmap :: (a -> b) -> MarkupM ev a -> MarkupM ev b #

(<$) :: a -> MarkupM ev b -> MarkupM ev a #

Applicative (MarkupM ev) Source # 
Instance details

Methods

pure :: a -> MarkupM ev a #

(<*>) :: MarkupM ev (a -> b) -> MarkupM ev a -> MarkupM ev b #

liftA2 :: (a -> b -> c) -> MarkupM ev a -> MarkupM ev b -> MarkupM ev c #

(*>) :: MarkupM ev a -> MarkupM ev b -> MarkupM ev b #

(<*) :: MarkupM ev a -> MarkupM ev b -> MarkupM ev a #

IsString (MarkupM ev a) Source # 
Instance details

Methods

fromString :: String -> MarkupM ev a #

Semigroup a => Semigroup (MarkupM ev a) Source # 
Instance details

Methods

(<>) :: MarkupM ev a -> MarkupM ev a -> MarkupM ev a #

sconcat :: NonEmpty (MarkupM ev a) -> MarkupM ev a #

stimes :: Integral b => b -> MarkupM ev a -> MarkupM ev a #

Monoid a => Monoid (MarkupM ev a) Source # 
Instance details

Methods

mempty :: MarkupM ev a #

mappend :: MarkupM ev a -> MarkupM ev a -> MarkupM ev a #

mconcat :: [MarkupM ev a] -> MarkupM ev a #

Attributable (MarkupM ev a -> MarkupM ev b) ev Source # 
Instance details

Methods

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

Attributable (MarkupM ev a) ev Source # 
Instance details

Methods

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

type Markup e = MarkupM e () Source #

Simplification of the MarkupM datatype.

data Tag Source #

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

Instances
IsString Tag Source # 
Instance details

Methods

fromString :: String -> Tag #

newtype Attribute ev Source #

Type for an attribute.

Constructors

Attribute (forall a. MarkupM ev a -> MarkupM ev a) 
Instances
Semigroup (Attribute ev) Source # 
Instance details

Methods

(<>) :: Attribute ev -> Attribute ev -> Attribute ev #

sconcat :: NonEmpty (Attribute ev) -> Attribute ev #

stimes :: Integral b => b -> Attribute ev -> Attribute ev #

Monoid (Attribute ev) Source # 
Instance details

Methods

mempty :: Attribute ev #

mappend :: Attribute ev -> Attribute ev -> Attribute ev #

mconcat :: [Attribute ev] -> Attribute ev #

Creating custom tags and attributes.

customParent Source #

Arguments

:: Tag

Element tag

-> Markup ev

Content

-> Markup ev

Resulting markup

Create a custom parent element

customLeaf Source #

Arguments

:: Tag

Element tag

-> Bool

Close the leaf?

-> Markup ev

Resulting markup

Create a custom leaf element

attribute Source #

Arguments

:: Tag

Raw key

-> Tag

Shared key string for the HTML attribute.

-> AttributeValue

Value for the HTML attribute.

-> Attribute ev

Resulting HTML attribute.

Create an HTML attribute that can be applied to an HTML element later using the ! operator.

dataAttribute Source #

Arguments

:: Tag

Name of the attribute.

-> AttributeValue

Value for the attribute.

-> Attribute ev

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 funcion. The above fragment could be described using BlazeMarkup with:

p ! dataAttribute "foo" "bar" $ "Hello."

customAttribute Source #

Arguments

:: Tag

Name of the attribute

-> AttributeValue

Value for the attribute

-> Attribute ev

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.

text Source #

Arguments

:: Text

Text to render.

-> Markup ev

Resulting HTML fragment.

Render text. Functions like these can be used to supply content in HTML.

preEscapedText Source #

Arguments

:: Text

Text to insert

-> Markup ev

Resulting HTML fragment

Render text without escaping.

lazyText Source #

Arguments

:: Text

Text to insert

-> Markup ev

Resulting HTML fragment

A variant of text for lazy Text.

preEscapedLazyText Source #

Arguments

:: Text

Text to insert

-> Markup ev

Resulting HTML fragment

A variant of preEscapedText for lazy Text

string Source #

Arguments

:: String

String to insert.

-> Markup ev

Resulting HTML fragment.

Create an HTML snippet from a String.

preEscapedString Source #

Arguments

:: String

String to insert.

-> Markup ev

Resulting HTML fragment.

Create an HTML snippet from a String without escaping

unsafeByteString Source #

Arguments

:: ByteString

Value to insert.

-> Markup ev

Resulting HTML fragment.

Insert a ByteString. This is an unsafe operation:

  • The ByteString could have the wrong encoding.
  • The ByteString might contain illegal HTML characters (no escaping is done).

unsafeLazyByteString Source #

Arguments

:: ByteString

Value to insert

-> Markup ev

Resulting HTML fragment

Insert a lazy ByteString. See unsafeByteString for reasons why this is an unsafe operation.

Converting values to tags.

textTag Source #

Arguments

:: Text

Text to create a tag from

-> Tag

Resulting tag

Create a Tag from some Text.

stringTag Source #

Arguments

:: String

String to create a tag from

-> Tag

Resulting tag

Create a Tag from a String.

Converting values to attribute values.

textValue Source #

Arguments

:: Text

The actual value.

-> AttributeValue

Resulting attribute value.

Render an attribute value from Text.

preEscapedTextValue Source #

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

Render an attribute value from Text without escaping.

lazyTextValue Source #

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of textValue for lazy Text

preEscapedLazyTextValue Source #

Arguments

:: Text

The actual value

-> AttributeValue

Resulting attribute value

A variant of preEscapedTextValue for lazy Text

stringValue :: String -> AttributeValue Source #

Create an attribute value from a String.

preEscapedStringValue :: String -> AttributeValue Source #

Create an attribute value from a String without escaping.

unsafeByteStringValue Source #

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 Source #

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 ev | h -> ev Source #

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

Minimal complete definition

(!)

Instances
Attributable (MarkupM ev a -> MarkupM ev b) ev Source # 
Instance details

Methods

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

Attributable (MarkupM ev a) ev Source # 
Instance details

Methods

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

(!) :: Attributable h ev => h -> Attribute ev -> h Source #

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 ev => h -> (Bool, Attribute ev) -> h Source #

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 :: MarkupM ev a -> MarkupM ev' b Source #

Take only the text content of an HTML tree.

contents $ do
    p ! $ "Hello "
    p ! $ "Word!"

Result:

Hello World!

external :: MarkupM ev a -> MarkupM ev a Source #

Mark HTML as external data. External data can be:

This function is applied automatically when using the style or script combinators.

Querying Markup elements

null :: MarkupM ev a -> Bool Source #

Check if a Markup value is completely empty (renders to the empty string).