Safe Haskell | None |
---|---|
Language | Haskell98 |
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:
import Text.Hastache import Text.Hastache.Context import qualified Data.Text.Lazy.IO as TL 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) TL.putStrLn res where template = "Hello, {{name}}!\n\nYou have {{unread}} unread messages." inf = Info "Haskell" 100
- hastacheStr :: MonadIO m => MuConfig m -> Text -> MuContext m -> m Text
- hastacheFile :: MonadIO m => MuConfig m -> FilePath -> MuContext m -> m Text
- hastacheStrBuilder :: MonadIO m => MuConfig m -> Text -> MuContext m -> m Builder
- hastacheFileBuilder :: MonadIO m => MuConfig m -> FilePath -> MuContext m -> m Builder
- type MuContext m = Text -> m (MuType m)
- data MuType m
- data MuConfig m = MuConfig {
- muEscapeFunc :: Text -> Text
- muTemplateFileDir :: Maybe FilePath
- muTemplateFileExt :: Maybe String
- muTemplateRead :: FilePath -> m (Maybe Text)
- class Show a => MuVar a where
- htmlEscape :: Text -> Text
- emptyEscape :: Text -> Text
- defaultConfig :: MonadIO m => MuConfig m
- encodeStr :: String -> Text
- encodeStrLT :: String -> Text
- decodeStr :: Text -> String
- decodeStrLT :: Text -> String
Documentation
Render Hastache template from Text
Render Hastache template from file
Render Hastache template from Text
:: MonadIO m | |
=> MuConfig m | Configuration |
-> FilePath | Template file name |
-> MuContext m | Context |
-> m Builder |
Render Hastache template from file
MuConfig | |
|
class Show a => MuVar a where Source
Convert to Lazy ByteString
Is empty variable (empty string, zero number etc.)
MuVar Char | |
MuVar Double | |
MuVar Float | |
MuVar Int | |
MuVar Int8 | |
MuVar Int16 | |
MuVar Int32 | |
MuVar Int64 | |
MuVar Integer | |
MuVar Word | |
MuVar Word8 | |
MuVar Word16 | |
MuVar Word32 | |
MuVar Word64 | |
MuVar () | |
MuVar ByteString | |
MuVar ByteString | |
MuVar Text | |
MuVar Text | |
MuVar [Char] | |
MuVar a => MuVar [a] | |
MuVar a => MuVar (Maybe a) | |
(MuVar a, MuVar b) => MuVar (Either a b) |
htmlEscape :: Text -> Text Source
Escape HTML symbols
emptyEscape :: Text -> Text Source
No escape
defaultConfig :: MonadIO m => MuConfig m Source
Default config: HTML escape function, current directory as template directory, template file extension not specified
encodeStrLT :: String -> Text Source
Convert String to Lazy Text
decodeStrLT :: Text -> String Source
Convert Lazy Text to String