{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Yaml.TH
(
yamlQQ
#if MIN_VERSION_template_haskell(2,9,0)
, decodeFile
#endif
, Value (..)
, Parser
, Object
, Array
, object
, array
, (.=)
, (.:)
, (.:?)
, (.!=)
, FromJSON (..)
) where
import Data.Text.Encoding
import qualified Data.Text as T
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Quote
import Data.Yaml hiding (decodeFile)
decodeFile :: forall a. (Lift a, FromJSON a) => FilePath -> Q (TExp a)
decodeFile :: forall a. (Lift a, FromJSON a) => FilePath -> Q (TExp a)
decodeFile FilePath
path = do
FilePath -> Q ()
addDependentFile FilePath
path
a
x <- forall a. IO a -> Q a
runIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. (MonadIO m, FromJSON a) => FilePath -> m a
decodeFileThrow FilePath
path
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Exp -> TExp a
TExp (forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
lift (a
x :: a))
yamlExp :: String -> Q Exp
yamlExp :: FilePath -> Q Exp
yamlExp FilePath
input = do
Value
val <- forall a. IO a -> Q a
runIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(MonadThrow m, FromJSON a) =>
ByteString -> m a
decodeThrow forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack FilePath
input
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
lift (Value
val :: Value)
yamlQQ :: QuasiQuoter
yamlQQ :: QuasiQuoter
yamlQQ = QuasiQuoter {
quoteExp :: FilePath -> Q Exp
quoteExp = FilePath -> Q Exp
yamlExp
, quotePat :: FilePath -> Q Pat
quotePat = forall {m :: * -> *} {p} {a}. MonadFail m => FilePath -> p -> m a
notDefined FilePath
"quotePat"
, quoteType :: FilePath -> Q Type
quoteType = forall {m :: * -> *} {p} {a}. MonadFail m => FilePath -> p -> m a
notDefined FilePath
"quoteType"
, quoteDec :: FilePath -> Q [Dec]
quoteDec = forall {m :: * -> *} {p} {a}. MonadFail m => FilePath -> p -> m a
notDefined FilePath
"quoteDec"
} where
notDefined :: FilePath -> p -> m a
notDefined FilePath
name p
_ = forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath
name forall a. [a] -> [a] -> [a]
++ FilePath
" is not defined for yamlQQ")