- hamlet :: QuasiQuoter
- xhamlet :: QuasiQuoter
- hamletDebug :: QuasiQuoter
- hamletFile :: FilePath -> Q Exp
- xhamletFile :: FilePath -> Q Exp
- hamletFileDebug :: FilePath -> Q Exp
- hamletWithSettings :: HamletSettings -> QuasiQuoter
- hamletFileWithSettings :: HamletSettings -> FilePath -> Q Exp
- data HamletSettings = HamletSettings {
- hamletDoctype :: String
- hamletCloseNewline :: Bool
- hamletCloseStyle :: String -> CloseStyle
- defaultHamletSettings :: HamletSettings
- xhtmlHamletSettings :: HamletSettings
- type Html = HtmlM ()
- type Hamlet url = (url -> [(String, String)] -> String) -> Html
- class Monad (HamletMonad a) => HamletValue a where
- data HamletMonad a :: * -> *
- type HamletUrl a
- toHamletValue :: HamletMonad a () -> a
- htmlToHamletMonad :: Html -> HamletMonad a ()
- urlToHamletMonad :: HamletUrl a -> [(String, String)] -> HamletMonad a ()
- fromHamletValue :: a -> HamletMonad a ()
- preEscapedString :: String -> Html
- string :: String -> Html
- unsafeByteString :: ByteString -> Html
- cdata :: Html -> Html
- renderHamlet :: (url -> [(String, String)] -> String) -> Hamlet url -> ByteString
- renderHtml :: Html -> ByteString
- renderHamletText :: (url -> [(String, String)] -> String) -> Hamlet url -> Text
- renderHtmlText :: Html -> Text
- data HamletRT
- data HamletData url
- data HamletException
- parseHamletRT :: Failure HamletException m => HamletSettings -> String -> m HamletRT
- renderHamletRT :: Failure HamletException m => HamletRT -> HamletMap url -> (url -> [(String, String)] -> String) -> m Html
Basic quasiquoters
Calls hamletWithSettings
with defaultHamletSettings
.
Calls hamletWithSettings
using XHTML 1.0 Strict settings.
hamletDebug :: QuasiQuoterSource
Calls hamletWithSettings
with debugHamletSettings
.
Load from external file
hamletFile :: FilePath -> Q ExpSource
Calls hamletFileWithSettings
with defaultHamletSettings
.
xhamletFile :: FilePath -> Q ExpSource
Calls hamletFileWithSettings
using XHTML 1.0 Strict settings.
hamletFileDebug :: FilePath -> Q ExpSource
Customized settings
hamletWithSettings :: HamletSettings -> QuasiQuoterSource
A quasi-quoter that converts Hamlet syntax into a function of form:
(url -> String) -> Html
Please see accompanying documentation for a description of Hamlet syntax.
data HamletSettings Source
Settings for parsing of a hamlet document.
HamletSettings | |
|
defaultHamletSettings :: HamletSettingsSource
Defaults settings: HTML5 doctype and HTML-style empty tags.
Datatypes
type Hamlet url = (url -> [(String, String)] -> String) -> HtmlSource
An function generating an Html
given a URL-rendering function.
Typeclass
class Monad (HamletMonad a) => HamletValue a whereSource
data HamletMonad a :: * -> *Source
toHamletValue :: HamletMonad a () -> aSource
htmlToHamletMonad :: Html -> HamletMonad a ()Source
urlToHamletMonad :: HamletUrl a -> [(String, String)] -> HamletMonad a ()Source
fromHamletValue :: a -> HamletMonad a ()Source
HamletValue Html | |
HamletValue (Hamlet url) |
Construction
Create an HTML snippet from a String
without escaping
Create an HTML snippet from a String
.
:: ByteString | Value to insert. |
-> Html | Resulting HTML fragment. |
Insert a ByteString
. This is an unsafe operation:
- The
ByteString
could have the wrong encoding. - The
ByteString
might contain illegal HTML characters (no escaping is done).
Rendering
ByteString
renderHamlet :: (url -> [(String, String)] -> String) -> Hamlet url -> ByteStringSource
Converts a Hamlet
to lazy bytestring.
:: Html | HTML to render |
-> ByteString | Resulting |
Render HTML to a lazy UTF-8 encoded 'L.ByteString.'
Text
renderHtmlText :: Html -> TextSource
Runtime Hamlet
data HamletData url Source
data HamletException Source
parseHamletRT :: Failure HamletException m => HamletSettings -> String -> m HamletRTSource
renderHamletRT :: Failure HamletException m => HamletRT -> HamletMap url -> (url -> [(String, String)] -> String) -> m HtmlSource