template-hsml-0.2.0.3: Haskell's Simple Markup Language

Safe HaskellSafe-Infered

Template.HSML

Contents

Description

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_name ">" ;
 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| <p>Generated by HSML</p> |]
     }
     where
       middle = [m|
         <ul class="users">
           {h| forM_ users wrap |}
         </ul> |]
       wrap u = [m|<li> {h| userTemplate u |} </li>|]
 
 userTemplate :: User -> B.Markup
 userTemplate User{..} = [m|
   <ul class={h| "user-" <> show userID |}>
     <li>Name: {h|userName|}</li>
     <li>Age: {h|userAge|}</li>
   </ul> |]

Example (default_layout.hsml):

 {a| title :: String |}
 {a| sectionMiddle :: B.Markup |}
 {a| sectionFooter :: B.Markup |}
 
 {h| B.docType |}
 
 <html lang="en">
   <head>
     <meta charset="utf-8"/>
     <title>{h|title|}</title>
   </head>
 
   <body>
     <div class="section middle">
       {h|sectionMiddle|}
     </div>
 
     <footer>
       {h|sectionFooter|}
     </footer>
   </body>
 </html>

Result of renderMarkup $ homeTemplate [User 1 Jon Doe 16, User 2 Jane Roe 17]:

 <!DOCTYPE HTML>
 <html lang="en">
   <head>
     <meta charset="utf-8">
     <title>Home page</title>
   </head>
 
   <body>
     <div class="section middle">
       <ul class="users">
         <li>
           <ul class="user-1">
             <li>Name: Jon Doe</li>
             <li>Age: 16</li>
           </ul>
         </li>
         <li>
           <ul class="user-2">
             <li>Name: Jane Roe</li>
             <li>Age: 17</li>
           </ul>
         </li>
       </ul>
     </div>
 
     <footer>
       <p>Generated by HSML</p>
     </footer>
   </body>
 </html>

Synopsis

Quasi Quoters

hsml :: QuasiQuoterSource

QuasiQuoter for Simplified HSML expressions with default options. See defaulOptionsS for details.

Example:

 example :: Blaze.Text.Markup
 example = [hsml|
   <h1>Page Title</h1>
   <p>
     Some interesting paragraph.
   </p>
   |]

m :: QuasiQuoterSource

The same as hsml.

Example:

 example :: Blaze.Text.Markup
 example = [m|
   <h1>Page Title</h1>
   <p>
     Some interesting paragraph.
   </p>
   |]

HSML

hsmlStringWithSource

Arguments

:: Options

HSML options.

-> String

Input string.

-> Q [Dec]

Resulting type declaration and type-class instance.

Parses HSML document string with the given options. Results in record type and its IsTemplate instance.

Example:

 $(hsmlStringWith (defaultOptions "MyTemplate") "<p>Paragraph</p>")

hsmlStringSource

Arguments

:: String

Name of the record type (passed to defaultOptions).

-> String

Input string.

-> Q [Dec]

Resulting type declaration and type-class instance.

Parses HSML document from string with default options. Results in record type and its IsTemplate instance.

Example:

 $(hsmlString "MyTemplate" "<p>Paragraph</p>")

hsmlFileWithSource

Arguments

:: Options

HSML options.

-> FilePath

Name of input file.

-> Q [Dec]

Resulting type declaration and type-class instance.

Parses HSML document from file with the given options. Results in record type and its IsTemplate instance.

Example:

 $(hsmlFileWith (defaultOptions "MyTemplate") "my_template.hsml")

hsmlFileSource

Arguments

:: String

Name of the record type (passed to defaultOptions).

-> FilePath

Name of input file.

-> Q [Dec]

Resulting type declaration and type-class instance.

Parses HSML document from file with default options. Results in record type and its IsTemplate instance.

Example:

 $(hsmlFile "MyTemplate" "my_template.hsml")

Simplified HSML

shsmlStringWithSource

Arguments

:: Options

HSML options

-> String

Input string.

-> ExpQ

Resulting expression.

Parses Simplified HSML document from string with the given options. Results in expression of type Markup.

Example:

 example :: Text.Blaze.Markup
 example = $(shsmlStringWith defaultOptionsS "<p>Paragraph</p>")

shsmlStringSource

Arguments

:: String

Input string.

-> ExpQ

Resulting expression.

Parses Simplified HSML document from string with default options. Results in expression of type Markup.

Example:

 example :: Text.Blaze.Markup
 example = $(shsmlString "<p>Paragraph</p>")

shsmlFileWithSource

Arguments

:: Options

HSML Options.

-> FilePath

Name of input file.

-> ExpQ

Resulting expression.

Parses Simplified HSML document from file with the given options. Results in expression of type Markup.

Example:

 example :: Text.Blaze.Markup
 example = $(shsmlFileWith defaultOptionsS "my_template.hsml")

shsmlFileSource

Arguments

:: FilePath

Name of input file.

-> ExpQ

Resulting expression.

Parses Simplified HSML document from file with default options. Results in expression of type Markup.

Example:

 example :: Text.Blaze.Markup
 example = $(shsmlFile "my_template.hsml")

Types

class IsTemplate a whereSource

Template type-class.

Methods

renderTemplateSource

Arguments

:: a 
-> Markup

Renders the template.

data Options Source

This type lets you customize some behaviour of HSML templates.

Constructors

Options 

Fields

optExpToMarkup :: Bool

If and only if set to True, applies toMarkup on section expressions in your HSML templates.

optExpToValue :: Bool

If and only if set to True, applies toValue on attribute value expressions in your HSML templates.

optTemplateName :: String

The name of the generated record.

NOTE: Has no effect on Simplified HSML templates.

optTemplateFieldName :: String -> String

The name of the fields of the genrated record.

NOTE: Has no effect on Simplified HTML templates.

defaultOptions :: String -> OptionsSource

Default settings for HSML generators.

 defaultOptions name = Options
     { optExpToMarkup = True
     , optExpToValue = True
     , optTemplateName = firstUpper name
     , optTemplateFieldName = \a -> firstLower name <> firstUpper a
     }
     where
       firstUpper "" = ""
       firstUpper (c:cs) = toUpper c : cs
 
       firstLower "" = ""
       firstLower (c:cs) = toLower c : cs

defaultOptionsS :: OptionsSource

Default settings for Simplified HSML generators.

 defaultOptionsS = Options
     { optExpToMarkup = True 
     , optExpToValue = True
     , optTemplateName = undefined
     , optTemplateFieldName = undefined 
     }