lucid2-0.0.20220526: Clear to write, read and edit DSL for HTML
Safe HaskellNone
LanguageHaskell2010

Lucid.Base

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 :: Monad m => HtmlT m a -> m (Builder, a) Source #

Run the HtmlT transformer.

generalizeHtmlT Source #

Arguments

:: Monad m 
=> HtmlT Identity a

The HTML generated purely.

-> HtmlT m a

Same HTML accessible in a polymorphic context.

Generalize the underlying monad.

Some builders are happy to deliver results in a pure underlying monad, here Identity, but have trouble maintaining the polymorphic type. This utility generalizes from Identity.

commuteHtmlT Source #

Arguments

:: (Monad m, Monad n) 
=> HtmlT m a

unpurely generated HTML

-> m (HtmlT n a)

Commuted monads. Note: n can be Identity

Commute inner m to the front.

This is useful when you have impure HTML generation, e.g. using StateT. Recall, there is `MonadState s HtmlT` instance.

exampleHtml :: MonadState Int m => HtmlT m ()
exampleHtml = ul_ $ replicateM_ 5 $ do
  x <- get
  put (x + 1)
  li_ $ toHtml $ show x

exampleHtml' :: Monad m => HtmlT m ()
exampleHtml' = evalState (commuteHtmlT exampleHtml) 1

hoistHtmlT :: (Monad m, Monad n) => (forall a. m a -> n a) -> HtmlT m b -> HtmlT n b Source #

Switch the underlying monad.

Combinators

makeElement Source #

Arguments

:: Monad m 
=> Text

Name.

-> [Attributes] 
-> HtmlT m a

Children HTML.

-> HtmlT m a

A parent element.

Make an HTML builder.

makeElementNoEnd Source #

Arguments

:: Monad m 
=> Text

Name.

-> [Attributes] 
-> HtmlT m ()

A parent element.

Make an HTML builder for elements which have no ending tag.

makeAttributes Source #

Arguments

:: Text

Attribute name.

-> Text

Attribute value.

-> Attributes 

Make a set of attributes.

makeAttributesRaw Source #

Arguments

:: Text

Attribute name.

-> Text

Attribute value.

-> Attributes 

Make a set of unescaped attributes.

data Attributes Source #

A list of attributes.

Instances

Instances details
Semigroup Attributes Source # 
Instance details

Defined in Lucid.Base

Monoid Attributes Source # 
Instance details

Defined in Lucid.Base

TermRaw Text Attributes Source #

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

Instance details

Defined in Lucid.Base

Term Text Attributes Source #

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

Instance details

Defined in Lucid.Base

Methods

term :: Text -> Text -> Attributes Source #

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

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

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

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

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

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

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

Instances details
MonadTrans HtmlT Source # 
Instance details

Defined in Lucid.Base

Methods

lift :: Monad m => m a -> 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 #

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

Monad m => Monad (HtmlT m) Source # 
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 #

Functor m => Functor (HtmlT m) Source # 
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 #

Monad m => Applicative (HtmlT m) Source # 
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 #

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

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

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

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

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

term :: Text -> [Attributes] -> 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 ~ (), Monad 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 ~ (), Monad 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 #

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

Since: 2.9.8

Instance details

Defined in Lucid.Base

Methods

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

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

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

Classes

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.

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

Instances

Instances details
Term Text Attributes Source #

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

Instance details

Defined in Lucid.Base

Methods

term :: Text -> Text -> Attributes Source #

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

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

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

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

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

Same as the Term class, but will not HTML escape its children. Useful for elements like style_ or script_.

Methods

termRaw 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. termRaw "p" yields p_.

Instances

Instances details
TermRaw Text Attributes Source #

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

Instance details

Defined in Lucid.Base

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

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

Given attributes, expect more child input.

Instance details

Defined in Lucid.Base

Methods

termRaw :: Text -> [Attributes] -> f -> 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

Instances details
ToHtml String Source # 
Instance details

Defined in Lucid.Base

Methods

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

toHtmlRaw :: forall (m :: Type -> Type). 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 :: forall (m :: Type -> Type). Monad m => ByteString -> HtmlT m () Source #

toHtmlRaw :: forall (m :: Type -> Type). 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 :: forall (m :: Type -> Type). Monad m => ByteString -> HtmlT m () Source #

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

ToHtml Text Source # 
Instance details

Defined in Lucid.Base

Methods

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

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

ToHtml Text Source # 
Instance details

Defined in Lucid.Base

Methods

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

toHtmlRaw :: forall (m :: Type -> Type). 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 :: forall (m0 :: Type -> Type). Monad m0 => HtmlT m a -> HtmlT m0 () Source #

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

Deprecated

relaxHtmlT :: Monad m => HtmlT Identity a -> HtmlT m a Source #

Deprecated: DO NOT USE. This was exported accidentally and throws an exception.