{-# LANGUAGE OverloadedStrings #-}

module Faker.Provider.Ancient where

import Config
import Control.Monad.Catch
import Control.Monad.IO.Class
import Data.Map.Strict (Map)
import Data.Monoid ((<>))
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Vector (Vector)
import Data.Yaml
import Faker
import Faker.Internal


parseAncient :: FromJSON a => FakerSettings -> Value -> Parser a
parseAncient :: FakerSettings -> Value -> Parser a
parseAncient FakerSettings
settings (Object Object
obj) = do
  Object
en <- Object
obj Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: (FakerSettings -> Key
getLocaleKey FakerSettings
settings)
  Object
faker <- Object
en Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"faker"
  a
ancient <- Object
faker Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ancient"
  a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
ancient
parseAncient 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)

parseAncientField ::
     (FromJSON a, Monoid a) => FakerSettings -> AesonKey -> Value -> Parser a
parseAncientField :: FakerSettings -> Key -> Value -> Parser a
parseAncientField FakerSettings
settings Key
txt Value
val = do
  Object
ancient <- FakerSettings -> Value -> Parser Object
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseAncient FakerSettings
settings Value
val
  a
field <- Object
ancient Object -> Key -> Parser (Maybe a)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
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

parseAncientGod :: (FromJSON a, Monoid a) => FakerSettings -> Value -> Parser a
parseAncientGod :: FakerSettings -> Value -> Parser a
parseAncientGod FakerSettings
settings = FakerSettings -> Key -> Value -> Parser a
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Key -> Value -> Parser a
parseAncientField FakerSettings
settings Key
"god"

parseAncientPrimordial ::
     (FromJSON a, Monoid a) => FakerSettings -> Value -> Parser a
parseAncientPrimordial :: FakerSettings -> Value -> Parser a
parseAncientPrimordial FakerSettings
settings = FakerSettings -> Key -> Value -> Parser a
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Key -> Value -> Parser a
parseAncientField FakerSettings
settings Key
"primordial"

parseAncientTitan ::
     (FromJSON a, Monoid a) => FakerSettings -> Value -> Parser a
parseAncientTitan :: FakerSettings -> Value -> Parser a
parseAncientTitan FakerSettings
settings = FakerSettings -> Key -> Value -> Parser a
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Key -> Value -> Parser a
parseAncientField FakerSettings
settings Key
"titan"

parseAncientHero :: (FromJSON a, Monoid a) => FakerSettings -> Value -> Parser a
parseAncientHero :: FakerSettings -> Value -> Parser a
parseAncientHero FakerSettings
settings = FakerSettings -> Key -> Value -> Parser a
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Key -> Value -> Parser a
parseAncientField FakerSettings
settings Key
"hero"

ancientGodProvider ::
     (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text)
ancientGodProvider :: FakerSettings -> m (Vector Text)
ancientGodProvider FakerSettings
settings = FakerSettings
-> SourceData
-> (FakerSettings -> Value -> Parser (Vector Text))
-> m (Vector Text)
forall (m :: * -> *) a.
(MonadThrow m, MonadIO m) =>
FakerSettings
-> SourceData -> (FakerSettings -> Value -> Parser a) -> m a
fetchData FakerSettings
settings SourceData
Ancient FakerSettings -> Value -> Parser (Vector Text)
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Value -> Parser a
parseAncientGod

ancientPrimordialProvider ::
     (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text)
ancientPrimordialProvider :: FakerSettings -> m (Vector Text)
ancientPrimordialProvider FakerSettings
settings =
  FakerSettings
-> SourceData
-> (FakerSettings -> Value -> Parser (Vector Text))
-> m (Vector Text)
forall (m :: * -> *) a.
(MonadThrow m, MonadIO m) =>
FakerSettings
-> SourceData -> (FakerSettings -> Value -> Parser a) -> m a
fetchData FakerSettings
settings SourceData
Ancient FakerSettings -> Value -> Parser (Vector Text)
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Value -> Parser a
parseAncientPrimordial

ancientTitanProvider ::
     (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text)
ancientTitanProvider :: FakerSettings -> m (Vector Text)
ancientTitanProvider FakerSettings
settings = FakerSettings
-> SourceData
-> (FakerSettings -> Value -> Parser (Vector Text))
-> m (Vector Text)
forall (m :: * -> *) a.
(MonadThrow m, MonadIO m) =>
FakerSettings
-> SourceData -> (FakerSettings -> Value -> Parser a) -> m a
fetchData FakerSettings
settings SourceData
Ancient FakerSettings -> Value -> Parser (Vector Text)
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Value -> Parser a
parseAncientTitan

ancientHeroProvider ::
     (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text)
ancientHeroProvider :: FakerSettings -> m (Vector Text)
ancientHeroProvider FakerSettings
settings = FakerSettings
-> SourceData
-> (FakerSettings -> Value -> Parser (Vector Text))
-> m (Vector Text)
forall (m :: * -> *) a.
(MonadThrow m, MonadIO m) =>
FakerSettings
-> SourceData -> (FakerSettings -> Value -> Parser a) -> m a
fetchData FakerSettings
settings SourceData
Ancient FakerSettings -> Value -> Parser (Vector Text)
forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> Value -> Parser a
parseAncientHero