module Snap.Snaplet.Heist
(
Heist
, HasHeist(..)
, heistInit
, heistInit'
, Unclassed.heistReloader
, Unclassed.setInterpreted
, Unclassed.getCurHeistConfig
, addTemplates
, addTemplatesAt
, Unclassed.addConfig
, getHeistState
, modifyHeistState
, withHeistState
, gRender
, gRenderAs
, gHeistServe
, gHeistServeSingle
, chooseMode
, cRender
, cRenderAs
, cHeistServe
, cHeistServeSingle
, render
, renderAs
, heistServe
, heistServeSingle
, heistLocal
, withSplices
, renderWithSplices
, Unclassed.SnapletHeist
, Unclassed.SnapletCSplice
, Unclassed.SnapletISplice
, clearHeistCache
) where
import Prelude hiding (id, (.))
import Control.Monad.State
import Data.ByteString (ByteString)
import Heist
import Snap.Snaplet
import Snap.Snaplet.Heist.Internal
import qualified Snap.Snaplet.HeistNoClass as Unclassed
import Snap.Snaplet.HeistNoClass ( heistInit
, heistInit'
, clearHeistCache
)
class HasHeist b where
heistLens :: SnapletLens (Snaplet b) (Heist b)
addTemplates :: HasHeist b
=> Snaplet (Heist b)
-> ByteString
-> Initializer b v ()
addTemplates :: forall b v.
HasHeist b =>
Snaplet (Heist b) -> ByteString -> Initializer b v ()
addTemplates Snaplet (Heist b)
h ByteString
pfx = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b.
Snaplet (Heist b) -> ByteString -> Initializer b (Heist b) ()
Unclassed.addTemplates Snaplet (Heist b)
h ByteString
pfx)
addTemplatesAt :: HasHeist b
=> Snaplet (Heist b)
-> ByteString
-> FilePath
-> Initializer b v ()
addTemplatesAt :: forall b v.
HasHeist b =>
Snaplet (Heist b) -> ByteString -> FilePath -> Initializer b v ()
addTemplatesAt Snaplet (Heist b)
h ByteString
pfx FilePath
p =
forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b.
Snaplet (Heist b)
-> ByteString -> FilePath -> Initializer b (Heist b) ()
Unclassed.addTemplatesAt Snaplet (Heist b)
h ByteString
pfx FilePath
p)
getHeistState :: (HasHeist b)
=> Handler b v (HeistState (Handler b b))
getHeistState :: forall b v. HasHeist b => Handler b v (HeistState (Handler b b))
getHeistState = forall b v.
SnapletLens (Snaplet b) (Heist b)
-> Handler b v (HeistState (Handler b b))
Unclassed.getHeistState forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens
modifyHeistState :: (HasHeist b)
=> (HeistState (Handler b b) -> HeistState (Handler b b))
-> Initializer b v ()
modifyHeistState :: forall b v.
HasHeist b =>
(HeistState (Handler b b) -> HeistState (Handler b b))
-> Initializer b v ()
modifyHeistState = forall b v.
SnapletLens (Snaplet b) (Heist b)
-> (HeistState (Handler b b) -> HeistState (Handler b b))
-> Initializer b v ()
Unclassed.modifyHeistState' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens
withHeistState :: (HasHeist b)
=> (HeistState (Handler b b) -> a)
-> Handler b v a
withHeistState :: forall b a v.
HasHeist b =>
(HeistState (Handler b b) -> a) -> Handler b v a
withHeistState = forall b a v.
SnapletLens (Snaplet b) (Heist b)
-> (HeistState (Handler b b) -> a) -> Handler b v a
Unclassed.withHeistState' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens
gRender :: HasHeist b
=> ByteString
-> Handler b v ()
gRender :: forall b v. HasHeist b => ByteString -> Handler b v ()
gRender ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> Handler b (Heist b) ()
Unclassed.gRender ByteString
t)
gRenderAs :: HasHeist b
=> ByteString
-> ByteString
-> Handler b v ()
gRenderAs :: forall b v.
HasHeist b =>
ByteString -> ByteString -> Handler b v ()
gRenderAs ByteString
ct ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> ByteString -> Handler b (Heist b) ()
Unclassed.gRenderAs ByteString
ct ByteString
t)
gHeistServe :: HasHeist b => Handler b v ()
gHeistServe :: forall b v. HasHeist b => Handler b v ()
gHeistServe = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens forall b. Handler b (Heist b) ()
Unclassed.gHeistServe
gHeistServeSingle :: HasHeist b
=> ByteString
-> Handler b v ()
gHeistServeSingle :: forall b v. HasHeist b => ByteString -> Handler b v ()
gHeistServeSingle ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> Handler b (Heist b) ()
Unclassed.gHeistServeSingle ByteString
t)
chooseMode :: HasHeist b
=> Handler b v a
-> Handler b v a
-> Handler b v a
chooseMode :: forall b v a.
HasHeist b =>
Handler b v a -> Handler b v a -> Handler b v a
chooseMode Handler b v a
cAction Handler b v a
iAction = do
DefaultMode
mode <- forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets forall b. Heist b -> DefaultMode
_defMode
case DefaultMode
mode of
DefaultMode
Unclassed.Compiled -> Handler b v a
cAction
DefaultMode
Unclassed.Interpreted -> Handler b v a
iAction
cRender :: HasHeist b
=> ByteString
-> Handler b v ()
cRender :: forall b v. HasHeist b => ByteString -> Handler b v ()
cRender ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> Handler b (Heist b) ()
Unclassed.cRender ByteString
t)
cRenderAs :: HasHeist b
=> ByteString
-> ByteString
-> Handler b v ()
cRenderAs :: forall b v.
HasHeist b =>
ByteString -> ByteString -> Handler b v ()
cRenderAs ByteString
ct ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> ByteString -> Handler b (Heist b) ()
Unclassed.cRenderAs ByteString
ct ByteString
t)
cHeistServe :: HasHeist b => Handler b v ()
cHeistServe :: forall b v. HasHeist b => Handler b v ()
cHeistServe = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens forall b. Handler b (Heist b) ()
Unclassed.cHeistServe
cHeistServeSingle :: HasHeist b
=> ByteString
-> Handler b v ()
cHeistServeSingle :: forall b v. HasHeist b => ByteString -> Handler b v ()
cHeistServeSingle ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> Handler b (Heist b) ()
Unclassed.cHeistServeSingle ByteString
t)
render :: HasHeist b
=> ByteString
-> Handler b v ()
render :: forall b v. HasHeist b => ByteString -> Handler b v ()
render ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> Handler b (Heist b) ()
Unclassed.render ByteString
t)
renderAs :: HasHeist b
=> ByteString
-> ByteString
-> Handler b v ()
renderAs :: forall b v.
HasHeist b =>
ByteString -> ByteString -> Handler b v ()
renderAs ByteString
ct ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> ByteString -> Handler b (Heist b) ()
Unclassed.renderAs ByteString
ct ByteString
t)
heistServe :: HasHeist b => Handler b v ()
heistServe :: forall b v. HasHeist b => Handler b v ()
heistServe = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens forall b. Handler b (Heist b) ()
Unclassed.heistServe
heistServeSingle :: HasHeist b
=> ByteString
-> Handler b v ()
heistServeSingle :: forall b v. HasHeist b => ByteString -> Handler b v ()
heistServeSingle ByteString
t = forall (m :: * -> * -> * -> *) b v' a v.
MonadSnaplet m =>
SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
withTop' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens (forall b. ByteString -> Handler b (Heist b) ()
Unclassed.heistServeSingle ByteString
t)
renderWithSplices :: HasHeist b
=> ByteString
-> Splices (Unclassed.SnapletISplice b)
-> Handler b v ()
renderWithSplices :: forall b v.
HasHeist b =>
ByteString -> Splices (SnapletISplice b) -> Handler b v ()
renderWithSplices = forall b v.
SnapletLens (Snaplet b) (Heist b)
-> ByteString -> Splices (SnapletISplice b) -> Handler b v ()
Unclassed.renderWithSplices' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens
withSplices :: HasHeist b
=> Splices (Unclassed.SnapletISplice b)
-> Handler b v a
-> Handler b v a
withSplices :: forall b v a.
HasHeist b =>
Splices (SnapletISplice b) -> Handler b v a -> Handler b v a
withSplices = forall b v a.
SnapletLens (Snaplet b) (Heist b)
-> Splices (SnapletISplice b) -> Handler b v a -> Handler b v a
Unclassed.withSplices' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens
heistLocal :: HasHeist b
=> (HeistState (Handler b b) -> HeistState (Handler b b))
-> Handler b v a
-> Handler b v a
heistLocal :: forall b v a.
HasHeist b =>
(HeistState (Handler b b) -> HeistState (Handler b b))
-> Handler b v a -> Handler b v a
heistLocal = forall b v a.
SnapletLens (Snaplet b) (Heist b)
-> (HeistState (Handler b b) -> HeistState (Handler b b))
-> Handler b v a
-> Handler b v a
Unclassed.heistLocal' forall b. HasHeist b => SnapletLens (Snaplet b) (Heist b)
heistLens