module Text.Hastache.Context (
mkStrContext
, mkStrContextM
, mkGenericContext
, mkGenericContext'
, Ext
, defaultExt
) where
import Data.Data
import Data.Generics
import Data.Int
import Data.Version (Version)
import Data.Ratio (Ratio)
import Data.Word
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Map as Map
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import Text.Hastache
x ~> f = f $ x
infixl 9 ~>
mkStrContext :: Monad m => (String -> MuType m) -> MuContext m
mkStrContext f a = decodeStr a ~> f ~> return
mkStrContextM :: Monad m => (String -> m (MuType m)) -> MuContext m
mkStrContextM f a = decodeStr a ~> f
type Ext = forall b. (Data b, Typeable b) => b -> String
defaultExt :: Ext
defaultExt = gshow
#if MIN_VERSION_base(4,7,0)
mkGenericContext :: (Monad m, Data a, Typeable m) => a -> MuContext m
#else
mkGenericContext :: (Monad m, Data a, Typeable1 m) => a -> MuContext m
#endif
mkGenericContext val = toGenTemp id defaultExt val ~> convertGenTempToContext
#if MIN_VERSION_base(4,7,0)
mkGenericContext' :: (Monad m, Data a, Typeable m)
=> (String -> String) -> Ext -> a -> MuContext m
#else
mkGenericContext' :: (Monad m, Data a, Typeable1 m)
=> (String -> String) -> Ext -> a -> MuContext m
#endif
mkGenericContext' f ext val = toGenTemp f ext val ~> convertGenTempToContext
data TD m =
TSimple (MuType m)
| TObj [(String, TD m)]
| TList [TD m]
| TUnknown
deriving (Show)
#if MIN_VERSION_base(4,7,0)
toGenTemp :: (Data a, Monad m, Typeable m)
=> (String -> String) -> Ext -> a -> TD m
#else
toGenTemp :: (Data a, Monad m, Typeable1 m)
=> (String -> String) -> Ext -> a -> TD m
#endif
toGenTemp f g a = TObj $ conName : zip fields (gmapQ (procField f g) a)
where
fields = toConstr a ~> constrFields ~> map f
conName = (toConstr a ~> showConstr, TSimple . MuVariable $ g a)
#if MIN_VERSION_base(4,7,0)
procField :: (Data a, Monad m, Typeable m)
=> (String -> String) -> Ext -> a -> TD m
#else
procField :: (Data a, Monad m, Typeable1 m)
=> (String -> String) -> Ext -> a -> TD m
#endif
procField f g a =
case res a of
TUnknown -> TSimple . MuVariable . g $ a
b -> b
where
res = obj
`ext1Q` list
`extQ` (\(i::String) -> MuVariable (encodeStr i) ~> TSimple)
`extQ` (\(i::Char) -> MuVariable i ~> TSimple)
`extQ` (\(i::Double) -> MuVariable i ~> TSimple)
`extQ` (\(i::Float) -> MuVariable i ~> TSimple)
`extQ` (\(i::Int) -> MuVariable i ~> TSimple)
`extQ` (\(i::Int8) -> MuVariable i ~> TSimple)
`extQ` (\(i::Int16) -> MuVariable i ~> TSimple)
`extQ` (\(i::Int32) -> MuVariable i ~> TSimple)
`extQ` (\(i::Int64) -> MuVariable i ~> TSimple)
`extQ` (\(i::Integer) -> MuVariable i ~> TSimple)
`extQ` (\(i::Word) -> MuVariable i ~> TSimple)
`extQ` (\(i::Word8) -> MuVariable i ~> TSimple)
`extQ` (\(i::Word16) -> MuVariable i ~> TSimple)
`extQ` (\(i::Word32) -> MuVariable i ~> TSimple)
`extQ` (\(i::Word64) -> MuVariable i ~> TSimple)
`extQ` (\(i::BS.ByteString) -> MuVariable i ~> TSimple)
`extQ` (\(i::LBS.ByteString) -> MuVariable i ~> TSimple)
`extQ` (\(i::T.Text) -> MuVariable i ~> TSimple)
`extQ` (\(i::TL.Text) -> MuVariable i ~> TSimple)
`extQ` (\(i::Bool) -> MuBool i ~> TSimple)
`extQ` (\() -> MuVariable () ~> TSimple)
`extQ` (\(i::Version) -> MuVariable i ~> TSimple)
`extQ` muLambdaTT
`extQ` muLambdaTTL
`extQ` muLambdaTLTL
`extQ` muLambdaBSBS
`extQ` muLambdaSS
`extQ` muLambdaBSLBS
`extQ` muLambdaMTT
`extQ` muLambdaMTTL
`extQ` muLambdaMTLTL
`extQ` muLambdaMBSBS
`extQ` muLambdaMSS
`extQ` muLambdaMBSLBS
`ext1Q` muMaybe
`ext2Q` muEither
obj a = case dataTypeRep (dataTypeOf a) of
AlgRep (_:_) -> toGenTemp f g a
_ -> TUnknown
list a = map (procField f g) a ~> TList
muMaybe Nothing = TSimple MuNothing
muMaybe (Just a) = TList [procField f g a]
muEither (Left a) = procField f g a
muEither (Right b) = procField f g b
muLambdaTT :: (T.Text -> T.Text) -> TD m
muLambdaTT f = MuLambda f ~> TSimple
muLambdaTLTL :: (TL.Text -> TL.Text) -> TD m
muLambdaTLTL f = MuLambda (f . TL.fromStrict) ~> TSimple
muLambdaTTL :: (T.Text -> TL.Text) -> TD m
muLambdaTTL f = MuLambda f ~> TSimple
muLambdaBSBS :: (BS.ByteString -> BS.ByteString) -> TD m
muLambdaBSBS f = MuLambda (f . T.encodeUtf8) ~> TSimple
muLambdaBSLBS :: (BS.ByteString -> LBS.ByteString) -> TD m
muLambdaBSLBS f = MuLambda (f . T.encodeUtf8) ~> TSimple
muLambdaSS :: (String -> String) -> TD m
muLambdaSS f = MuLambda fd ~> TSimple
where
fd s = decodeStr s ~> f
muLambdaMTT :: (T.Text -> m T.Text) -> TD m
muLambdaMTT f = MuLambdaM f ~> TSimple
muLambdaMTLTL :: (TL.Text -> m TL.Text) -> TD m
muLambdaMTLTL f = MuLambdaM (f . TL.fromStrict) ~> TSimple
muLambdaMTTL :: (T.Text -> m TL.Text) -> TD m
muLambdaMTTL f = MuLambdaM f ~> TSimple
muLambdaMBSBS :: (BS.ByteString -> m BS.ByteString) -> TD m
muLambdaMBSBS f = MuLambdaM (f . T.encodeUtf8) ~> TSimple
muLambdaMBSLBS :: (BS.ByteString -> m LBS.ByteString) -> TD m
muLambdaMBSLBS f = MuLambdaM (f . T.encodeUtf8) ~> TSimple
muLambdaMSS :: (String -> m String) -> TD m
muLambdaMSS f = MuLambdaM fd ~> TSimple
where
fd s = decodeStr s ~> f
convertGenTempToContext :: Monad m => TD m -> MuContext m
convertGenTempToContext v = mkMap "" Map.empty v ~> mkMapContext
where
mkMap name m (TSimple t) = Map.insert (encodeStr name) t m
mkMap name m (TObj lst) = foldl (foldTObj name) m lst ~>
Map.insert (encodeStr name)
([foldl (foldTObj "") Map.empty lst ~> mkMapContext] ~> MuList)
mkMap name m (TList lst) = Map.insert (encodeStr name)
(map convertGenTempToContext lst ~> MuList) m
mkMap _ m _ = m
mkName name newName = if length name > 0
then concat [name, ".", newName]
else newName
foldTObj name m (fn, fv) = mkMap (mkName name fn) m fv
mkMapContext m a = return $ case Map.lookup a m of
Nothing ->
case a == dotT of
True ->
case Map.lookup T.empty m of
Nothing -> MuNothing
Just a -> a
_ -> MuNothing
Just a -> a
dotT :: T.Text
dotT = T.singleton '.'