hastache-0.6.1: Haskell implementation of Mustache templates

Safe HaskellNone
LanguageHaskell98

Text.Hastache

Description

Haskell implementation of Mustache templates

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

Simplest example:

import           Text.Hastache
import           Text.Hastache.Context
import qualified Data.Text.Lazy.IO as TL

main = do 
    res <- hastacheStr defaultConfig (encodeStr template)  
        (mkStrContext context) 
    TL.putStrLn res 
  where 
    template = "Hello, {{name}}!\n\nYou have {{unread}} unread messages." 
    context "name" = MuVariable "Haskell"
    context "unread" = MuVariable (100 :: Int)

Result:

Hello, Haskell!

You have 100 unread messages.

Using Generics:

{-# LANGUAGE DeriveDataTypeable, OverloadedStrings #-}

import           Text.Hastache
import           Text.Hastache.Context
import qualified Data.Text.Lazy.IO as TL
import           Data.Data

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

main = do
    res <- hastacheStr defaultConfig template
        (mkGenericContext inf)
    TL.putStrLn res
  where
    template = "Hello, {{name}}!\n\nYou have {{unread}} unread messages."
    inf = Info "Haskell" 100

Synopsis

Documentation

hastacheStr #

Arguments

:: MonadIO m 
=> MuConfig m

Configuration

-> Text

Template

-> MuContext m

Context

-> m Text 

Render Hastache template from Text

hastacheFile #

Arguments

:: MonadIO m 
=> MuConfig m

Configuration

-> FilePath

Template file name

-> MuContext m

Context

-> m Text 

Render Hastache template from file

hastacheStrBuilder #

Arguments

:: MonadIO m 
=> MuConfig m

Configuration

-> Text

Template

-> MuContext m

Context

-> m Builder 

Render Hastache template from Text

hastacheFileBuilder #

Arguments

:: MonadIO m 
=> MuConfig m

Configuration

-> FilePath

Template file name

-> MuContext m

Context

-> m Builder 

Render Hastache template from file

type MuContext m #

Arguments

 = Text

Variable name

-> m (MuType m)

Value

Data for Hastache variable

data MuType m #

Constructors

MuVar a => MuVariable a 
MuList [MuContext m] 
MuBool Bool 
MuVar a => MuLambda (Text -> a) 
MuVar a => MuLambdaM (Text -> m a) 
MuNothing 

Instances

Show (MuType m) # 

Methods

showsPrec :: Int -> MuType m -> ShowS #

show :: MuType m -> String #

showList :: [MuType m] -> ShowS #

Monad m => Monoid (MuContext m) # 

data MuConfig m #

Constructors

MuConfig 

Fields

class Show a => MuVar a where #

Minimal complete definition

toLText

Methods

toLText :: a -> Text #

Convert to lazy Text

isEmpty :: a -> Bool #

Is empty variable (empty string, zero number etc.)

Instances

MuVar Char # 

Methods

toLText :: Char -> Text #

isEmpty :: Char -> Bool #

MuVar Double # 

Methods

toLText :: Double -> Text #

isEmpty :: Double -> Bool #

MuVar Float # 

Methods

toLText :: Float -> Text #

isEmpty :: Float -> Bool #

MuVar Int # 

Methods

toLText :: Int -> Text #

isEmpty :: Int -> Bool #

MuVar Int8 # 

Methods

toLText :: Int8 -> Text #

isEmpty :: Int8 -> Bool #

MuVar Int16 # 

Methods

toLText :: Int16 -> Text #

isEmpty :: Int16 -> Bool #

MuVar Int32 # 

Methods

toLText :: Int32 -> Text #

isEmpty :: Int32 -> Bool #

MuVar Int64 # 

Methods

toLText :: Int64 -> Text #

isEmpty :: Int64 -> Bool #

MuVar Integer # 
MuVar Word # 

Methods

toLText :: Word -> Text #

isEmpty :: Word -> Bool #

MuVar Word8 # 

Methods

toLText :: Word8 -> Text #

isEmpty :: Word8 -> Bool #

MuVar Word16 # 

Methods

toLText :: Word16 -> Text #

isEmpty :: Word16 -> Bool #

MuVar Word32 # 

Methods

toLText :: Word32 -> Text #

isEmpty :: Word32 -> Bool #

MuVar Word64 # 

Methods

toLText :: Word64 -> Text #

isEmpty :: Word64 -> Bool #

MuVar () # 

Methods

toLText :: () -> Text #

isEmpty :: () -> Bool #

MuVar Version # 
MuVar ByteString # 
MuVar ByteString # 
MuVar Text # 

Methods

toLText :: Text -> Text #

isEmpty :: Text -> Bool #

MuVar Text # 

Methods

toLText :: Text -> Text #

isEmpty :: Text -> Bool #

MuVar [Char] # 

Methods

toLText :: [Char] -> Text #

isEmpty :: [Char] -> Bool #

MuVar a => MuVar [a] # 

Methods

toLText :: [a] -> Text #

isEmpty :: [a] -> Bool #

MuVar a => MuVar (Maybe a) # 

Methods

toLText :: Maybe a -> Text #

isEmpty :: Maybe a -> Bool #

(MuVar a, MuVar b) => MuVar (Either a b) # 

Methods

toLText :: Either a b -> Text #

isEmpty :: Either a b -> Bool #

composeCtx :: Monad m => MuContext m -> MuContext m -> MuContext m #

Left-leaning compoistion of contexts. Given contexts c1 and c2, the behaviour of (c1 <> c2) x is following: if c1 x produces MuNothing, then the result is c2 x. Otherwise the result is c1 x. Even if c1 x is MuNothing, the monadic effects of c1 are still to take place.

htmlEscape :: Text -> Text #

Escape HTML symbols

emptyEscape :: Text -> Text #

No escape

defaultConfig :: MonadIO m => MuConfig m #

Default config: HTML escape function, current directory as template directory, template file extension not specified

encodeStr :: String -> Text #

Convert String to Text

encodeStrLT :: String -> Text #

Convert String to Lazy Text

decodeStr :: Text -> String #

Convert Text to String

decodeStrLT :: Text -> String #

Convert Lazy Text to String