{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Heist.Internal.Types.HeistState where
import Blaze.ByteString.Builder (Builder)
import Control.Applicative (Alternative (..))
import Control.Arrow (first)
import Control.Exception (Exception)
import Control.Monad (MonadPlus (..), ap)
import Control.Monad.Base
import Control.Monad.Cont (MonadCont (..))
#if MIN_VERSION_mtl(2,2,1)
import Control.Monad.Except (MonadError (..))
#else
import Control.Monad.Error (MonadError (..))
#endif
#if MIN_VERSION_base(4,9,0)
import qualified Control.Monad.Fail as Fail
#endif
import Control.Monad.Fix (MonadFix (..))
import Control.Monad.Reader (MonadReader (..))
import Control.Monad.State.Strict (MonadState (..), StateT)
import Control.Monad.Trans (MonadIO (..), MonadTrans (..))
import Control.Monad.Trans.Control
import Data.ByteString.Char8 (ByteString)
import Data.DList (DList)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as H
import Data.HeterogeneousEnvironment (HeterogeneousEnvironment)
import qualified Data.HeterogeneousEnvironment as HE
import Data.Map.Syntax
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup
#endif
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8)
#if MIN_VERSION_base (4,7,0)
import Data.Typeable (Typeable)
#else
import Data.Typeable (TyCon, Typeable(..),
Typeable1(..), mkTyCon,
mkTyConApp)
#endif
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative (Applicative (..), (<$>))
import Data.Monoid (Monoid(..))
#endif
import qualified Text.XmlHtml as X
type Splices s = MapSyntax Text s
type Template = [X.Node]
type MIMEType = ByteString
type TPath = [ByteString]
data DocumentFile = DocumentFile
{ dfDoc :: X.Document
, dfFile :: Maybe FilePath
} deriving ( Eq, Show
#if MIN_VERSION_base(4,7,0)
, Typeable
#endif
)
data Markup = Xml | Html
newtype RuntimeSplice m a = RuntimeSplice {
unRT :: StateT HeterogeneousEnvironment m a
} deriving ( Applicative
, Functor
, Monad
, MonadIO
, MonadState HeterogeneousEnvironment
, MonadTrans
#if MIN_VERSION_base(4,7,0)
, Typeable
#endif
)
instance (Monad m, Semigroup a) => Semigroup (RuntimeSplice m a) where
a <> b = do
!x <- a
!y <- b
return $! x <> y
#if !MIN_VERSION_base(4,11,0)
instance (Monad m, Semigroup a, Monoid a) => Monoid (RuntimeSplice m a) where
#else
instance (Monad m, Monoid a) => Monoid (RuntimeSplice m a) where
#endif
mempty = return mempty
#if !MIN_VERSION_base(4,11,0)
mappend = (<>)
#endif
data Chunk m = Pure !ByteString
| RuntimeHtml !(RuntimeSplice m Builder)
| RuntimeAction !(RuntimeSplice m ())
#if MIN_VERSION_base(4,7,0)
deriving Typeable
#endif
instance Show (Chunk m) where
show (Pure _) = "Pure"
show (RuntimeHtml _) = "RuntimeHtml"
show (RuntimeAction _) = "RuntimeAction"
showChunk :: Chunk m -> String
showChunk (Pure b) = T.unpack $ decodeUtf8 b
showChunk (RuntimeHtml _) = "RuntimeHtml"
showChunk (RuntimeAction _) = "RuntimeAction"
isPureChunk :: Chunk m -> Bool
isPureChunk (Pure _) = True
isPureChunk _ = False
type AttrSplice m = Text -> RuntimeSplice m [(Text, Text)]
data SpliceError = SpliceError
{ spliceHistory :: [(TPath, Maybe FilePath, Text)]
, spliceTemplateFile :: Maybe FilePath
, visibleSplices :: [Text]
, contextNode :: X.Node
, spliceMsg :: Text
} deriving ( Show, Eq )
spliceErrorText :: SpliceError -> Text
spliceErrorText (SpliceError hist tf splices node msg) =
(maybe "" ((`mappend` ": ") . T.pack) tf) `T.append` msg `T.append`
foldr (\(_, tf', tag) -> (("\n ... via " `T.append`
(maybe "" ((`mappend` ": ") . T.pack) tf')
`T.append` tag) `T.append`)) T.empty hist
`T.append`
if null splices
then T.empty
else "\nBound splices:" `T.append`
foldl (\x y -> x `T.append` " " `T.append` y) T.empty splices
`T.append`
(T.pack $ "\nNode: " ++ (show node))
data CompileException = forall e . Exception e => CompileException
{ originalException :: e
, exceptionContext :: [SpliceError]
} deriving ( Typeable )
instance Show CompileException where
show (CompileException e []) =
"Heist load exception (unknown context): " ++ (show e)
show (CompileException _ (c:_)) = (T.unpack $ spliceErrorText c)
instance Exception CompileException
data HeistState m = HeistState {
_spliceMap :: HashMap Text (HeistT m m Template)
, _templateMap :: HashMap TPath DocumentFile
, _compiledSpliceMap :: HashMap Text (HeistT m IO (DList (Chunk m)))
, _compiledTemplateMap :: !(HashMap TPath ([Chunk m], MIMEType))
, _attrSpliceMap :: HashMap Text (AttrSplice m)
, _recurse :: Bool
, _curContext :: TPath
, _splicePath :: [(TPath, Maybe FilePath, Text)]
, _recursionDepth :: Int
, _doctypes :: [X.DocType]
, _curTemplateFile :: Maybe FilePath
, _keygen :: HE.KeyGen
, _preprocessingMode :: Bool
, _curMarkup :: Markup
, _splicePrefix :: Text
, _spliceErrors :: [SpliceError]
, _errorNotBound :: Bool
, _numNamespacedTags :: Int
#if MIN_VERSION_base(4,7,0)
} deriving (Typeable)
#else
}
#endif
#if !MIN_VERSION_base(4,7,0)
instance (Typeable1 m) => Typeable (HeistState m) where
typeOf _ = mkTyConApp templateStateTyCon [typeOf1 (undefined :: m ())]
#endif
newtype HeistT n m a = HeistT {
runHeistT :: X.Node
-> HeistState n
-> m (a, HeistState n)
#if MIN_VERSION_base(4,7,0)
} deriving Typeable
#else
}
#endif
templateNames :: HeistState m -> [TPath]
templateNames ts = H.keys $ _templateMap ts
compiledTemplateNames :: HeistState m -> [TPath]
compiledTemplateNames ts = H.keys $ _compiledTemplateMap ts
spliceNames :: HeistState m -> [Text]
spliceNames ts = H.keys $ _spliceMap ts
compiledSpliceNames :: HeistState m -> [Text]
compiledSpliceNames ts = H.keys $ _compiledSpliceMap ts
#if !MIN_VERSION_base(4,7,0)
templateStateTyCon :: TyCon
templateStateTyCon = mkTyCon "Heist.HeistState"
{-# NOINLINE templateStateTyCon #-}
#endif
evalHeistT :: (Monad m)
=> HeistT n m a
-> X.Node
-> HeistState n
-> m a
evalHeistT m r s = do
(a, _) <- runHeistT m r s
return a
{-# INLINE evalHeistT #-}
instance Functor m => Functor (HeistT n m) where
fmap f (HeistT m) = HeistT $ \r s -> first f <$> m r s
instance (Monad m, Functor m) => Applicative (HeistT n m) where
pure = return
(<*>) = ap
instance Monad m => Monad (HeistT n m) where
return a = HeistT (\_ s -> return (a, s))
{-# INLINE return #-}
HeistT m >>= k = HeistT $ \r s -> do
(a, s') <- m r s
runHeistT (k a) r s'
{-# INLINE (>>=) #-}
#if MIN_VERSION_base(4,9,0)
instance Fail.MonadFail m => Fail.MonadFail (HeistT n m) where
fail = lift . Fail.fail
#endif
instance MonadIO m => MonadIO (HeistT n m) where
liftIO = lift . liftIO
instance MonadTrans (HeistT n) where
lift m = HeistT $ \_ s -> do
a <- m
return (a, s)
instance MonadBase b m => MonadBase b (HeistT n m) where
liftBase = lift . liftBase
#if MIN_VERSION_monad_control(1,0,0)
instance MonadTransControl (HeistT n) where
type StT (HeistT n) a = (a, HeistState n)
liftWith f = HeistT $ \n s -> do
res <- f $ \(HeistT g) -> g n s
return (res, s)
restoreT k = HeistT $ \_ _ -> k
{-# INLINE liftWith #-}
{-# INLINE restoreT #-}
instance MonadBaseControl b m => MonadBaseControl b (HeistT n m) where
type StM (HeistT n m) a = ComposeSt (HeistT n) m a
liftBaseWith = defaultLiftBaseWith
restoreM = defaultRestoreM
{-# INLINE liftBaseWith #-}
{-# INLINE restoreM #-}
#else
instance MonadTransControl (HeistT n) where
newtype StT (HeistT n) a = StHeistT {unStHeistT :: (a, HeistState n)}
liftWith f = HeistT $ \n s -> do
res <- f $ \(HeistT g) -> liftM StHeistT $ g n s
return (res, s)
restoreT k = HeistT $ \_ _ -> liftM unStHeistT k
{-# INLINE liftWith #-}
{-# INLINE restoreT #-}
instance MonadBaseControl b m => MonadBaseControl b (HeistT n m) where
newtype StM (HeistT n m) a = StMHeist {unStMHeist :: ComposeSt (HeistT n) m a}
liftBaseWith = defaultLiftBaseWith StMHeist
restoreM = defaultRestoreM unStMHeist
{-# INLINE liftBaseWith #-}
{-# INLINE restoreM #-}
#endif
instance MonadFix m => MonadFix (HeistT n m) where
mfix f = HeistT $ \r s ->
mfix $ \ (a, _) -> runHeistT (f a) r s
instance (Functor m, MonadPlus m) => Alternative (HeistT n m) where
empty = mzero
(<|>) = mplus
instance MonadPlus m => MonadPlus (HeistT n m) where
mzero = lift mzero
m `mplus` n = HeistT $ \r s ->
runHeistT m r s `mplus` runHeistT n r s
instance MonadState s m => MonadState s (HeistT n m) where
get = lift get
{-# INLINE get #-}
put = lift . put
{-# INLINE put #-}
instance MonadReader r m => MonadReader r (HeistT n m) where
ask = HeistT $ \_ s -> do
r <- ask
return (r,s)
local f (HeistT m) =
HeistT $ \r s -> local f (m r s)
_liftCatch
:: (m (a,HeistState n)
-> (e -> m (a,HeistState n))
-> m (a,HeistState n))
-> HeistT n m a
-> (e -> HeistT n m a)
-> HeistT n m a
_liftCatch ce m h =
HeistT $ \r s ->
(runHeistT m r s `ce`
(\e -> runHeistT (h e) r s))
instance (MonadError e m) => MonadError e (HeistT n m) where
throwError = lift . throwError
catchError = _liftCatch catchError
_liftCallCC
:: ((((a,HeistState n) -> m (b, HeistState n))
-> m (a, HeistState n))
-> m (a, HeistState n))
-> ((a -> HeistT n m b) -> HeistT n m a)
-> HeistT n m a
_liftCallCC ccc f = HeistT $ \r s ->
ccc $ \c ->
runHeistT (f (\a -> HeistT $ \_ _ -> c (a, s))) r s
instance (MonadCont m) => MonadCont (HeistT n m) where
callCC = _liftCallCC callCC
#if !MIN_VERSION_base(4,7,0)
templateMonadTyCon :: TyCon
templateMonadTyCon = mkTyCon "Heist.HeistT"
{-# NOINLINE templateMonadTyCon #-}
instance (Typeable1 m) => Typeable1 (HeistT n m) where
typeOf1 _ = mkTyConApp templateMonadTyCon [typeOf1 (undefined :: m ())]
#endif
getParamNode :: Monad m => HeistT n m X.Node
getParamNode = HeistT $ curry return
{-# INLINE getParamNode #-}
localParamNode :: Monad m
=> (X.Node -> X.Node)
-> HeistT n m a
-> HeistT n m a
localParamNode f m = HeistT $ \r s -> runHeistT m (f r) s
{-# INLINE localParamNode #-}
getsHS :: Monad m => (HeistState n -> r) -> HeistT n m r
getsHS f = HeistT $ \_ s -> return (f s, s)
{-# INLINE getsHS #-}
getHS :: Monad m => HeistT n m (HeistState n)
getHS = HeistT $ \_ s -> return (s, s)
{-# INLINE getHS #-}
putHS :: Monad m => HeistState n -> HeistT n m ()
putHS s = HeistT $ \_ _ -> return ((), s)
{-# INLINE putHS #-}
modifyHS :: Monad m
=> (HeistState n -> HeistState n)
-> HeistT n m ()
modifyHS f = HeistT $ \_ s -> return ((), f s)
{-# INLINE modifyHS #-}
restoreHS :: Monad m => HeistState n -> HeistT n m ()
restoreHS old = modifyHS (\cur -> old { _doctypes = _doctypes cur
, _numNamespacedTags =
_numNamespacedTags cur
, _spliceErrors = _spliceErrors cur })
{-# INLINE restoreHS #-}
localHS :: Monad m
=> (HeistState n -> HeistState n)
-> HeistT n m a
-> HeistT n m a
localHS f k = do
ts <- getHS
putHS $ f ts
res <- k
restoreHS ts
return res
{-# INLINE localHS #-}
modRecursionDepth :: Monad m => (Int -> Int) -> HeistT n m ()
modRecursionDepth f =
modifyHS (\st -> st { _recursionDepth = f (_recursionDepth st) })
incNamespacedTags :: Monad m => HeistT n m ()
incNamespacedTags =
modifyHS (\st -> st { _numNamespacedTags = _numNamespacedTags st + 1 })
data AttAST = Literal Text
| Ident Text
deriving (Show)
isIdent :: AttAST -> Bool
isIdent (Ident _) = True
isIdent _ = False