HStringTemplateHelpers-0.0.10: Convenience functions and instances for HStringTemplateSource codeContentsIndex
Text.StringTemplate.Helpers
Description

Functions I found useful for doing webapps with HStringTemplate.

More usage examples can be found by grep -r "Text.StringTemplate.Helpers" in happs-tutorial, on hackage.

Synopsis
directoryGroups' :: (FilePath -> IO a) -> FilePath -> IO (Map FilePath a)
directoryGroups :: Stringable a => FilePath -> IO (Map FilePath (STGroup a))
directoryGroupsOld :: Stringable a => FilePath -> IO (Map FilePath (STGroup a))
dirgroupKeys :: Stringable a => STDirGroups a -> [FilePath]
getTemplateGroup :: Stringable a => FilePath -> STDirGroups a -> STGroup a
renderTemplateDirGroup :: ToSElem a => STDirGroups String -> FilePath -> String -> [(String, a)] -> String
lookupDirgroup :: Stringable a => FilePath -> STDirGroups a -> Maybe (STGroup a)
renderTemplateGroup :: ToSElem a => STGroup String -> [(String, a)] -> [Char] -> String
render1 :: [(String, String)] -> String -> String
type STDirGroups a = Map FilePath (STGroup a)
readTmplDef :: Read b => b -> STGroup String -> FilePath -> b
readTmplM :: (Monad m, Read a) => STGroup String -> FilePath -> m a
readTmplTuples :: STGroup String -> String -> [(String, String)]
badTmplVarName :: String -> Bool
directoryGroupNew' :: Stringable a => (FilePath -> Bool) -> (String -> Bool) -> FilePath -> IO (STGroup a)
Documentation
directoryGroups' :: (FilePath -> IO a) -> FilePath -> IO (Map FilePath a)Source

Helper function to calculate a map of directory groups from a top-level directory

Each directory gives rise to its own groups.

Groups are independent; groups from higher in the directory structure do not have access to groups lower.

The top group has key "." (mnemonic, current directory), other groups have key names of subdirectories, including the starting ., eg "./templates/path/to/subdir"

directoryGroups :: Stringable a => FilePath -> IO (Map FilePath (STGroup a))Source
Strict directoryGroups, which is the right thing.
directoryGroupsOld :: Stringable a => FilePath -> IO (Map FilePath (STGroup a))Source
Non-strict. I'm pretty sure this is wrong. Based on default directoryGroup function in HStringTemplate package
dirgroupKeys :: Stringable a => STDirGroups a -> [FilePath]Source
The STGroup can't be shown in a useful way because it's a function type, but you can at least show the directories via Data.Map.keys.
getTemplateGroup :: Stringable a => FilePath -> STDirGroups a -> STGroup aSource
 example: getTG "./baselayout" ts'
renderTemplateDirGroup :: ToSElem a => STDirGroups String -> FilePath -> String -> [(String, a)] -> StringSource
 example: renderTemplateDirGroup ts' "./baselayout" "base" 
lookupDirgroup :: Stringable a => FilePath -> STDirGroups a -> Maybe (STGroup a)Source
renderTemplateGroup :: ToSElem a => STGroup String -> [(String, a)] -> [Char] -> StringSource

Chooses a template from an STGroup, or errors if not found.

Render that template using attrs.

If a template k/v pair is repeated, it appears twice. (Perhaps a clue to buggy behavior?)

Repeated keys could be eliminated by running clean:

 clean = nubBy (\(a1,b1) (a2,b2) -> a1 == a2) . sortBy (\(a1,b1) (a2,b2) -> a1 `compare` a2)

The ToSElem type is probably either String or [String]

render1 :: [(String, String)] -> String -> StringSource
 render1 [("name","Bill")] "Hi, my name is $name$"
 render1 attribs tmpl = render . setManyAttrib attribs . newSTMP $ tmpl
type STDirGroups a = Map FilePath (STGroup a)Source
readTmplDef :: Read b => b -> STGroup String -> FilePath -> bSource
readTmplM :: (Monad m, Read a) => STGroup String -> FilePath -> m aSource
readTmplTuples :: STGroup String -> String -> [(String, String)]Source
badTmplVarName :: String -> BoolSource
directoryGroupNew' :: Stringable a => (FilePath -> Bool) -> (String -> Bool) -> FilePath -> IO (STGroup a)Source

directoryGroup helper function for more flexibility, and rewritten to use do notation rather than applicative style that melted my brain.

ignoreTemplate specifies a filter for templates that should be skipped, eg backup files etc.

errorTemplate specifies a filter which will cause function to fail.

 directoryGroupHAppS = directoryGroupNew' ignoret badTmplVarName
 where ignoret f = not . null . filter (=='#') $ f 
Produced by Haddock version 2.6.0