-- | `HSML` is simple templating system with syntax similar to XML that -- lets you embed Haskell expressions and declarations inside your -- templates. Apart from that, it also lets you specify argumets for your -- templates, thanks to that, templates can be mostly self-contained. -- -- This is the syntax, with some of the details left out: -- -- > syntax = { argument }, { chunk } ; -- > chunk = text | text_raw | element_node | element_leaf | haskell ; -- > argument = "{a|" ? argument name ?, [ "::" ? type ? ] "|}" ; -- > -- > text = ? all characters except \'<\' and \'{\' which have to be escaped ? ; -- > text_raw = "{r|" ? all characters, the sequence can not contain \"|}\" substring ? "|}" ; -- > element_node = "<" element_name { attribute } ">" { chunk } "" ; -- > element_leaf = "<" element_name { attribute } "/>" ; -- > haskell = "{h|" expression | declaration "|}" ; -- > -- > attribute = attribute_exp | attribute_normal -- > attribute_exp = "{h|" expression "|}" -- > attribute_normal = attribute_name "=" attribute_value ; -- > attribute_name = ? classic attribute name ? | "{h|" expression "|}" ; -- > attribute_value = ? classic attribute value ? | "{h| expression "|}" ; -- > -- > expression = ? Haskell expression not containing \"|}\" as a substring ? ; -- > declaration = ? Haskell declaration not containing \"|}\" as a substring ? ; -- -- Example (Main.hs): -- -- > {-# LANGUAGE TemplateHaskell #-} -- > {-# LANGUAGE QuasiQuotes #-} -- > {-# LANGUAGE RecordWildCards #-} -- > -- > ------------------------------------------------------------------------------ -- > import Data.Monoid ((<>)) -- > ------------------------------------------------------------------------------ -- > import Control.Monad -- > ------------------------------------------------------------------------------ -- > import qualified Text.Blaze.Html5 as B -- > ------------------------------------------------------------------------------ -- > import Template.HSML -- > ------------------------------------------------------------------------------ -- > -- > data User = User -- > { userID :: Int -- > , userName :: String -- > , userAge :: Int -- > } -- > -- > $(hsmlFileWith (defaultOptions "Default") "default_layout.hsml") -- > -- > homeTemplate :: [User] -> B.Markup -- > homeTemplate users = renderTemplate Default -- > { defaultTitle = "Home page" -- > , defaultSectionMiddle = middle -- > , defaultSectionFooter = [m|

Generated by HSML

|] -- > } -- > where -- > middle = [m| -- > |] -- > wrap u = [m|
  • {h| userTemplate u |}
  • |] -- > -- > userTemplate :: User -> B.Markup -- > userTemplate User{..} = [m| -- > |] -- -- Example (default_layout.hsml): -- -- > {a| title :: String |} -- > {a| sectionMiddle :: B.Markup |} -- > {a| sectionFooter :: B.Markup |} -- > -- > {h| B.docType |} -- > -- > -- > -- > -- > {h|title|} -- > -- > -- > -- >
    -- > {h|sectionMiddle|} -- >
    -- > -- > -- > -- > -- -- Result of @renderMarkup $ homeTemplate [User 1 "Jon Doe" 16, User -- 2 "Jane Roe" 17]@: -- -- > -- > -- > -- > -- > Home page -- > -- > -- > -- >
    -- > -- >
    -- > -- > -- > -- > module Template.HSML ( -- * Quasi Quoters hsml , m -- * HSML , hsmlStringWith , hsmlString , hsmlFileWith , hsmlFile -- * Simplified HSML , shsmlStringWith , shsmlString , shsmlFileWith , shsmlFile -- * Types , IsTemplate(..) , Options(..) , defaultOptions , defaultOptionsS ) where ------------------------------------------------------------------------------ import Template.HSML.Internal.TH import Template.HSML.Internal.Types ------------------------------------------------------------------------------