Safe Haskell | None |
---|---|
Language | Haskell2010 |
Base types and combinators.
Synopsis
- renderText :: Html a -> Text
- renderBS :: Html a -> ByteString
- renderTextT :: Monad m => HtmlT m a -> m Text
- renderBST :: Monad m => HtmlT m a -> m ByteString
- renderToFile :: FilePath -> Html a -> IO ()
- execHtmlT :: Monad m => HtmlT m a -> m Builder
- evalHtmlT :: Monad m => HtmlT m a -> m a
- runHtmlT :: Monad m => HtmlT m a -> m (Builder, a)
- generalizeHtmlT :: Monad m => HtmlT Identity a -> HtmlT m a
- commuteHtmlT :: (Monad m, Monad n) => HtmlT m a -> m (HtmlT n a)
- hoistHtmlT :: (Monad m, Monad n) => (forall a. m a -> n a) -> HtmlT m b -> HtmlT n b
- makeElement :: Monad m => Text -> [Attributes] -> HtmlT m a -> HtmlT m a
- makeElementNoEnd :: Monad m => Text -> [Attributes] -> HtmlT m ()
- makeAttributes :: Text -> Text -> Attributes
- makeAttributesRaw :: Text -> Text -> Attributes
- data Attributes
- type Html = HtmlT Identity
- data HtmlT m a
- class Term arg result | result -> arg where
- class TermRaw arg result | result -> arg where
- class ToHtml a where
- relaxHtmlT :: Monad m => HtmlT Identity a -> HtmlT m a
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
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
.
:: 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!"))
()
:: (Monad m, Monad n) | |
=> HtmlT m a | unpurely generated HTML |
-> m (HtmlT n a) | Commuted monads. Note: |
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
:: Monad m | |
=> Text | Name. |
-> [Attributes] | |
-> HtmlT m a | Children HTML. |
-> HtmlT m a | A parent element. |
Make an HTML builder.
:: Monad m | |
=> Text | Name. |
-> [Attributes] | |
-> HtmlT m () | A parent element. |
Make an HTML builder for elements which have no ending tag.
:: Text | Attribute name. |
-> Text | Attribute value. |
-> Attributes |
Make a set of attributes.
:: Text | Attribute name. |
-> Text | Attribute value. |
-> Attributes |
Make a set of unescaped attributes.
data Attributes Source #
A list of attributes.
Instances
Semigroup Attributes Source # | |
Defined in Lucid.Base (<>) :: Attributes -> Attributes -> Attributes # sconcat :: NonEmpty Attributes -> Attributes # stimes :: Integral b => b -> Attributes -> Attributes # | |
Monoid Attributes Source # | |
Defined in Lucid.Base mempty :: Attributes # mappend :: Attributes -> Attributes -> Attributes # mconcat :: [Attributes] -> Attributes # | |
TermRaw Text Attributes Source # | Some termRaws (like |
Defined in Lucid.Base | |
Term Text Attributes Source # | Some terms (like |
Defined in Lucid.Base | |
(Monad m, ToHtml f, a ~ ()) => TermRaw [Attributes] (f -> HtmlT m a) Source # | Given attributes, expect more child input. |
Defined in Lucid.Base | |
(Monad m, f ~ HtmlT m a) => Term [Attributes] (f -> HtmlT m a) Source # | Given attributes, expect more child input. |
Defined in Lucid.Base |
Types
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 # | |
Defined in Lucid.Base | |
MonadState s m => MonadState s (HtmlT m) Source # | Since: 2.9.7 |
MonadReader r m => MonadReader r (HtmlT m) Source # | Since: 2.9.7 |
(Monad m, a ~ ()) => TermRaw Text (HtmlT m a) Source # | Given children immediately, just use that and expect no attributes. |
Monad m => Monad (HtmlT m) Source # | |
Functor m => Functor (HtmlT m) Source # | |
MonadFix m => MonadFix (HtmlT m) Source # | |
Defined in Lucid.Base | |
Monad m => Applicative (HtmlT m) Source # | |
MonadIO m => MonadIO (HtmlT m) Source # | If you want to use IO in your HTML generation. |
Defined in Lucid.Base | |
(Monad m, ToHtml f, a ~ ()) => TermRaw [Attributes] (f -> HtmlT m a) Source # | Given attributes, expect more child input. |
Defined in Lucid.Base | |
(Monad m, f ~ HtmlT m a) => Term [Attributes] (f -> HtmlT m a) Source # | Given attributes, expect more child input. |
Defined in Lucid.Base | |
m ~ Identity => Show (HtmlT m a) Source # | Just calls |
(Monad m, a ~ ()) => IsString (HtmlT m a) Source # | We pack it via string. Could possibly encode straight into a builder. That might be faster. |
Defined in Lucid.Base fromString :: String -> HtmlT m a # | |
(a ~ (), Monad m) => Semigroup (HtmlT m a) Source # | Since: 2.9.7 |
(a ~ (), Monad m) => Monoid (HtmlT m a) Source # | Monoid is right-associative, a la the |
(a ~ (), m ~ Identity) => ToHtml (HtmlT m a) Source # | Since: 2.9.8 |
Monad m => Term (HtmlT m a) (HtmlT m a) Source # | Given children immediately, just use that and expect no attributes. |
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 isHtmlT 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_
ortitle_
. 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.
:: 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
Term Text Attributes Source # | Some terms (like |
Defined in Lucid.Base | |
(Monad m, f ~ HtmlT m a) => Term [Attributes] (f -> HtmlT m a) Source # | Given attributes, expect more child input. |
Defined in Lucid.Base | |
Monad m => Term (HtmlT m a) (HtmlT m a) Source # | Given children immediately, just use that and expect no attributes. |
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_
.
:: 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
TermRaw Text Attributes Source # | Some termRaws (like |
Defined in Lucid.Base | |
(Monad m, a ~ ()) => TermRaw Text (HtmlT m a) Source # | Given children immediately, just use that and expect no attributes. |
(Monad m, ToHtml f, a ~ ()) => TermRaw [Attributes] (f -> HtmlT m a) Source # | Given attributes, expect more child input. |
Defined in Lucid.Base |
Can be converted to HTML.
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 # | |
ToHtml ByteString Source # | This instance requires the ByteString to contain UTF-8 encoded
text, for the Since: 2.9.5 |
ToHtml ByteString Source # | This instance requires the ByteString to contain UTF-8 encoded
text, for the Since: 2.9.5 |
ToHtml Text Source # | |
ToHtml Text Source # | |
(a ~ (), m ~ Identity) => ToHtml (HtmlT m a) Source # | Since: 2.9.8 |