module Heist
(
loadTemplates
, reloadTemplates
, addTemplatePathPrefix
, initHeist
, initHeistWithCacheTag
, defaultInterpretedSplices
, defaultLoadTimeSplices
, HeistConfig(..)
, TemplateRepo
, TemplateLocation
, Template
, TPath
, MIMEType
, DocumentFile(..)
, AttrSplice
, RuntimeSplice
, Chunk
, HeistState
, templateNames
, compiledTemplateNames
, hasTemplate
, spliceNames
, compiledSpliceNames
, HeistT
, evalHeistT
, getParamNode
, getContext
, getTemplateFilePath
, localParamNode
, getsHS
, getHS
, putHS
, modifyHS
, restoreHS
, localHS
, getDoc
, getXMLDoc
, orError
, module Heist.SpliceAPI
) where
import Control.Error
import Control.Exception (SomeException)
import Control.Monad.CatchIO
import Control.Monad.State
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.Foldable as F
import qualified Data.HeterogeneousEnvironment as HE
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as Map
import Data.Monoid
import System.Directory.Tree
import qualified Text.XmlHtml as X
import Heist.Common
import qualified Heist.Compiled.Internal as C
import qualified Heist.Interpreted.Internal as I
import Heist.SpliceAPI
import Heist.Splices
import Heist.Types
type TemplateRepo = HashMap TPath DocumentFile
type TemplateLocation = EitherT [String] IO TemplateRepo
data HeistConfig m = HeistConfig
{ hcInterpretedSplices :: Splices (I.Splice m)
, hcLoadTimeSplices :: Splices (I.Splice IO)
, hcCompiledSplices :: Splices (C.Splice m)
, hcAttributeSplices :: Splices (AttrSplice m)
, hcTemplateLocations :: [TemplateLocation]
}
instance Monoid (HeistConfig m) where
mempty = HeistConfig (put mempty) (put mempty) (put mempty) (put mempty) mempty
mappend (HeistConfig a b c d e) (HeistConfig a' b' c' d' e') =
HeistConfig (unionWithS const a a')
(unionWithS const b b')
(unionWithS const c c')
(unionWithS const d d')
(e `mappend` e')
defaultLoadTimeSplices :: MonadIO m => Splices (I.Splice m)
defaultLoadTimeSplices =
insertS "content" deprecatedContentCheck defaultInterpretedSplices
defaultInterpretedSplices :: MonadIO m => Splices (I.Splice m)
defaultInterpretedSplices = do
applyTag ## applyImpl
bindTag ## bindImpl
ignoreTag ## ignoreImpl
markdownTag ## markdownSplice
allErrors :: [Either String (TPath, v)]
-> EitherT [String] IO (HashMap TPath v)
allErrors tlist =
case errs of
[] -> right $ Map.fromList $ rights tlist
_ -> left errs
where
errs = lefts tlist
loadTemplates :: FilePath -> EitherT [String] IO TemplateRepo
loadTemplates dir = do
d <- lift $ readDirectoryWith (loadTemplate dir) dir
allErrors $ F.fold (free d)
reloadTemplates :: TemplateRepo -> EitherT [String] IO TemplateRepo
reloadTemplates repo = do
tlist <- lift $ mapM loadOrKeep $ Map.toList repo
allErrors tlist
where
loadOrKeep (p,df) =
case dfFile df of
Nothing -> return $ Right (p, df)
Just fp -> do
df' <- loadTemplate' fp
return $ fmap (p,) $ case df' of
[t] -> t
_ -> Left "Template repo has non-templates"
addTemplatePathPrefix :: ByteString -> TemplateRepo -> TemplateRepo
addTemplatePathPrefix dir ts
| B.null dir = ts
| otherwise = Map.fromList $
map (\(x,y) -> (f x, y)) $
Map.toList ts
where
f ps = ps++splitTemplatePath dir
emptyHS :: HE.KeyGen -> HeistState m
emptyHS kg = HeistState Map.empty Map.empty Map.empty Map.empty Map.empty
True [] 0 [] Nothing kg False Html
initHeist :: Monad n
=> HeistConfig n
-> EitherT [String] IO (HeistState n)
initHeist hc = do
keyGen <- lift HE.newKeyGen
repos <- sequence $ hcTemplateLocations hc
initHeist' keyGen hc (Map.unions repos)
initHeist' :: Monad n
=> HE.KeyGen
-> HeistConfig n
-> TemplateRepo
-> EitherT [String] IO (HeistState n)
initHeist' keyGen (HeistConfig i lt c a _) repo = do
let empty = emptyHS keyGen
tmap <- preproc keyGen lt repo
let hs1 = empty { _spliceMap = Map.fromList $ splicesToList i
, _templateMap = tmap
, _compiledSpliceMap = Map.fromList $ splicesToList c
, _attrSpliceMap = Map.fromList $ splicesToList a
}
lift $ C.compileTemplates hs1
preproc :: HE.KeyGen
-> Splices (I.Splice IO)
-> TemplateRepo
-> EitherT [String] IO TemplateRepo
preproc keyGen splices templates = do
let hs = (emptyHS keyGen) { _spliceMap = Map.fromList $ splicesToList splices
, _templateMap = templates
, _preprocessingMode = True }
let eval a = evalHeistT a (X.TextNode "") hs
tPairs <- lift $ mapM (eval . preprocess) $ Map.toList templates
let bad = lefts tPairs
if not (null bad)
then left bad
else right $ Map.fromList $ rights tPairs
preprocess :: (TPath, DocumentFile)
-> HeistT IO IO (Either String (TPath, DocumentFile))
preprocess (tpath, docFile) = do
let tname = tpathName tpath
!emdoc <- try $ I.evalWithDoctypes tname
:: HeistT IO IO (Either SomeException (Maybe X.Document))
let f !doc = (tpath, docFile { dfDoc = doc })
return $! either (Left . show) (Right . maybe die f) emdoc
where
die = error "Preprocess didn't succeed! This should never happen."
initHeistWithCacheTag :: MonadIO n
=> HeistConfig n
-> EitherT [String] IO (HeistState n, CacheTagState)
initHeistWithCacheTag (HeistConfig i lt c a locations) = do
(ss, cts) <- liftIO mkCacheTag
let tag = "cache"
keyGen <- lift HE.newKeyGen
repos <- sequence locations
rawWithCache <- preproc keyGen (tag ## ss) $ Map.unions repos
let hc' = HeistConfig (insertS tag (cacheImpl cts) i) lt
(insertS tag (cacheImplCompiled cts) c)
a locations
hs <- initHeist' keyGen hc' rawWithCache
return (hs, cts)