hastache: Haskell implementation of Mustache templates

[ bsd3, deprecated, library, program, text ] [ Propose Tags ]
Deprecated in favor of mustache

Haskell implementation of Mustache templates (http://mustache.github.com/).

See homepage for examples of usage: http://github.com/lymar/hastache


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.1, 0.1.2, 0.1.3, 0.1.4, 0.1.5, 0.1.6, 0.2.0, 0.2.1, 0.2.2, 0.2.4, 0.3.2, 0.3.3, 0.4.1, 0.4.2, 0.5.0, 0.5.1, 0.6.0, 0.6.1
Dependencies base (>=4 && <4.11), blaze-builder, bytestring, containers, directory, filepath, ieee754, mtl, syb, text, utf8-string [details]
License BSD-3-Clause
Copyright Sergey S Lymar (c) 2011
Author Sergey S Lymar <sergey.lymar@gmail.com>
Maintainer Sergey S Lymar <sergey.lymar@gmail.com>
Revised Revision 1 made by phadej at 2020-03-26T16:34:47Z
Category Text
Home page http://github.com/lymar/hastache
Bug tracker http://github.com/lymar/hastache/issues
Source repo head: git clone http://github.com/lymar/hastache
Uploaded by SergeyLymar at 2012-02-03T12:26:34Z
Distributions FreeBSD:0.6.1
Reverse Dependencies 17 direct, 3579 indirect [details]
Downloads 43217 total (59 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for hastache-0.3.3

[back to package description]

Hastache

Haskell implementation of Mustache templates

Installation

cabal update
cabal install hastache

Usage

Read Mustache documentation for template syntax.

Examples

Variables

import Text.Hastache 
import Text.Hastache.Context 
import qualified Data.ByteString.Lazy as LZ 

main = hastacheStr defaultConfig (encodeStr template) (mkStrContext context)
    >>= LZ.putStrLn

template = "Hello, {{name}}!\n\nYou have {{unread}} unread messages." 

context "name" = MuVariable "Haskell"
context "unread" = MuVariable (100 :: Int)
Hello, Haskell!

You have 100 unread messages.

With Generics

{-# LANGUAGE DeriveDataTypeable #-}
import Text.Hastache 
import Text.Hastache.Context 
import qualified Data.ByteString.Lazy as LZ 
import Data.Data 
import Data.Generics 

main = hastacheStr defaultConfig (encodeStr template) context
    >>= LZ.putStrLn

data Info = Info { 
    name    :: String, 
    unread  :: Int 
    } deriving (Data, Typeable)

template = "Hello, {{name}}!\n\nYou have {{unread}} unread messages."
context = mkGenericContext $ Info "Haskell" 100

Lists

template = concat [ 
    "{{#heroes}}\n", 
    "* {{name}} \n", 
    "{{/heroes}}\n"] 

context "heroes" = MuList $ map (mkStrContext . mkListContext) 
    ["Nameless","Long Sky","Flying Snow","Broken Sword","Qin Shi Huang"]
    where
    mkListContext name = \"name" -> MuVariable name
* Nameless 
* Long Sky 
* Flying Snow 
* Broken Sword 
* Qin Shi Huang

With Generics

data Hero = Hero { name :: String } deriving (Data, Typeable)
data Heroes = Heroes { heroes :: [Hero] } deriving (Data, Typeable)

template = concat [ 
    "{{#heroes}}\n", 
    "* {{name}} \n", 
    "{{/heroes}}\n"] 

context = mkGenericContext $ Heroes $ map Hero ["Nameless","Long Sky",
    "Flying Snow","Broken Sword","Qin Shi Huang"]

Another Generics version

data Heroes = Heroes { heroes :: [String] } deriving (Data, Typeable)

template = concat [ 
    "{{#heroes}}\n", 
    "* {{.}} \n", 
    "{{/heroes}}\n"] 

context = mkGenericContext $ Heroes ["Nameless","Long Sky","Flying Snow", 
    "Broken Sword","Qin Shi Huang"]

Functions

template = "Hello, {{#reverse}}world{{/reverse}}!" 

context "reverse" = MuLambda (reverse . decodeStr)
Hello, dlrow!

Monadic functions

{-# LANGUAGE FlexibleContexts #-}
import Text.Hastache 
import Text.Hastache.Context 
import qualified Data.ByteString.Lazy as LZ 
import Control.Monad.State 

main = run >>= LZ.putStrLn

run = evalStateT stateFunc ""

stateFunc :: StateT String IO LZ.ByteString
stateFunc = 
    hastacheStr defaultConfig (encodeStr template) (mkStrContext context) 

template = "{{#arg}}aaa{{/arg}} {{#arg}}bbb{{/arg}} {{#arg}}ccc{{/arg}}"

context "arg" = MuLambdaM $ arg . decodeStr

arg :: MonadState String m => String -> m String
arg a = do    
    v <- get
    let nv = v ++ a
    put nv
    return nv
aaa aaabbb aaabbbccc

Generics big example

data Book = Book { 
    title           :: String, 
    publicationYear :: Integer 
    } deriving (Data, Typeable) 
 
data Life = Life { 
    born            :: Integer, 
    died            :: Integer 
    } deriving (Data, Typeable) 
     
data Writer = Writer { 
    name            :: String, 
    life            :: Life, 
    books           :: [Book]
    } deriving (Data, Typeable) 
     
template = concat [ 
    "Name: {{name}} ({{life.born}} - {{life.died}})\n", 
    "{{#life}}\n", 
        "Born: {{born}}\n", 
        "Died: {{died}}\n", 
    "{{/life}}\n", 
    "Bibliography:\n", 
    "{{#books}}\n", 
    "    {{title}} ({{publicationYear}})\n", 
    "{{/books}}\n"
    ]

context = mkGenericContext Writer { 
    name = "Mikhail Bulgakov", 
    life = Life 1891 1940, 
    books = [ 
        Book "Heart of a Dog" 1987, 
        Book "Notes of a country doctor" 1926, 
        Book "The Master and Margarita" 1967]
    }
Name: Mikhail Bulgakov (1891 - 1940)
Born: 1891
Died: 1940
Bibliography:
    Heart of a Dog (1987)
    Notes of a country doctor (1926)
    The Master and Margarita (1967)

More examples