{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

module Faker.Provider.Superhero where

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

parseSuperhero :: FromJSON a => FakerSettings -> Value -> Parser a
parseSuperhero :: FakerSettings -> Value -> Parser a
parseSuperhero 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
superhero <- Object
faker Object -> Text -> Parser a
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"superhero"
  a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
superhero
parseSuperhero 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)

parseSuperheroField ::
     (FromJSON a, Monoid a) => FakerSettings -> Text -> Value -> Parser a
parseSuperheroField :: FakerSettings -> Text -> Value -> Parser a
parseSuperheroField FakerSettings
settings Text
txt Value
val = do
  Object
superhero <- FakerSettings -> Value -> Parser Object
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseSuperhero FakerSettings
settings Value
val
  a
field <- Object
superhero 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

parseSuperheroFields ::
     (FromJSON a, Monoid a) => FakerSettings -> [Text] -> Value -> Parser a
parseSuperheroFields :: FakerSettings -> [Text] -> Value -> Parser a
parseSuperheroFields FakerSettings
settings [Text]
txts Value
val = do
  Value
superhero <- FakerSettings -> Value -> Parser Value
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseSuperhero FakerSettings
settings Value
val
  Value -> [Text] -> Parser a
forall a. FromJSON a => Value -> [Text] -> Parser a
helper Value
superhero [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)

parseUnresolvedSuperheroField ::
     (FromJSON a, Monoid a)
  => FakerSettings
  -> Text
  -> Value
  -> Parser (Unresolved a)
parseUnresolvedSuperheroField :: FakerSettings -> Text -> Value -> Parser (Unresolved a)
parseUnresolvedSuperheroField FakerSettings
settings Text
txt Value
val = do
  Object
superhero <- FakerSettings -> Value -> Parser Object
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseSuperhero FakerSettings
settings Value
val
  a
field <- Object
superhero 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
  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
field

$(genParser "superhero" "power")

$(genProvider "superhero" "power")

$(genParser "superhero" "prefix")

$(genProvider "superhero" "prefix")

$(genParser "superhero" "suffix")

$(genProvider "superhero" "suffix")

$(genParser "superhero" "descriptor")

$(genProvider "superhero" "descriptor")

$(genParserUnresolved "superhero" "name")

$(genProviderUnresolved "superhero" "name")

resolveSuperheroText ::
     (MonadIO m, MonadThrow m) => FakerSettings -> Text -> m Text
resolveSuperheroText :: FakerSettings -> Text -> m Text
resolveSuperheroText FakerSettings
settings Text
txt = FakerSettings
-> Text -> (FakerSettings -> Text -> m Text) -> m Text
forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
FakerSettings
-> Text -> (FakerSettings -> Text -> m Text) -> m Text
genericResolver FakerSettings
settings Text
txt FakerSettings -> Text -> m Text
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> Text -> m Text
resolveSuperheroField

resolveSuperheroField ::
     (MonadThrow m, MonadIO m) => FakerSettings -> Text -> m Text
resolveSuperheroField :: FakerSettings -> Text -> m Text
resolveSuperheroField FakerSettings
settings field :: Text
field@Text
"Superhero.prefix" =
  Text
-> Text
-> (FakerSettings -> m (Vector Text))
-> FakerSettings
-> m Text
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
Text
-> Text
-> (FakerSettings -> m (Vector Text))
-> FakerSettings
-> m Text
cachedRandomVec Text
"superhero" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
superheroPrefixProvider FakerSettings
settings
resolveSuperheroField FakerSettings
settings field :: Text
field@Text
"Superhero.suffix" =
  Text
-> Text
-> (FakerSettings -> m (Vector Text))
-> FakerSettings
-> m Text
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
Text
-> Text
-> (FakerSettings -> m (Vector Text))
-> FakerSettings
-> m Text
cachedRandomVec Text
"superhero" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
superheroSuffixProvider FakerSettings
settings
resolveSuperheroField FakerSettings
settings field :: Text
field@Text
"Superhero.descriptor" =
  Text
-> Text
-> (FakerSettings -> m (Vector Text))
-> FakerSettings
-> m Text
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
Text
-> Text
-> (FakerSettings -> m (Vector Text))
-> FakerSettings
-> m Text
cachedRandomVec Text
"superhero" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
superheroDescriptorProvider FakerSettings
settings
resolveSuperheroField FakerSettings
settings Text
str = FakerException -> m Text
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FakerException -> m Text) -> FakerException -> m Text
forall a b. (a -> b) -> a -> b
$ String -> Text -> FakerException
InvalidField String
"superhero" Text
str