{-|
Module      : $Header$
Description : Types and conversions
Copyright   : (c) Justus Adam, 2015
License     : BSD3
Maintainer  : dev@justus.science
Stability   : experimental
Portability : POSIX
-}
module Text.Mustache.Types
  (
  -- * Types for the Parser / Template
    ASTree
  , STree
  , Node(..)
  , DataIdentifier(..)
  , Template(..)
  , TemplateCache
  -- * Types for the Substitution / Data
  , Value(..)
  , Key
  -- ** Converting
  , object
  , (~>), (↝), (~=), (⥱)
  , ToMustache, toMustache, mFromJSON, integralToMustache
  -- ** Representation
  , Array, Object, Pair
  , SubM, askContext, askPartials
  , Context(..)
  ) where


import           Control.Monad.Reader
import qualified Data.Aeson                   as Aeson
import qualified Data.HashMap.Strict          as HM
import           Data.Text                    (Text)
import           Text.Mustache.Internal.Types


-- | Convenience function for creating Object values.
--
-- This function is supposed to be used in conjuction with the '~>' and '~=' operators.
--
-- ==== __Examples__
--
-- @
--   data Address = Address { ... }
--
--   instance Address ToJSON where
--     ...
--
--   data Person = Person { name :: String, address :: Address }
--
--   instance ToMustache Person where
--     toMustache (Person { name, address }) = object
--       [ "name" ~> name
--       , "address" ~= address
--       ]
-- @
--
-- Here we can see that we can use the '~>' operator for values that have
-- themselves a 'ToMustache' instance, or alternatively if they lack such an
-- instance but provide an instance for the 'ToJSON' typeclass we can use the
-- '~=' operator.
object :: [Pair] -> Value
object :: [Pair] -> Value
object = Object -> Value
Object (Object -> Value) -> ([Pair] -> Object) -> [Pair] -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Object
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList


-- | Map keys to values that provide a 'ToMustache' instance
--
-- Recommended in conjunction with the `OverloadedStrings` extension.
(~>) :: ToMustache ω => Text -> ω -> Pair
~> :: Text -> ω -> Pair
(~>) Text
t = (Text
t, ) (Value -> Pair) -> (ω -> Value) -> ω -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ω -> Value
forall ω. ToMustache ω => ω -> Value
toMustache
{-# INLINEABLE (~>) #-}
infixr 8 ~>

-- | Unicode version of '~>'
(↝) :: ToMustache ω => Text -> ω -> Pair
↝ :: Text -> ω -> Pair
(↝) = Text -> ω -> Pair
forall ω. ToMustache ω => Text -> ω -> Pair
(~>)
{-# INLINEABLE () #-}
infixr 8 


-- | Map keys to values that provide a 'ToJSON' instance
--
-- Recommended in conjunction with the `OverloadedStrings` extension.
(~=) :: Aeson.ToJSON ι => Text -> ι -> Pair
~= :: Text -> ι -> Pair
(~=) Text
t = (Text
t Text -> Value -> Pair
forall ω. ToMustache ω => Text -> ω -> Pair
~>) (Value -> Pair) -> (ι -> Value) -> ι -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ι -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON
{-# INLINEABLE (~=) #-}
infixr 8 ~=


-- | Unicode version of '~='
(⥱) :: Aeson.ToJSON ι => Text -> ι -> Pair
⥱ :: Text -> ι -> Pair
(⥱) = Text -> ι -> Pair
forall ι. ToJSON ι => Text -> ι -> Pair
(~=)
{-# INLINEABLE () #-}
infixr 8 


-- | Converts a value that can be represented as JSON to a Value.
mFromJSON :: Aeson.ToJSON ι => ι -> Value
mFromJSON :: ι -> Value
mFromJSON = Value -> Value
forall ω. ToMustache ω => ω -> Value
toMustache (Value -> Value) -> (ι -> Value) -> ι -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ι -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON


askContext :: SubM (Context Value)
askContext :: SubM (Context Value)
askContext = ((Context Value, TemplateCache) -> Context Value)
-> SubM (Context Value)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Context Value, TemplateCache) -> Context Value
forall a b. (a, b) -> a
fst


askPartials :: SubM TemplateCache
askPartials :: SubM TemplateCache
askPartials = ((Context Value, TemplateCache) -> TemplateCache)
-> SubM TemplateCache
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Context Value, TemplateCache) -> TemplateCache
forall a b. (a, b) -> b
snd