{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Faker.Provider.Tolkien where import Config import Control.Monad.Catch import Data.Text (Text) import Data.Vector (Vector) import Data.Monoid ((<>)) import Data.Yaml import Faker import Faker.Internal import Faker.Provider.TH import Language.Haskell.TH parseTolkien :: FromJSON a => FakerSettings -> Value -> Parser a parseTolkien :: FakerSettings -> Value -> Parser a parseTolkien FakerSettings settings (Object Object obj) = do Object en <- Object obj Object -> Text -> Parser Object forall a. FromJSON a => Object -> Text -> Parser a .: (FakerSettings -> Text getLocale FakerSettings settings) Object faker <- Object en Object -> Text -> Parser Object forall a. FromJSON a => Object -> Text -> Parser a .: Text "faker" a tolkien <- Object faker Object -> Text -> Parser a forall a. FromJSON a => Object -> Text -> Parser a .: Text "tolkien" a -> Parser a forall (f :: * -> *) a. Applicative f => a -> f a pure a tolkien parseTolkien FakerSettings settings Value val = String -> Parser a forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Parser a) -> String -> Parser a forall a b. (a -> b) -> a -> b $ String "expected Object, but got " String -> String -> String forall a. Semigroup a => a -> a -> a <> (Value -> String forall a. Show a => a -> String show Value val) parseTolkienField :: (FromJSON a, Monoid a) => FakerSettings -> Text -> Value -> Parser a parseTolkienField :: FakerSettings -> Text -> Value -> Parser a parseTolkienField FakerSettings settings Text txt Value val = do Object tolkien <- FakerSettings -> Value -> Parser Object forall a. FromJSON a => FakerSettings -> Value -> Parser a parseTolkien FakerSettings settings Value val a field <- Object tolkien Object -> Text -> Parser (Maybe a) forall a. FromJSON a => Object -> Text -> Parser (Maybe a) .:? Text txt Parser (Maybe a) -> a -> Parser a forall a. Parser (Maybe a) -> a -> Parser a .!= a forall a. Monoid a => a mempty a -> Parser a forall (f :: * -> *) a. Applicative f => a -> f a pure a field parseTolkienFields :: (FromJSON a, Monoid a) => FakerSettings -> [Text] -> Value -> Parser a parseTolkienFields :: FakerSettings -> [Text] -> Value -> Parser a parseTolkienFields FakerSettings settings [Text] txts Value val = do Value tolkien <- FakerSettings -> Value -> Parser Value forall a. FromJSON a => FakerSettings -> Value -> Parser a parseTolkien FakerSettings settings Value val Value -> [Text] -> Parser a forall a. FromJSON a => Value -> [Text] -> Parser a helper Value tolkien [Text] txts where helper :: (FromJSON a) => Value -> [Text] -> Parser a helper :: Value -> [Text] -> Parser a helper Value a [] = Value -> Parser a forall a. FromJSON a => Value -> Parser a parseJSON Value a helper (Object Object a) (Text x:[Text] xs) = do Value field <- Object a Object -> Text -> Parser Value forall a. FromJSON a => Object -> Text -> Parser a .: Text x Value -> [Text] -> Parser a forall a. FromJSON a => Value -> [Text] -> Parser a helper Value field [Text] xs helper Value a (Text x:[Text] xs) = String -> Parser a forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Parser a) -> String -> Parser a forall a b. (a -> b) -> a -> b $ String "expect Object, but got " String -> String -> String forall a. Semigroup a => a -> a -> a <> (Value -> String forall a. Show a => a -> String show Value a) parseUnresolvedTolkienFields :: (FromJSON a, Monoid a) => FakerSettings -> [Text] -> Value -> Parser (Unresolved a) parseUnresolvedTolkienFields :: FakerSettings -> [Text] -> Value -> Parser (Unresolved a) parseUnresolvedTolkienFields FakerSettings settings [Text] txts Value val = do Value tolkien <- FakerSettings -> Value -> Parser Value forall a. FromJSON a => FakerSettings -> Value -> Parser a parseTolkien FakerSettings settings Value val Value -> [Text] -> Parser (Unresolved a) forall a. FromJSON a => Value -> [Text] -> Parser (Unresolved a) helper Value tolkien [Text] txts where helper :: (FromJSON a) => Value -> [Text] -> Parser (Unresolved a) helper :: Value -> [Text] -> Parser (Unresolved a) helper Value a [] = do a v <- Value -> Parser a forall a. FromJSON a => Value -> Parser a parseJSON Value a Unresolved a -> Parser (Unresolved a) forall (f :: * -> *) a. Applicative f => a -> f a pure (Unresolved a -> Parser (Unresolved a)) -> Unresolved a -> Parser (Unresolved a) forall a b. (a -> b) -> a -> b $ a -> Unresolved a forall (f :: * -> *) a. Applicative f => a -> f a pure a v helper (Object Object a) (Text x:[Text] xs) = do Value field <- Object a Object -> Text -> Parser Value forall a. FromJSON a => Object -> Text -> Parser a .: Text x Value -> [Text] -> Parser (Unresolved a) forall a. FromJSON a => Value -> [Text] -> Parser (Unresolved a) helper Value field [Text] xs helper Value a [Text] _ = String -> Parser (Unresolved a) forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Parser (Unresolved a)) -> String -> Parser (Unresolved a) forall a b. (a -> b) -> a -> b $ String "expect Object, but got " String -> String -> String forall a. Semigroup a => a -> a -> a <> (Value -> String forall a. Show a => a -> String show Value a) $(genParser "tolkien" "poems") $(genProvider "tolkien" "poems") $(genParser "tolkien" "locations") $(genProvider "tolkien" "locations") $(genParser "tolkien" "races") $(genProvider "tolkien" "races") $(genParser "tolkien" "characters") $(genProvider "tolkien" "characters") $(genParsers "tolkien" ["lord_of_the_rings","characters"]) $(genProviders "tolkien" ["lord_of_the_rings","characters"]) $(genParsers "tolkien" ["lord_of_the_rings","locations"]) $(genProviders "tolkien" ["lord_of_the_rings","locations"]) $(genParsers "tolkien" ["lord_of_the_rings","quotes"]) $(genProviders "tolkien" ["lord_of_the_rings","quotes"]) $(genParsers "tolkien" ["hobbit","character"]) $(genProviders "tolkien" ["hobbit","character"]) $(genParsers "tolkien" ["hobbit","thorins_company"]) $(genProviders "tolkien" ["hobbit","thorins_company"]) $(genParsers "tolkien" ["hobbit","quote"]) $(genProviders "tolkien" ["hobbit","quote"]) $(genParsers "tolkien" ["hobbit","location"]) $(genProviders "tolkien" ["hobbit","location"])