lucid-0.2: Clear to write, read and edit DSL for HTML

Safe HaskellNone
LanguageHaskell98

Lucid.Base

Contents

Description

Base types and combinators.

Synopsis

Rendering

renderText :: Html a -> Text Source

Render the HTML to a lazy Text.

This is a convenience function defined in terms of execHtmlT, runIdentity and toLazyByteString, and decodeUtf8. Check the source if you're interested in the lower-level behaviour.

renderBS :: Html a -> ByteString Source

Render the HTML to a lazy ByteString.

This is a convenience function defined in terms of execHtmlT, runIdentity and toLazyByteString. Check the source if you're interested in the lower-level behaviour.

renderTextT :: Monad m => HtmlT m a -> m Text Source

Render the HTML to a lazy Text, but in a monad.

This is a convenience function defined in terms of execHtmlT and toLazyByteString, and decodeUtf8. Check the source if you're interested in the lower-level behaviour.

renderBST :: Monad m => HtmlT m a -> m ByteString Source

Render the HTML to a lazy ByteString, but in a monad.

This is a convenience function defined in terms of execHtmlT and toLazyByteString. Check the source if you're interested in the lower-level behaviour.

renderToFile :: FilePath -> Html a -> IO () Source

Render the HTML to a lazy ByteString.

This is a convenience function defined in terms of execHtmlT, runIdentity and toLazyByteString. Check the source if you're interested in the lower-level behaviour.

Running

execHtmlT Source

Arguments

:: Monad m 
=> HtmlT m a

The HTML to generate.

-> m Builder

The a is discarded.

Build the HTML. Analogous to execState.

You might want to use this is if you want to do something with the raw Builder. Otherwise for simple cases you can just use renderText or renderBS.

evalHtmlT Source

Arguments

:: Monad m 
=> HtmlT m a

HTML monad to evaluate.

-> m a

Ignore the HTML output and just return the value.

Evaluate the HTML to its return value. Analogous to evalState.

Use this if you want to ignore the HTML output of an action completely and just get the result.

For using with the Html type, you'll need runIdentity e.g.

>>> runIdentity (evalHtmlT (p_ "Hello!"))
()

runHtmlT :: HtmlT m a -> m (Builder -> Builder -> Builder, a) Source

This is the low-level way to run the HTML transformer, finally returning an element builder and a value. You can pass mempty for both arguments for a top-level call. See evalHtmlT and execHtmlT for easier to use functions.

Combinators

makeElement Source

Arguments

:: Monad m 
=> Builder

Name.

-> HtmlT m a

Children HTML.

-> HtmlT m ()

A parent element.

Make an HTML builder.

makeElementNoEnd Source

Arguments

:: Monad m 
=> Builder

Name.

-> HtmlT m ()

A parent element.

Make an HTML builder for

Types

type Html = HtmlT Identity Source

Simple HTML builder type. Defined in terms of HtmlT. Check out that type for instance information.

Simple use-cases will just use this type. But if you want to transformer over Reader or something, you can go and use HtmlT.

data Attr Source

An attribute.

Constructors

Attr 

Fields

attrName :: !Builder

The attribute name.

attrValue :: !Text

The attribute value.

Instances

ToText a => Mixed a Attr

Attributes can be a mixed thing e.g. style_.

data HtmlT m a Source

A monad transformer that generates HTML. Use the simpler Html type if you don't want to transform over some other monad.

Instances

MonadTrans HtmlT

Used for lift.

(Monad m, (~) * a (HtmlT m r), (~) * r ()) => Mixed a (HtmlT m r)

HTML elements can be a mixed thing e.g. style_.

Monad m => Monad (HtmlT m)

Basically acts like Writer.

Monad m => Functor (HtmlT m)

Just re-uses Monad.

Monad m => Applicative (HtmlT m)

Based on the monad instance.

Monoid a => Monoid (Html a)

Monoid is right-associative, a la the Builder in it.

MonadIO m => MonadIO (HtmlT m)

If you want to use IO in your HTML generation.

(~) (* -> *) m Identity => Show (HtmlT m a)

Just calls renderText.

(Monad m, (~) * a ()) => IsString (HtmlT m a)

We pack it via string. Could possibly encode straight into a builder. That might be faster.

(Monad m, (~) * a ()) => With (HtmlT m a -> HtmlT m a)

For the contentful elements: div_

(Monad m, (~) * a ()) => With (HtmlT m a)

For the contentless elements: br_

Classes

class ToText a where Source

Used for attributes.

Methods

toText :: a -> Text Source

Instances

class ToHtml a where Source

Can be converted to HTML.

Methods

toHtml :: Monad m => a -> HtmlT m () Source

toHtmlRaw :: Monad m => a -> HtmlT m () Source

Instances

class Mixed a r where Source

Used for names that are mixed, e.g. style_.

Methods

mixed :: Builder -> a -> r Source

Instances

ToText a => Mixed a Attr

Attributes can be a mixed thing e.g. style_.

(Monad m, (~) * a (HtmlT m r), (~) * r ()) => Mixed a (HtmlT m r)

HTML elements can be a mixed thing e.g. style_.

class With a where Source

With an element use these attributes.

Methods

with Source

Arguments

:: a

Some element, either Html () or Html () -> Html ().

-> [Attr] 
-> a 

With the given element(s), use the given attributes.

Instances

(Monad m, (~) * a ()) => With (HtmlT m a -> HtmlT m a)

For the contentful elements: div_

(Monad m, (~) * a ()) => With (HtmlT m a)

For the contentless elements: br_