module Snap.Snaplet.Heist.Internal where
import Prelude
import Control.Error
import Control.Lens
import Control.Monad.State
import qualified Data.HashMap.Strict as Map
import Data.IORef
import Data.List
import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as T
import Heist
import Heist.Splices.Cache
import System.FilePath.Posix
import Snap.Core
import Snap.Snaplet
data DefaultMode = Compiled | Interpreted
data Heist b = Configuring
{ _heistConfig :: IORef (HeistConfig (Handler b b), DefaultMode)
}
| Running
{ _masterConfig :: HeistConfig (Handler b b)
, _heistState :: HeistState (Handler b b)
, _heistCTS :: CacheTagState
, _defMode :: DefaultMode
}
makeLenses ''Heist
gHeistInit :: Handler b (Heist b) ()
-> FilePath
-> SnapletInit b (Heist b)
gHeistInit serve templateDir = do
makeSnaplet "heist" "" Nothing $ do
hs <- heistInitWorker templateDir defaultConfig
addRoutes [ ("", serve)
, ("heistReload", failIfNotLocal heistReloader)
]
return hs
where
sc = set scLoadTimeSplices defaultLoadTimeSplices mempty
defaultConfig = emptyHeistConfig & hcSpliceConfig .~ sc
& hcNamespace .~ ""
& hcErrorNotBound .~ True
heistInitWorker :: FilePath
-> HeistConfig (Handler b b)
-> Initializer b (Heist b) (Heist b)
heistInitWorker templateDir initialConfig = do
snapletPath <- getSnapletFilePath
let tDir = snapletPath </> templateDir
templates <- liftIO $ runEitherT (loadTemplates tDir) >>=
either (error . concat) return
printInfo $ T.pack $ unwords
[ "...loaded"
, (show $ Map.size templates)
, "templates from"
, tDir
]
let config = over hcTemplateLocations (<> [loadTemplates tDir])
initialConfig
ref <- liftIO $ newIORef (config, Compiled)
addPostInitHook finalLoadHook
return $ Configuring ref
finalLoadHook :: Heist b -> EitherT Text IO (Heist b)
finalLoadHook (Configuring ref) = do
(hc,dm) <- lift $ readIORef ref
(hs,cts) <- toTextErrors $ initHeistWithCacheTag hc
return $ Running hc hs cts dm
where
toTextErrors = bimapEitherT (T.pack . intercalate "\n") id
finalLoadHook (Running _ _ _ _) = left "finalLoadHook called while running"
heistReloader :: Handler b (Heist b) ()
heistReloader = do
h <- get
ehs <- liftIO $ runEitherT $ initHeist $ _masterConfig h
either (writeText . T.pack . unlines)
(\hs -> do writeText "Heist reloaded."
modifyMaster $ set heistState hs h)
ehs