| 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
- relaxHtmlT :: Monad m => HtmlT Identity a -> HtmlT m a
- makeElement :: Monad m => Text -> HtmlT m a -> HtmlT m a
- makeElementNoEnd :: Monad m => Text -> HtmlT m ()
- makeXmlElementNoEnd :: Monad m => Text -> HtmlT m ()
- makeAttribute :: Text -> Text -> Attribute
- type Html = HtmlT Identity
- newtype HtmlT m a = HtmlT {}
- data Attribute = Attribute !Text !Text
- class Term arg result | result -> arg where
- class TermRaw arg result | result -> arg where
- class ToHtml a 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 elements which have no ending tag.
Make an XML builder for elements which have no ending tag.
Make an attribute builder.
Types
A monad transformer that generates HTML. Use the simpler Html
 type if you don't want to transform over some other monad.
Constructors
| HtmlT | |
Instances
| MFunctor HtmlT Source # | |
| MonadTrans HtmlT Source # | Used for  | 
| (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 # | Basically acts like Writer. | 
| Monad m => Functor (HtmlT m) Source # | Just re-uses Monad. | 
| Monad m => Applicative (HtmlT m) Source # | Based on the monad instance. | 
| MonadIO m => MonadIO (HtmlT m) Source # | If you want to use IO in your HTML generation. | 
| (Monad m, ToHtml f, (~) * a ()) => TermRaw [Attribute] (f -> HtmlT m a) Source # | Given attributes, expect more child input. | 
| (Monad m, (~) * f (HtmlT m a)) => Term [Attribute] (f -> HtmlT m a) Source # | Given attributes, expect more child input. | 
| (~) (* -> *) 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. | 
| ((~) * a (), Monad m) => Monoid (HtmlT m a) Source # | Monoid is right-associative, a la the  | 
| Monad m => With (HtmlT m a -> HtmlT m a) Source # | For the contentful elements:  | 
| Monad m => With (HtmlT m a) Source # | For the contentless elements:  | 
| Monad m => Term (HtmlT m a) (HtmlT m a) Source # | Given children immediately, just use that and expect no attributes. | 
A simple attribute. Don't use the constructor, use makeAttribute.
Instances
| Eq Attribute Source # | |
| Show Attribute Source # | |
| Hashable Attribute Source # | |
| TermRaw Text Attribute Source # | Some termRaws (like  | 
| Term Text Attribute Source # | Some terms (like  | 
| (Monad m, ToHtml f, (~) * a ()) => TermRaw [Attribute] (f -> HtmlT m a) Source # | Given attributes, expect more child input. | 
| (Monad m, (~) * f (HtmlT m a)) => Term [Attribute] (f -> HtmlT m a) Source # | Given attributes, expect more child input. | 
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 argof[(Text,Text)]which will return a function that wants children.
- The second is an argwhich 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.
Minimal complete definition
Methods
term :: Text -> arg -> result Source #
Used for constructing elements e.g. term "p" yields p_.
termWith :: Text -> [Attribute] -> arg -> result Source #
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  | 
| (Monad m, (~) * f (HtmlT m a)) => Term [Attribute] (f -> HtmlT m a) Source # | Given attributes, expect more child input. | 
| 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_.
Minimal complete definition
Methods
termRaw :: Text -> arg -> result Source #
Used for constructing elements e.g. termRaw "p" yields p_.
termRawWith :: Text -> [Attribute] -> arg -> result Source #
Use this if you want to make an element which inserts some pre-prepared attributes into the element.
Instances
| TermRaw Text Attribute Source # | Some termRaws (like  | 
| (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 [Attribute] (f -> HtmlT m a) Source # | Given attributes, expect more child input. | 
Can be converted to HTML.
Instances
| ToHtml String Source # | |
| ToHtml ByteString Source # | This instance requires the ByteString to contain UTF-8 encoded
 text, for the  | 
| ToHtml ByteString Source # | This instance requires the ByteString to contain UTF-8 encoded
 text, for the  | 
| ToHtml Text Source # | |
| ToHtml Text 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.
Minimal complete definition