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

Safe HaskellNone
LanguageHaskell98

Lucid

Contents

Description

Clear to write, read and edit DSL for writing HTML

See Lucid.Html5 for a complete list of Html5 combinators. That module is re-exported from this module for your convenience.

See Lucid.Base for lower level functions like makeElement, makeAttribute, termRaw, etc.

To convert html to the lucid DSL, use the (experimental) program lucid-from-html which may eventually be integrated into lucid itself.

Synopsis

Intro

HTML terms in Lucid are written with a postfix ‘_’ to indicate data rather than code. Some examples:

p_, class_, table_, style_

Note: If you're testing in the REPL you need to add a type annotation to indicate that you want HTML. In normal code your top-level declaration signatures handle that.

For GHCi:

:set -XOverloadedStrings -XExtendedDefaultRules@
import Lucid

In a module: {-# LANGUAGE OverloadedStrings, ExtendedDefaultRules #-}

Plain text is written like this, and is automatically escaped:

>>> "123 < 456" :: Html ()
123 &lt; 456

Except some elements, like script_:

>>> script_ "alert('Hello!' > 12)" :: Html ()
<script>alert('Hello!' > 12)</script>

Elements nest by function application:

>>> table_ (tr_ (td_ (p_ "Hello, World!"))) :: Html ()
<table><tr><td><p>Hello, World!</p></td></tr></table>

Elements are juxtaposed via monoidal append (remember to import Data.Monoid):

>>> p_ "hello" <> p_ "sup" :: Html ()
<p>hello</p><p>sup</p>

Or monadic sequencing:

>>> div_ (do p_ "hello"; p_ "sup") :: Html ()
<div><p>hello</p><p>sup</p></div>

Attributes are set by providing an argument list:

>>> p_ [class_ "brand"] "Lucid Inc" :: Html ()
<p class="brand">Lucid Inc</p>
>>> p_ [data_ "zot" "foo",checked_] "Go!" :: Html ()
<p data-zot="foo" checked>go</p>

Attribute and element terms are not conflicting:

>>> style_ [style_ "inception"] "Go deeper." :: Html ()
<style style="inception">Go deeper.</style>

Here is a fuller example of Lucid:

table_ [rows_ "2"]
       (tr_ (do td_ [class_ "top",colspan_ "2",style_ "color:red"]
                    (p_ "Hello, attributes!")
                td_ "yay!"))

Elements (and some attributes) are variadic and overloaded, see the Term class for more explanation about that.

For proper rendering you can easily run some HTML immediately with:

>>> renderText (p_ "Hello!")
> "<p>Hello!</p>"
>>> renderBS (p_ [style_ "color:red"] "Hello!")
"<p style=\"color:red\">Hello!</p>"

For ease of use in GHCi, there is a Show instance, as demonstrated above.

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

If the above rendering functions aren't suited for your purpose, you can run the monad directly and use the more low-level blaze Builder, which has a plethora of output modes in Blaze.ByteString.Builder.

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 (HashMap Text Text -> 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 this argument for a top-level call. See evalHtmlT and execHtmlT for easier to use functions.

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

Used for lift.

Instance details

Defined in Lucid.Base

Methods

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

MonadWriter w m => MonadWriter w (HtmlT m) Source #

Since: 2.9.9

Instance details

Defined in Lucid.Base

Methods

writer :: (a, w) -> HtmlT m a #

tell :: w -> HtmlT m () #

listen :: HtmlT m a -> HtmlT m (a, w) #

pass :: HtmlT m (a, w -> w) -> HtmlT m a #

MonadState s m => MonadState s (HtmlT m) Source #

Since: 2.9.7

Instance details

Defined in Lucid.Base

Methods

get :: HtmlT m s #

put :: s -> HtmlT m () #

state :: (s -> (a, s)) -> HtmlT m a #

MonadReader r m => MonadReader r (HtmlT m) Source #

Since: 2.9.7

Instance details

Defined in Lucid.Base

Methods

ask :: HtmlT m r #

local :: (r -> r) -> HtmlT m a -> HtmlT m a #

reader :: (r -> a) -> HtmlT m a #

MonadError e m => MonadError e (HtmlT m) Source #

Since: 2.9.9

Instance details

Defined in Lucid.Base

Methods

throwError :: e -> HtmlT m a #

catchError :: HtmlT m a -> (e -> HtmlT m a) -> HtmlT m a #

(Monad m, a ~ ()) => TermRaw Text (HtmlT m a) Source #

Given children immediately, just use that and expect no attributes.

Instance details

Defined in Lucid.Base

Methods

termRaw :: Text -> Text -> HtmlT m a Source #

termRawWith :: Text -> [Attribute] -> Text -> HtmlT m a Source #

Monad m => Monad (HtmlT m) Source #

Basically acts like Writer.

Instance details

Defined in Lucid.Base

Methods

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

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

return :: a -> HtmlT m a #

fail :: String -> HtmlT m a #

Functor m => Functor (HtmlT m) Source #

Just re-uses Monad.

Instance details

Defined in Lucid.Base

Methods

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

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

MonadFix m => MonadFix (HtmlT m) Source # 
Instance details

Defined in Lucid.Base

Methods

mfix :: (a -> HtmlT m a) -> HtmlT m a #

Applicative m => Applicative (HtmlT m) Source #

Based on the monad instance.

Instance details

Defined in Lucid.Base

Methods

pure :: a -> HtmlT m a #

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

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

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

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

MonadIO m => MonadIO (HtmlT m) Source #

If you want to use IO in your HTML generation.

Instance details

Defined in Lucid.Base

Methods

liftIO :: IO a -> HtmlT m a #

MFunctor HtmlT Source #

Since: 2.9.5

Instance details

Defined in Lucid.Base

Methods

hoist :: Monad m => (forall a. m a -> n a) -> HtmlT m b -> HtmlT n b #

(Monad m, ToHtml f, a ~ ()) => TermRaw [Attribute] (f -> HtmlT m a) Source #

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

termRaw :: Text -> [Attribute] -> f -> HtmlT m a Source #

termRawWith :: Text -> [Attribute] -> [Attribute] -> f -> HtmlT m a Source #

(Applicative m, f ~ HtmlT m a) => Term [Attribute] (f -> HtmlT m a) Source #

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

term :: Text -> [Attribute] -> f -> HtmlT m a Source #

termWith :: Text -> [Attribute] -> [Attribute] -> f -> HtmlT m a Source #

m ~ Identity => Show (HtmlT m a) Source #

Just calls renderText.

Instance details

Defined in Lucid.Base

Methods

showsPrec :: Int -> HtmlT m a -> ShowS #

show :: HtmlT m a -> String #

showList :: [HtmlT m a] -> ShowS #

(Monad m, a ~ ()) => IsString (HtmlT m a) Source #

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

Instance details

Defined in Lucid.Base

Methods

fromString :: String -> HtmlT m a #

(a ~ (), Applicative m) => Semigroup (HtmlT m a) Source #

Since: 2.9.7

Instance details

Defined in Lucid.Base

Methods

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

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

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

(a ~ (), Applicative m) => Monoid (HtmlT m a) Source #

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

Instance details

Defined in Lucid.Base

Methods

mempty :: HtmlT m a #

mappend :: HtmlT m a -> HtmlT m a -> HtmlT m a #

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

Functor m => With (HtmlT m a -> HtmlT m a) Source #

For the contentful elements: div_

Instance details

Defined in Lucid.Base

Methods

with :: (HtmlT m a -> HtmlT m a) -> [Attribute] -> HtmlT m a -> HtmlT m a Source #

Functor m => With (HtmlT m a) Source #

For the contentless elements: br_

Instance details

Defined in Lucid.Base

Methods

with :: HtmlT m a -> [Attribute] -> HtmlT m a Source #

(a ~ (), m ~ Identity) => ToHtml (HtmlT m a) Source #

Since: 2.9.8

Instance details

Defined in Lucid.Base

Methods

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

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

Applicative m => Term (HtmlT m a) (HtmlT m a) Source #

Given children immediately, just use that and expect no attributes.

Instance details

Defined in Lucid.Base

Methods

term :: Text -> HtmlT m a -> HtmlT m a Source #

termWith :: Text -> [Attribute] -> HtmlT m a -> HtmlT m a Source #

data Attribute Source #

A simple attribute. Don't use the constructor, use makeAttribute.

Instances
Eq Attribute Source # 
Instance details

Defined in Lucid.Base

Show Attribute Source # 
Instance details

Defined in Lucid.Base

Hashable Attribute Source # 
Instance details

Defined in Lucid.Base

TermRaw Text Attribute Source #

Some termRaws (like style_, title_) can be used for attributes as well as elements.

Instance details

Defined in Lucid.Base

Term Text Attribute Source #

Some terms (like style_, title_) can be used for attributes as well as elements.

Instance details

Defined in Lucid.Base

(Monad m, ToHtml f, a ~ ()) => TermRaw [Attribute] (f -> HtmlT m a) Source #

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

termRaw :: Text -> [Attribute] -> f -> HtmlT m a Source #

termRawWith :: Text -> [Attribute] -> [Attribute] -> f -> HtmlT m a Source #

(Applicative m, f ~ HtmlT m a) => Term [Attribute] (f -> HtmlT m a) Source #

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

term :: Text -> [Attribute] -> f -> HtmlT m a Source #

termWith :: Text -> [Attribute] -> [Attribute] -> f -> HtmlT m a Source #

Classes

To support convenient use of HTML terms, HTML terms are overloaded. Here are the following types possible for an element term accepting attributes and/or children:

p_ :: Term arg result => arg -> result
p_ :: Monad m => [Attribute] -> HtmlT m () -> HtmlT m ()
p_ :: Monad m => HtmlT m () -> HtmlT m ()

The first is the generic form. The latter two are the possible types for an element.

Elements that accept no content are always concrete:

input_ :: Monad m => [Attribute] -> HtmlT m ()

And some elements share the same name as attributes, so you can also overload them as attributes:

style_ :: TermRaw arg result => arg -> result
style_ :: Monad m => [Attribute] -> Text -> HtmlT m ()
style_ :: Monad m => Text -> HtmlT m ()
style_ :: Text -> Attribute

class Term arg result | result -> arg where Source #

Used to construct HTML terms.

Simplest use: p_ = term "p" yields p_.

Very overloaded for three cases:

  • The first case is the basic arg of [(Text,Text)] which will return a function that wants children.
  • The second is an arg which is HtmlT m (), in which case the term accepts no attributes and just the children are used for the element.
  • Finally, this is also used for overloaded attributes, like style_ or title_. If a return type of (Text,Text) is inferred then an attribute will be made.

The instances look intimidating but actually the constraints make it very general so that type inference works well even in the presence of things like OverloadedLists and such.

Minimal complete definition

termWith

Methods

term Source #

Arguments

:: Text

Name of the element or attribute.

-> arg

Either an attribute list or children.

-> result

Result: either an element or an attribute.

Used for constructing elements e.g. term "p" yields p_.

termWith Source #

Arguments

:: Text

Name.

-> [Attribute]

Attribute transformer.

-> arg

Some argument.

-> result

Result: either an element or an attribute.

Use this if you want to make an element which inserts some pre-prepared attributes into the element.

Instances
Term Text Attribute Source #

Some terms (like style_, title_) can be used for attributes as well as elements.

Instance details

Defined in Lucid.Base

(Applicative m, f ~ HtmlT m a) => Term [Attribute] (f -> HtmlT m a) Source #

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

term :: Text -> [Attribute] -> f -> HtmlT m a Source #

termWith :: Text -> [Attribute] -> [Attribute] -> f -> HtmlT m a Source #

Applicative m => Term (HtmlT m a) (HtmlT m a) Source #

Given children immediately, just use that and expect no attributes.

Instance details

Defined in Lucid.Base

Methods

term :: Text -> HtmlT m a -> HtmlT m a Source #

termWith :: Text -> [Attribute] -> HtmlT m a -> HtmlT m a Source #

class ToHtml a where Source #

Can be converted to HTML.

Methods

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

Convert to HTML, doing HTML escaping.

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

Convert to HTML without any escaping.

Instances
ToHtml String Source # 
Instance details

Defined in Lucid.Base

Methods

toHtml :: Monad m => String -> HtmlT m () Source #

toHtmlRaw :: Monad m => String -> HtmlT m () Source #

ToHtml ByteString Source #

This instance requires the ByteString to contain UTF-8 encoded text, for the toHtml method. The toHtmlRaw method doesn't care, but the overall HTML rendering methods in this module assume UTF-8.

Since: 2.9.5

Instance details

Defined in Lucid.Base

Methods

toHtml :: Monad m => ByteString -> HtmlT m () Source #

toHtmlRaw :: Monad m => ByteString -> HtmlT m () Source #

ToHtml ByteString Source #

This instance requires the ByteString to contain UTF-8 encoded text, for the toHtml method. The toHtmlRaw method doesn't care, but the overall HTML rendering methods in this module assume UTF-8.

Since: 2.9.5

Instance details

Defined in Lucid.Base

Methods

toHtml :: Monad m => ByteString -> HtmlT m () Source #

toHtmlRaw :: Monad m => ByteString -> HtmlT m () Source #

ToHtml Text Source # 
Instance details

Defined in Lucid.Base

Methods

toHtml :: Monad m => Text -> HtmlT m () Source #

toHtmlRaw :: Monad m => Text -> HtmlT m () Source #

ToHtml Text Source # 
Instance details

Defined in Lucid.Base

Methods

toHtml :: Monad m => Text -> HtmlT m () Source #

toHtmlRaw :: Monad m => Text -> HtmlT m () Source #

(a ~ (), m ~ Identity) => ToHtml (HtmlT m a) Source #

Since: 2.9.8

Instance details

Defined in Lucid.Base

Methods

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

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

class With a where Source #

With an element use these attributes. An overloaded way of adding attributes either to an element accepting attributes-and-children or one that just accepts attributes. See the two instances.

Methods

with Source #

Arguments

:: a

Some element, either Html a or Html a -> Html a.

-> [Attribute] 
-> a 

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

Instances
Functor m => With (HtmlT m a -> HtmlT m a) Source #

For the contentful elements: div_

Instance details

Defined in Lucid.Base

Methods

with :: (HtmlT m a -> HtmlT m a) -> [Attribute] -> HtmlT m a -> HtmlT m a Source #

Functor m => With (HtmlT m a) Source #

For the contentless elements: br_

Instance details

Defined in Lucid.Base

Methods

with :: HtmlT m a -> [Attribute] -> HtmlT m a Source #

Re-exports