| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Lucid.Base
Description
Base types and combinators.
- 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 :: HtmlT m a -> m (HashMap Text Text -> Builder -> Builder, a)
- makeElement :: Monad m => Builder -> HtmlT m a -> HtmlT m ()
- makeElementNoEnd :: Monad m => Builder -> HtmlT m ()
- type Html = HtmlT Identity
- data HtmlT m a
- class ToHtml a where
- class Mixed a r where
- class MixedRaw a r where
- class With a where
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.
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!"))()
Combinators
Make an HTML builder.
Make an HTML builder for
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 | Used for |
| (Monad m, ToHtml a, (~) * r ()) => MixedRaw a (HtmlT m r) | HTML elements can be a mixed thing e.g. |
| (Monad m, (~) * a (HtmlT m r), (~) * r ()) => Mixed a (HtmlT m r) | HTML elements can be a mixed thing e.g. |
| 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 |
| MonadIO m => MonadIO (HtmlT m) | If you want to use IO in your HTML generation. |
| (~) (* -> *) m Identity => Show (HtmlT m a) | Just calls |
| (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: |
| (Monad m, (~) * a ()) => With (HtmlT m a) | For the contentless elements: |
Classes
Can be converted to HTML.
Used for names that are mixed, e.g. style_.
class MixedRaw a r where Source
Used for names that are mixed, e.g. style_. Doesn't encode the
inner content of its element.
With an element use these attributes.
Methods
With the given element(s), use the given attributes.