Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- runHashMap :: Splices s -> Either [String] (HashMap Text s)
- runMapNoErrors :: (Eq k, Hashable k) => MapSyntaxM k v a -> HashMap k v
- applySpliceMap :: HeistState n -> (HeistState n -> HashMap Text v) -> MapSyntaxM Text v a -> HashMap Text v
- orError :: Monad m => HeistT n m b -> String -> HeistT n m b
- heistErrMsg :: Monad m => Text -> HeistT n m Text
- tellSpliceError :: Monad m => Text -> HeistT n m ()
- showTPath :: TPath -> String
- tpathName :: TPath -> ByteString
- setCurTemplateFile :: Maybe FilePath -> HeistState n -> HeistState n
- setCurContext :: TPath -> HeistState n -> HeistState n
- attParser :: Parser [AttAST]
- splitPathWith :: Char -> ByteString -> TPath
- splitLocalPath :: ByteString -> TPath
- splitTemplatePath :: ByteString -> TPath
- lookupTemplate :: ByteString -> HeistState n -> (HeistState n -> HashMap TPath t) -> Maybe (t, TPath)
- hasTemplate :: ByteString -> HeistState n -> Bool
- singleLookup :: (Eq a, Hashable a) => HashMap [a] t -> [a] -> a -> Maybe (t, [a])
- traversePath :: (Eq a, Hashable a) => HashMap [a] t -> [a] -> a -> Maybe (t, [a])
- mapSplices :: (Monad m, Monoid b) => (a -> m b) -> [a] -> m b
- getContext :: Monad m => HeistT n m TPath
- getTemplateFilePath :: Monad m => HeistT n m (Maybe FilePath)
- loadTemplate :: String -> String -> IO [Either String (TPath, DocumentFile)]
- loadTemplate' :: String -> IO [Either String DocumentFile]
- type ParserFun = String -> ByteString -> Either String Document
- getDocWith :: ParserFun -> String -> IO (Either String DocumentFile)
- getDoc :: String -> IO (Either String DocumentFile)
- getXMLDoc :: String -> IO (Either String DocumentFile)
- setTemplates :: HashMap TPath DocumentFile -> HeistState n -> HeistState n
- insertTemplate :: TPath -> DocumentFile -> HeistState n -> HeistState n
- mimeType :: Document -> MIMEType
- bindAttributeSplices :: Splices (AttrSplice n) -> HeistState n -> HeistState n
- addDoctype :: Monad m => [DocType] -> HeistT n m ()
Documentation
runMapNoErrors :: (Eq k, Hashable k) => MapSyntaxM k v a -> HashMap k v Source #
applySpliceMap :: HeistState n -> (HeistState n -> HashMap Text v) -> MapSyntaxM Text v a -> HashMap Text v Source #
orError :: Monad m => HeistT n m b -> String -> HeistT n m b Source #
If Heist is running in fail fast mode, then this function will throw an exception with the second argument as the error message. Otherwise, the first argument will be executed to represent silent failure.
This behavior allows us to fail quickly if an error crops up during load-time splice processing or degrade more gracefully if the error occurs while a user request is being processed.
heistErrMsg :: Monad m => Text -> HeistT n m Text Source #
Prepends the location of the template currently being processed to an error message.
tellSpliceError :: Monad m => Text -> HeistT n m () Source #
Adds an error message to the list of splice processing errors.
tpathName :: TPath -> ByteString Source #
Convert a TPath into a ByteString path.
setCurTemplateFile :: Maybe FilePath -> HeistState n -> HeistState n Source #
Sets the current template file.
setCurContext :: TPath -> HeistState n -> HeistState n Source #
splitPathWith :: Char -> ByteString -> TPath Source #
Converts a path into an array of the elements in reverse order. If the
path is absolute, we need to remove the leading slash so the split doesn't
leave ""
as the last element of the TPath.
FIXME ".."
currently doesn't work in paths, the solution is non-trivial
splitLocalPath :: ByteString -> TPath Source #
Converts a path into an array of the elements in reverse order using the
path separator of the local operating system. See splitPathWith
for more
details.
splitTemplatePath :: ByteString -> TPath Source #
Converts a path into an array of the elements in reverse order using a
forward slash (/) as the path separator. See splitPathWith
for more
details.
lookupTemplate :: ByteString -> HeistState n -> (HeistState n -> HashMap TPath t) -> Maybe (t, TPath) Source #
Convenience function for looking up a template.
hasTemplate :: ByteString -> HeistState n -> Bool Source #
Returns True
if the given template can be found in the heist state.
singleLookup :: (Eq a, Hashable a) => HashMap [a] t -> [a] -> a -> Maybe (t, [a]) Source #
Does a single template lookup without cascading up.
traversePath :: (Eq a, Hashable a) => HashMap [a] t -> [a] -> a -> Maybe (t, [a]) Source #
Searches for a template by looking in the full path then backing up into each of the parent directories until the template is found.
:: (Monad m, Monoid b) | |
=> (a -> m b) | Splice generating function |
-> [a] | List of items to generate splices for |
-> m b | The result of all splices concatenated together. |
Maps a splice generating function over a list and concatenates the results. This function now has a more general type signature so it works with both compiled and interpreted splices. The old type signature was this:
mapSplices :: (Monad n) => (a -> Splice n n) -> [a] -> Splice n n
getTemplateFilePath :: Monad m => HeistT n m (Maybe FilePath) Source #
Gets the full path to the file holding the template currently being processed. Returns Nothing if the template is not associated with a file on disk or if there is no template being processed.
:: String | path of the template root |
-> String | full file path (includes the template root) |
-> IO [Either String (TPath, DocumentFile)] |
Loads a template with the specified path and filename. The template is only loaded if it has a ".tpl" or ".xtpl" extension.
loadTemplate' :: String -> IO [Either String DocumentFile] Source #
Loads a template at the specified path, choosing the appropriate parser based on the file extension. The template is only loaded if it has a ".tpl" or ".xtpl" extension. Returns an empty list if the extension doesn't match.
getDocWith :: ParserFun -> String -> IO (Either String DocumentFile) Source #
Reads an HTML or XML template from disk.
setTemplates :: HashMap TPath DocumentFile -> HeistState n -> HeistState n Source #
Sets the templateMap in a HeistState.
insertTemplate :: TPath -> DocumentFile -> HeistState n -> HeistState n Source #
Adds a template to the heist state.
:: Splices (AttrSplice n) | splices to bind |
-> HeistState n | start state |
-> HeistState n |
Binds a set of new splice declarations within a HeistState
.