| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.Hamlet.Runtime
Description
Module for parsing and rendering Hamlet templates at runtime, not compile time. This uses the same Hamlet parsing as compile-time Hamlet, but has some limitations, such as:
- No compile-time checking of validity
- Can't apply functions at runtime
- No URL rendering
{-# LANGUAGE OverloadedStrings #-}
import Text.Hamlet.Runtime
import qualified Data.Map as Map
import Text.Blaze.Html.Renderer.String (renderHtml)
main :: IO ()
main = do
    template <- parseHamletTemplate defaultHamletSettings $ unlines
        [ "<p>Hello, #{name}"
        , "$if hungry"
        , "  <p>Available food:"
        , "  <ul>"
        , "    $forall food <- foods"
        , "      <li>#{food}"
        ]
    let hamletDataMap = Map.fromList
            [ ("name", "Michael")
            , ("hungry", toHamletData True) -- always True
            , ("foods", toHamletData
                [ "Apples"
                , "Bananas"
                , "Carrots"
                ])
            ]
    html <- renderHamletTemplate template hamletDataMap
    putStrLn $ renderHtml htmlSince: 2.0.6
Synopsis
- data HamletTemplate
- data HamletSettings
- defaultHamletSettings :: HamletSettings
- data HamletData
- class ToHamletData a where- toHamletData :: a -> HamletData
 
- parseHamletTemplate :: MonadThrow m => HamletSettings -> String -> m HamletTemplate
- readHamletTemplateFile :: (MonadThrow m, MonadIO m) => HamletSettings -> FilePath -> m HamletTemplate
- renderHamletTemplate :: MonadThrow m => HamletTemplate -> Map Text HamletData -> m Html
Documentation
data HamletTemplate Source #
A parsed Hamlet template. See parseHamletTemplate and
 readHamletTemplateFile.
Since: 2.0.6
data HamletSettings Source #
Settings for parsing of a hamlet document.
Instances
| Lift HamletSettings Source # | |
| Defined in Text.Hamlet.Parse | |
defaultHamletSettings :: HamletSettings Source #
Defaults settings: HTML5 doctype and HTML-style empty tags.
data HamletData Source #
A piece of data that can be embedded and passed to a Hamlet template (via
 renderHamletTemplate).
This supplies an IsString instance, so with OverloadedStrings it will
 support literal strings, which are converted to HTML via toHtml. For other
 datatypes, use toHamletData.
Since: 2.0.6
Instances
| IsString HamletData Source # | |
| Defined in Text.Hamlet.Runtime Methods fromString :: String -> HamletData # | |
| ToHamletData HamletData Source # | |
| Defined in Text.Hamlet.Runtime Methods toHamletData :: HamletData -> HamletData Source # | |
class ToHamletData a where Source #
Data which can be passed to a Hamlet template.
Since: 2.0.6
Methods
toHamletData :: a -> HamletData Source #
Instances
| ToHamletData Bool Source # | |
| Defined in Text.Hamlet.Runtime Methods toHamletData :: Bool -> HamletData Source # | |
| ToHamletData Text Source # | |
| Defined in Text.Hamlet.Runtime Methods toHamletData :: Text -> HamletData Source # | |
| ToHamletData Html Source # | |
| Defined in Text.Hamlet.Runtime Methods toHamletData :: Html -> HamletData Source # | |
| ToHamletData HamletData Source # | |
| Defined in Text.Hamlet.Runtime Methods toHamletData :: HamletData -> HamletData Source # | |
| a ~ HamletData => ToHamletData [a] Source # | |
| Defined in Text.Hamlet.Runtime Methods toHamletData :: [a] -> HamletData Source # | |
| a ~ HamletData => ToHamletData (Maybe a) Source # | |
| Defined in Text.Hamlet.Runtime Methods toHamletData :: Maybe a -> HamletData Source # | |
parseHamletTemplate :: MonadThrow m => HamletSettings -> String -> m HamletTemplate Source #
Parse an in-memory Hamlet template. This operation may fail if the template is not parsable.
Since: 2.0.6
readHamletTemplateFile :: (MonadThrow m, MonadIO m) => HamletSettings -> FilePath -> m HamletTemplate Source #
Same as parseHamletTemplate, but reads from a file. The file is assumed
 to be UTF-8 encoded (same assumption as compile-time Hamlet).
Since: 2.0.6
renderHamletTemplate :: MonadThrow m => HamletTemplate -> Map Text HamletData -> m Html Source #