{-# OPTIONS_GHC -fno-warn-orphans  #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE CPP                        #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TupleSections              #-}
module Text.Mustache.Internal.Types where
import           Control.Arrow
import           Control.Monad.RWS        hiding (lift)
import qualified Data.Aeson               as Aeson
#if MIN_VERSION_aeson(2,0,0)
import qualified Data.Aeson.KeyMap        as KM
#endif
import           Data.Int                 (Int8, Int16, Int32, Int64)
import           Data.Foldable            (toList)
import qualified Data.HashMap.Strict      as HM
import qualified Data.HashSet             as HS
import qualified Data.Map                 as Map
import           Data.Scientific
import qualified Data.Sequence            as Seq
import qualified Data.Set                 as Set
import           Data.Text
import qualified Data.Text.Lazy           as LT
import qualified Data.Vector              as V
import           Data.Word                (Word8, Word16, Word32, Word64)
import           Language.Haskell.TH.Lift (deriveLift)
import           Language.Haskell.TH.Syntax
import           Numeric.Natural          (Natural)
data SubstitutionError
  = VariableNotFound [Key] 
  | InvalidImplicitSectionContextType String 
  | InvertedImplicitSection 
  | SectionTargetNotFound [Key] 
  | PartialNotFound FilePath 
  | DirectlyRenderedValue Value 
  deriving (Int -> SubstitutionError -> ShowS
[SubstitutionError] -> ShowS
SubstitutionError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubstitutionError] -> ShowS
$cshowList :: [SubstitutionError] -> ShowS
show :: SubstitutionError -> String
$cshow :: SubstitutionError -> String
showsPrec :: Int -> SubstitutionError -> ShowS
$cshowsPrec :: Int -> SubstitutionError -> ShowS
Show)
tellError :: SubstitutionError -> SubM ()
tellError :: SubstitutionError -> SubM ()
tellError SubstitutionError
e = forall a.
RWS
  (Context Value, TemplateCache) ([SubstitutionError], [Text]) () a
-> SubM a
SubM forall a b. (a -> b) -> a -> b
$ forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell ([SubstitutionError
e], [])
tellSuccess :: Text -> SubM ()
tellSuccess :: Text -> SubM ()
tellSuccess Text
s = forall a.
RWS
  (Context Value, TemplateCache) ([SubstitutionError], [Text]) () a
-> SubM a
SubM forall a b. (a -> b) -> a -> b
$ forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell ([], [Text
s])
newtype SubM a = SubM { forall a.
SubM a
-> RWS
     (Context Value, TemplateCache) ([SubstitutionError], [Text]) () a
runSubM' :: RWS (Context Value, TemplateCache) ([SubstitutionError], [Text]) ()  a } deriving (Applicative SubM
forall a. a -> SubM a
forall a b. SubM a -> SubM b -> SubM b
forall a b. SubM a -> (a -> SubM b) -> SubM b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> SubM a
$creturn :: forall a. a -> SubM a
>> :: forall a b. SubM a -> SubM b -> SubM b
$c>> :: forall a b. SubM a -> SubM b -> SubM b
>>= :: forall a b. SubM a -> (a -> SubM b) -> SubM b
$c>>= :: forall a b. SubM a -> (a -> SubM b) -> SubM b
Monad, forall a b. a -> SubM b -> SubM a
forall a b. (a -> b) -> SubM a -> SubM b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> SubM b -> SubM a
$c<$ :: forall a b. a -> SubM b -> SubM a
fmap :: forall a b. (a -> b) -> SubM a -> SubM b
$cfmap :: forall a b. (a -> b) -> SubM a -> SubM b
Functor, Functor SubM
forall a. a -> SubM a
forall a b. SubM a -> SubM b -> SubM a
forall a b. SubM a -> SubM b -> SubM b
forall a b. SubM (a -> b) -> SubM a -> SubM b
forall a b c. (a -> b -> c) -> SubM a -> SubM b -> SubM c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. SubM a -> SubM b -> SubM a
$c<* :: forall a b. SubM a -> SubM b -> SubM a
*> :: forall a b. SubM a -> SubM b -> SubM b
$c*> :: forall a b. SubM a -> SubM b -> SubM b
liftA2 :: forall a b c. (a -> b -> c) -> SubM a -> SubM b -> SubM c
$cliftA2 :: forall a b c. (a -> b -> c) -> SubM a -> SubM b -> SubM c
<*> :: forall a b. SubM (a -> b) -> SubM a -> SubM b
$c<*> :: forall a b. SubM (a -> b) -> SubM a -> SubM b
pure :: forall a. a -> SubM a
$cpure :: forall a. a -> SubM a
Applicative, MonadReader (Context Value, TemplateCache))
runSubM :: SubM a -> Context Value -> TemplateCache -> ([SubstitutionError], [Text])
runSubM :: forall a.
SubM a
-> Context Value -> TemplateCache -> ([SubstitutionError], [Text])
runSubM SubM a
comp Context Value
ctx TemplateCache
cache = forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$ forall r w s a. RWS r w s a -> r -> s -> (a, w)
evalRWS (forall a.
SubM a
-> RWS
     (Context Value, TemplateCache) ([SubstitutionError], [Text]) () a
runSubM' SubM a
comp) (Context Value
ctx, TemplateCache
cache) ()
shiftContext :: Context Value -> SubM a -> SubM a
shiftContext :: forall a. Context Value -> SubM a -> SubM a
shiftContext = forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const
search :: [Key] -> SubM (Maybe Value)
search :: [Text] -> SubM (Maybe Value)
search [] = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
search (Text
key:[Text]
nextKeys) = (forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Text] -> Value -> Maybe Value
innerSearch [Text]
nextKeys) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SubM (Maybe Value)
go
  where
    go :: SubM (Maybe Value)
go = forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks forall a b. (a, b) -> a
fst forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Context [Value]
parents Value
focus -> do
        let searchParents :: SubM (Maybe Value)
searchParents = case [Value]
parents of
                  (Value
newFocus: [Value]
newParents) -> forall a. Context Value -> SubM a -> SubM a
shiftContext (forall α. [α] -> α -> Context α
Context [Value]
newParents Value
newFocus) forall a b. (a -> b) -> a -> b
$ SubM (Maybe Value)
go
                  [Value]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
        case Value
focus of
          Object Object
o ->
            case forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup Text
key Object
o of
              Just Value
res -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Value
res
              Maybe Value
_ -> SubM (Maybe Value)
searchParents
          Value
_ -> SubM (Maybe Value)
searchParents
innerSearch :: [Key] -> Value -> Maybe Value
innerSearch :: [Text] -> Value -> Maybe Value
innerSearch []     Value
v          = forall a. a -> Maybe a
Just Value
v
innerSearch (Text
y:[Text]
ys) (Object Object
o) = forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup Text
y Object
o forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Text] -> Value -> Maybe Value
innerSearch [Text]
ys
innerSearch [Text]
_      Value
_          = forall a. Maybe a
Nothing
type STree = ASTree Text
type ASTree α = [Node α]
data Node α
  = TextBlock α
  | Section DataIdentifier (ASTree α)
  | InvertedSection DataIdentifier (ASTree α)
  | Variable Bool DataIdentifier
  | Partial (Maybe α) FilePath
  deriving (Int -> Node α -> ShowS
forall α. Show α => Int -> Node α -> ShowS
forall α. Show α => [Node α] -> ShowS
forall α. Show α => Node α -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Node α] -> ShowS
$cshowList :: forall α. Show α => [Node α] -> ShowS
show :: Node α -> String
$cshow :: forall α. Show α => Node α -> String
showsPrec :: Int -> Node α -> ShowS
$cshowsPrec :: forall α. Show α => Int -> Node α -> ShowS
Show, Node α -> Node α -> Bool
forall α. Eq α => Node α -> Node α -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Node α -> Node α -> Bool
$c/= :: forall α. Eq α => Node α -> Node α -> Bool
== :: Node α -> Node α -> Bool
$c== :: forall α. Eq α => Node α -> Node α -> Bool
Eq)
data DataIdentifier
  = NamedData [Key]
  | Implicit
  deriving (Int -> DataIdentifier -> ShowS
[DataIdentifier] -> ShowS
DataIdentifier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataIdentifier] -> ShowS
$cshowList :: [DataIdentifier] -> ShowS
show :: DataIdentifier -> String
$cshow :: DataIdentifier -> String
showsPrec :: Int -> DataIdentifier -> ShowS
$cshowsPrec :: Int -> DataIdentifier -> ShowS
Show, DataIdentifier -> DataIdentifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataIdentifier -> DataIdentifier -> Bool
$c/= :: DataIdentifier -> DataIdentifier -> Bool
== :: DataIdentifier -> DataIdentifier -> Bool
$c== :: DataIdentifier -> DataIdentifier -> Bool
Eq)
type Array  = V.Vector Value
type Object = HM.HashMap Text Value
type Pair   = (Text, Value)
data Context α = Context { forall α. Context α -> [α]
ctxtParents :: [α], forall α. Context α -> α
ctxtFocus :: α }
  deriving (Context α -> Context α -> Bool
forall α. Eq α => Context α -> Context α -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Context α -> Context α -> Bool
$c/= :: forall α. Eq α => Context α -> Context α -> Bool
== :: Context α -> Context α -> Bool
$c== :: forall α. Eq α => Context α -> Context α -> Bool
Eq, Int -> Context α -> ShowS
forall α. Show α => Int -> Context α -> ShowS
forall α. Show α => [Context α] -> ShowS
forall α. Show α => Context α -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Context α] -> ShowS
$cshowList :: forall α. Show α => [Context α] -> ShowS
show :: Context α -> String
$cshow :: forall α. Show α => Context α -> String
showsPrec :: Int -> Context α -> ShowS
$cshowsPrec :: forall α. Show α => Int -> Context α -> ShowS
Show, Context α -> Context α -> Bool
Context α -> Context α -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {α}. Ord α => Eq (Context α)
forall α. Ord α => Context α -> Context α -> Bool
forall α. Ord α => Context α -> Context α -> Ordering
forall α. Ord α => Context α -> Context α -> Context α
min :: Context α -> Context α -> Context α
$cmin :: forall α. Ord α => Context α -> Context α -> Context α
max :: Context α -> Context α -> Context α
$cmax :: forall α. Ord α => Context α -> Context α -> Context α
>= :: Context α -> Context α -> Bool
$c>= :: forall α. Ord α => Context α -> Context α -> Bool
> :: Context α -> Context α -> Bool
$c> :: forall α. Ord α => Context α -> Context α -> Bool
<= :: Context α -> Context α -> Bool
$c<= :: forall α. Ord α => Context α -> Context α -> Bool
< :: Context α -> Context α -> Bool
$c< :: forall α. Ord α => Context α -> Context α -> Bool
compare :: Context α -> Context α -> Ordering
$ccompare :: forall α. Ord α => Context α -> Context α -> Ordering
Ord)
data Value
  = Object !Object
  | Array  !Array
  | Number !Scientific
  | String !Text
  | Lambda (STree -> SubM STree)
  | Bool   !Bool
  | Null
instance Show Value where
  show :: Value -> String
show (Lambda STree -> SubM STree
_) = String
"Lambda function"
  show (Object Object
o) = forall a. Show a => a -> String
show Object
o
  show (Array  Array
a) = forall a. Show a => a -> String
show Array
a
  show (String Text
s) = forall a. Show a => a -> String
show Text
s
  show (Number Scientific
n) = forall a. Show a => a -> String
show Scientific
n
  show (Bool   Bool
b) = forall a. Show a => a -> String
show Bool
b
  show Value
Null       = String
"null"
listToMustache' :: ToMustache ω => [ω] -> Value
listToMustache' :: forall ω. ToMustache ω => [ω] -> Value
listToMustache' = Array -> Value
Array forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall ω. ToMustache ω => ω -> Value
toMustache
integralToMustache :: Integral ω => ω -> Value
integralToMustache :: forall ω. Integral ω => ω -> Value
integralToMustache = forall ω. ToMustache ω => ω -> Value
toMustache forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger
class ToMustache ω where
  toMustache :: ω -> Value
  listToMustache :: [ω] -> Value
  listToMustache = forall ω. ToMustache ω => [ω] -> Value
listToMustache'
instance ToMustache Float where
  toMustache :: Float -> Value
toMustache = Scientific -> Value
Number forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => a -> Scientific
fromFloatDigits
instance ToMustache Double where
  toMustache :: Double -> Value
toMustache = Scientific -> Value
Number forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => a -> Scientific
fromFloatDigits
instance ToMustache Integer where
  toMustache :: Integer -> Value
toMustache = Scientific -> Value
Number forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger
instance ToMustache Natural where
  toMustache :: Natural -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Int where
  toMustache :: Int -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Word where
  toMustache :: Word -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Int8 where
  toMustache :: Int8 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Int16 where
  toMustache :: Int16 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Int32 where
  toMustache :: Int32 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Int64 where
  toMustache :: Int64 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Word8 where
  toMustache :: Word8 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Word16 where
  toMustache :: Word16 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Word32 where
  toMustache :: Word32 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Word64 where
  toMustache :: Word64 -> Value
toMustache = forall ω. Integral ω => ω -> Value
integralToMustache
instance ToMustache Char where
  toMustache :: Char -> Value
toMustache = forall ω. ToMustache ω => ω -> Value
toMustache forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[])
  listToMustache :: String -> Value
listToMustache = Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack
instance ToMustache Value where
  toMustache :: Value -> Value
toMustache = forall a. a -> a
id
instance ToMustache Bool where
  toMustache :: Bool -> Value
toMustache = Bool -> Value
Bool
instance ToMustache () where
  toMustache :: () -> Value
toMustache = forall a b. a -> b -> a
const Value
Null
instance ToMustache ω => ToMustache (Maybe ω) where
  toMustache :: Maybe ω -> Value
toMustache (Just ω
w) = forall ω. ToMustache ω => ω -> Value
toMustache ω
w
  toMustache Maybe ω
Nothing  = Value
Null
instance ToMustache Text where
  toMustache :: Text -> Value
toMustache = Text -> Value
String
instance ToMustache LT.Text where
  toMustache :: Text -> Value
toMustache = Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
LT.toStrict
instance ToMustache Scientific where
  toMustache :: Scientific -> Value
toMustache = Scientific -> Value
Number
instance ToMustache α => ToMustache [α] where
  toMustache :: [α] -> Value
toMustache = forall ω. ToMustache ω => [ω] -> Value
listToMustache
instance ToMustache ω => ToMustache (Seq.Seq ω) where
  toMustache :: Seq ω -> Value
toMustache = forall ω. ToMustache ω => [ω] -> Value
listToMustache' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
instance ToMustache ω => ToMustache (V.Vector ω) where
  toMustache :: Vector ω -> Value
toMustache = Array -> Value
Array forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall ω. ToMustache ω => ω -> Value
toMustache
instance (ToMustache ω) => ToMustache (Map.Map Text ω) where
  toMustache :: Map Text ω -> Value
toMustache = forall v a. ToMustache v => (a -> Text) -> Map a v -> Value
mapInstanceHelper forall a. a -> a
id
instance (ToMustache ω) => ToMustache (Map.Map LT.Text ω) where
  toMustache :: Map Text ω -> Value
toMustache = forall v a. ToMustache v => (a -> Text) -> Map a v -> Value
mapInstanceHelper Text -> Text
LT.toStrict
instance (ToMustache ω) => ToMustache (Map.Map String ω) where
  toMustache :: Map String ω -> Value
toMustache = forall v a. ToMustache v => (a -> Text) -> Map a v -> Value
mapInstanceHelper String -> Text
pack
mapInstanceHelper :: ToMustache v => (a -> Text) -> Map.Map a v -> Value
mapInstanceHelper :: forall v a. ToMustache v => (a -> Text) -> Map a v -> Value
mapInstanceHelper a -> Text
conv =
  forall ω. ToMustache ω => ω -> Value
toMustache
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey
    (\a
k -> forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HM.insert (a -> Text
conv a
k) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ω. ToMustache ω => ω -> Value
toMustache)
    forall k v. HashMap k v
HM.empty
instance ToMustache ω => ToMustache (HM.HashMap Text ω) where
  toMustache :: HashMap Text ω -> Value
toMustache = Object -> Value
Object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall ω. ToMustache ω => ω -> Value
toMustache
instance ToMustache ω => ToMustache (HM.HashMap LT.Text ω) where
  toMustache :: HashMap Text ω -> Value
toMustache = forall v a. ToMustache v => (a -> Text) -> HashMap a v -> Value
hashMapInstanceHelper Text -> Text
LT.toStrict
instance ToMustache ω => ToMustache (HM.HashMap String ω) where
  toMustache :: HashMap String ω -> Value
toMustache = forall v a. ToMustache v => (a -> Text) -> HashMap a v -> Value
hashMapInstanceHelper String -> Text
pack
hashMapInstanceHelper :: ToMustache v => (a -> Text) -> HM.HashMap a v -> Value
hashMapInstanceHelper :: forall v a. ToMustache v => (a -> Text) -> HashMap a v -> Value
hashMapInstanceHelper a -> Text
conv =
  forall ω. ToMustache ω => ω -> Value
toMustache
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
HM.foldrWithKey
    (\a
k -> forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HM.insert (a -> Text
conv a
k) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ω. ToMustache ω => ω -> Value
toMustache)
    forall k v. HashMap k v
HM.empty
instance ToMustache (STree -> SubM STree) where
    toMustache :: (STree -> SubM STree) -> Value
toMustache = (STree -> SubM STree) -> Value
Lambda
instance ToMustache Aeson.Value where
  toMustache :: Value -> Value
toMustache (Aeson.Object Object
o) = Object -> Value
Object forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall ω. ToMustache ω => ω -> Value
toMustache
#if MIN_VERSION_aeson(2,0,0)
    (forall v. KeyMap v -> HashMap Text v
KM.toHashMapText Object
o)
#else
    o
#endif
  toMustache (Aeson.Array  Array
a) = Array -> Value
Array forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall ω. ToMustache ω => ω -> Value
toMustache Array
a
  toMustache (Aeson.Number Scientific
n) = Scientific -> Value
Number Scientific
n
  toMustache (Aeson.String Text
s) = Text -> Value
String Text
s
  toMustache (Aeson.Bool   Bool
b) = Bool -> Value
Bool Bool
b
  toMustache Value
Aeson.Null       = Value
Null
instance ToMustache ω => ToMustache (HS.HashSet ω) where
  toMustache :: HashSet ω -> Value
toMustache = forall ω. ToMustache ω => [ω] -> Value
listToMustache' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HashSet a -> [a]
HS.toList
instance ToMustache ω => ToMustache (Set.Set ω) where
  toMustache :: Set ω -> Value
toMustache = forall ω. ToMustache ω => [ω] -> Value
listToMustache' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Set a -> [a]
Set.toList
instance (ToMustache α, ToMustache β) => ToMustache (α, β) where
  toMustache :: (α, β) -> Value
toMustache (α
a, β
b) = forall ω. ToMustache ω => ω -> Value
toMustache [forall ω. ToMustache ω => ω -> Value
toMustache α
a, forall ω. ToMustache ω => ω -> Value
toMustache β
b]
instance (ToMustache α, ToMustache β, ToMustache γ)
         => ToMustache (α, β, γ) where
  toMustache :: (α, β, γ) -> Value
toMustache (α
a, β
b, γ
c) = forall ω. ToMustache ω => ω -> Value
toMustache [forall ω. ToMustache ω => ω -> Value
toMustache α
a, forall ω. ToMustache ω => ω -> Value
toMustache β
b, forall ω. ToMustache ω => ω -> Value
toMustache γ
c]
instance (ToMustache α, ToMustache β, ToMustache γ, ToMustache δ)
         => ToMustache (α, β, γ, δ) where
  toMustache :: (α, β, γ, δ) -> Value
toMustache (α
a, β
b, γ
c, δ
d) = forall ω. ToMustache ω => ω -> Value
toMustache
    [ forall ω. ToMustache ω => ω -> Value
toMustache α
a
    , forall ω. ToMustache ω => ω -> Value
toMustache β
b
    , forall ω. ToMustache ω => ω -> Value
toMustache γ
c
    , forall ω. ToMustache ω => ω -> Value
toMustache δ
d
    ]
instance ( ToMustache α
         , ToMustache β
         , ToMustache γ
         , ToMustache δ
         , ToMustache ε
         ) => ToMustache (α, β, γ, δ, ε) where
  toMustache :: (α, β, γ, δ, ε) -> Value
toMustache (α
a, β
b, γ
c, δ
d, ε
e) = forall ω. ToMustache ω => ω -> Value
toMustache
    [ forall ω. ToMustache ω => ω -> Value
toMustache α
a
    , forall ω. ToMustache ω => ω -> Value
toMustache β
b
    , forall ω. ToMustache ω => ω -> Value
toMustache γ
c
    , forall ω. ToMustache ω => ω -> Value
toMustache δ
d
    , forall ω. ToMustache ω => ω -> Value
toMustache ε
e
    ]
instance ( ToMustache α
         , ToMustache β
         , ToMustache γ
         , ToMustache δ
         , ToMustache ε
         , ToMustache ζ
         ) => ToMustache (α, β, γ, δ, ε, ζ) where
  toMustache :: (α, β, γ, δ, ε, ζ) -> Value
toMustache (α
a, β
b, γ
c, δ
d, ε
e, ζ
f) = forall ω. ToMustache ω => ω -> Value
toMustache
    [ forall ω. ToMustache ω => ω -> Value
toMustache α
a
    , forall ω. ToMustache ω => ω -> Value
toMustache β
b
    , forall ω. ToMustache ω => ω -> Value
toMustache γ
c
    , forall ω. ToMustache ω => ω -> Value
toMustache δ
d
    , forall ω. ToMustache ω => ω -> Value
toMustache ε
e
    , forall ω. ToMustache ω => ω -> Value
toMustache ζ
f
    ]
instance ( ToMustache α
         , ToMustache β
         , ToMustache γ
         , ToMustache δ
         , ToMustache ε
         , ToMustache ζ
         , ToMustache η
         ) => ToMustache (α, β, γ, δ, ε, ζ, η) where
  toMustache :: (α, β, γ, δ, ε, ζ, η) -> Value
toMustache (α
a, β
b, γ
c, δ
d, ε
e, ζ
f, η
g) = forall ω. ToMustache ω => ω -> Value
toMustache
    [ forall ω. ToMustache ω => ω -> Value
toMustache α
a
    , forall ω. ToMustache ω => ω -> Value
toMustache β
b
    , forall ω. ToMustache ω => ω -> Value
toMustache γ
c
    , forall ω. ToMustache ω => ω -> Value
toMustache δ
d
    , forall ω. ToMustache ω => ω -> Value
toMustache ε
e
    , forall ω. ToMustache ω => ω -> Value
toMustache ζ
f
    , forall ω. ToMustache ω => ω -> Value
toMustache η
g
    ]
instance ( ToMustache α
         , ToMustache β
         , ToMustache γ
         , ToMustache δ
         , ToMustache ε
         , ToMustache ζ
         , ToMustache η
         , ToMustache θ
         ) => ToMustache (α, β, γ, δ, ε, ζ, η, θ) where
  toMustache :: (α, β, γ, δ, ε, ζ, η, θ) -> Value
toMustache (α
a, β
b, γ
c, δ
d, ε
e, ζ
f, η
g, θ
h) = forall ω. ToMustache ω => ω -> Value
toMustache
    [ forall ω. ToMustache ω => ω -> Value
toMustache α
a
    , forall ω. ToMustache ω => ω -> Value
toMustache β
b
    , forall ω. ToMustache ω => ω -> Value
toMustache γ
c
    , forall ω. ToMustache ω => ω -> Value
toMustache δ
d
    , forall ω. ToMustache ω => ω -> Value
toMustache ε
e
    , forall ω. ToMustache ω => ω -> Value
toMustache ζ
f
    , forall ω. ToMustache ω => ω -> Value
toMustache η
g
    , forall ω. ToMustache ω => ω -> Value
toMustache θ
h
    ]
type TemplateCache = HM.HashMap String Template
type Key = Text
data Template = Template
  { Template -> String
name     :: String
  , Template -> STree
ast      :: STree
  , Template -> TemplateCache
partials :: TemplateCache
  } deriving (Int -> Template -> ShowS
[Template] -> ShowS
Template -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Template] -> ShowS
$cshowList :: [Template] -> ShowS
show :: Template -> String
$cshow :: Template -> String
showsPrec :: Int -> Template -> ShowS
$cshowsPrec :: Int -> Template -> ShowS
Show)
deriveLift ''DataIdentifier
deriveLift ''Node
deriveLift ''Template
#if !MIN_VERSION_unordered_containers(0,2,17)
instance Lift TemplateCache where
#if MIN_VERSION_template_haskell(2,16,0)
  liftTyped m = [|| HM.fromList $$(liftTyped $ HM.toList m) ||]
#else
  lift m = [| HM.fromList $(lift $ HM.toList m) |]
#endif
#endif
#if !MIN_VERSION_text(1,2,4)
instance Lift Text where
  lift = lift . unpack
#endif