| Safe Haskell | None |
|---|
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.ByteString.Lazy.Char8 as LZ
main = do
res <- hastacheStr defaultConfig (encodeStr template)
(mkStrContext context)
LZ.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:
import Text.Hastache
import Text.Hastache.Context
import qualified Data.ByteString.Lazy.Char8 as LZ
import Data.Data
import Data.Generics
data Info = Info {
name :: String,
unread :: Int
} deriving (Data, Typeable)
main = do
res <- hastacheStr defaultConfig (encodeStr template)
(mkGenericContext inf)
LZ.putStrLn res
where
template = "Hello, {{name}}!\n\nYou have {{unread}} unread messages."
inf = Info "Haskell" 100
- hastacheStr :: MonadIO m => MuConfig m -> ByteString -> MuContext m -> m ByteString
- hastacheFile :: MonadIO m => MuConfig m -> FilePath -> MuContext m -> m ByteString
- hastacheStrBuilder :: MonadIO m => MuConfig m -> ByteString -> MuContext m -> m Builder
- hastacheFileBuilder :: MonadIO m => MuConfig m -> FilePath -> MuContext m -> m Builder
- type MuContext m = ByteString -> m (MuType m)
- data MuType m
- = forall a . MuVar a => MuVariable a
- | MuList [MuContext m]
- | MuBool Bool
- | forall a . MuVar a => MuLambda (ByteString -> a)
- | forall a . MuVar a => MuLambdaM (ByteString -> m a)
- | MuNothing
- data MuConfig m = MuConfig {}
- class Show a => MuVar a where
- toLByteString :: a -> ByteString
- isEmpty :: a -> Bool
- htmlEscape :: ByteString -> ByteString
- emptyEscape :: ByteString -> ByteString
- defaultConfig :: MonadIO m => MuConfig m
- encodeStr :: String -> ByteString
- encodeStrLBS :: String -> ByteString
- decodeStr :: ByteString -> String
- decodeStrLBS :: ByteString -> String
Documentation
Arguments
| :: MonadIO m | |
| => MuConfig m | Configuration |
| -> ByteString | Template |
| -> MuContext m | Context |
| -> m ByteString |
Render Hastache template from ByteString
Arguments
| :: MonadIO m | |
| => MuConfig m | Configuration |
| -> FilePath | Template file name |
| -> MuContext m | Context |
| -> m ByteString |
Render Hastache template from file
Arguments
| :: MonadIO m | |
| => MuConfig m | Configuration |
| -> ByteString | Template |
| -> MuContext m | Context |
| -> m Builder |
Render Hastache template from ByteString
Arguments
| :: MonadIO m | |
| => MuConfig m | Configuration |
| -> FilePath | Template file name |
| -> MuContext m | Context |
| -> m Builder |
Render Hastache template from file
Arguments
| = ByteString | Variable name |
| -> m (MuType m) | Value |
Data for Hastache variable
Constructors
| forall a . MuVar a => MuVariable a | |
| MuList [MuContext m] | |
| MuBool Bool | |
| forall a . MuVar a => MuLambda (ByteString -> a) | |
| forall a . MuVar a => MuLambdaM (ByteString -> m a) | |
| MuNothing |
Constructors
| MuConfig | |
Fields
| |
class Show a => MuVar a whereSource
Methods
toLByteString :: a -> ByteStringSource
Convert to Lazy ByteString
Is empty variable (empty string, zero number etc.)
htmlEscape :: ByteString -> ByteStringSource
Escape HTML symbols
emptyEscape :: ByteString -> ByteStringSource
No escape
defaultConfig :: MonadIO m => MuConfig mSource
Default config: HTML escape function, current directory as template directory, template file extension not specified
encodeStr :: String -> ByteStringSource
Convert String to UTF-8 Bytestring
encodeStrLBS :: String -> ByteStringSource
Convert String to UTF-8 Lazy Bytestring
decodeStr :: ByteString -> StringSource
Convert UTF-8 Bytestring to String
decodeStrLBS :: ByteString -> StringSource
Convert UTF-8 Lazy Bytestring to String