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

module Faker.Provider.Bird where

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

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

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

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


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



parseUnresolvedBirdFields ::
     (FromJSON a, Monoid a)
  => FakerSettings
  -> [Text]
  -> Value
  -> Parser (Unresolved a)
parseUnresolvedBirdFields :: FakerSettings -> [Text] -> Value -> Parser (Unresolved a)
parseUnresolvedBirdFields FakerSettings
settings [Text]
txts Value
val = do
  Value
bird <- FakerSettings -> Value -> Parser Value
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseBird FakerSettings
settings Value
val
  Value -> [Text] -> Parser (Unresolved a)
forall a. FromJSON a => Value -> [Text] -> Parser (Unresolved a)
helper Value
bird [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 "bird" "anatomy")

$(genProvider "bird" "anatomy")

$(genParser "bird" "anatomy_past_tense")

$(genProvider "bird" "anatomy_past_tense")

$(genParser "bird" "geo")

$(genProvider "bird" "geo")

$(genParser "bird" "colors")

$(genProvider "bird" "colors")

$(genParser "bird" "emotional_adjectives")

$(genProvider "bird" "emotional_adjectives")

$(genParser "bird" "silly_adjectives")

$(genProvider "bird" "silly_adjectives")

$(genParser "bird" "adjectives")

$(genProvider "bird" "adjectives")

$(genParser "bird" "common_family_name")

$(genProvider "bird" "common_family_name")



$(genParserUnresolved "bird" "plausible_common_names")
$(genProviderUnresolved "bird" "plausible_common_names")
$(genParserUnresolved "bird" "implausible_common_names")
$(genProviderUnresolved "bird" "implausible_common_names")


resolveBirdText :: (MonadIO m, MonadThrow m) => FakerSettings -> Text -> m Text
resolveBirdText :: FakerSettings -> Text -> m Text
resolveBirdText = (FakerSettings -> Text -> m Text)
-> FakerSettings -> Text -> m Text
forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
(FakerSettings -> Text -> m Text)
-> FakerSettings -> Text -> m Text
genericResolver' FakerSettings -> Text -> m Text
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> Text -> m Text
resolveBirdField

resolveBirdField :: (MonadThrow m, MonadIO m) => FakerSettings -> Text -> m Text
resolveBirdField :: FakerSettings -> Text -> m Text
resolveBirdField FakerSettings
settings field :: Text
field@Text
"geo" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdGeoProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"adjective" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdAdjectivesProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"anatomy" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdAnatomyProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"anatomy_past_tense" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdAnatomyPastTenseProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"common_name" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdCommonFamilyNameProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"color" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdColorsProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"emotional_adjective" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdEmotionalAdjectivesProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"silly_adjective" =
  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
"bird" Text
field FakerSettings -> m (Vector Text)
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> m (Vector Text)
birdSillyAdjectivesProvider FakerSettings
settings
resolveBirdField FakerSettings
settings field :: Text
field@Text
"Name.last_name" =
  FakerSettings -> Text -> m Text
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> Text -> m Text
resolveNameField FakerSettings
settings Text
"last_name"
resolveBirdField 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
"bird" Text
str


$(genParsers "bird" ["order_common_map","Accipitriformes"])
$(genProviders "bird" ["order_common_map","Accipitriformes"])

$(genParsers "bird" ["order_common_map","Anseriformes"])
$(genProviders "bird" ["order_common_map","Anseriformes"])

$(genParsers "bird" ["order_common_map","Apterygiformes"])
$(genProviders "bird" ["order_common_map","Apterygiformes"])

$(genParsers "bird" ["order_common_map","Bucerotiformes"])
$(genProviders "bird" ["order_common_map","Bucerotiformes"])

$(genParsers "bird" ["order_common_map","Caprimulgiformes"])
$(genProviders "bird" ["order_common_map","Caprimulgiformes"])

$(genParsers "bird" ["order_common_map","Cariamiformes"])
$(genProviders "bird" ["order_common_map","Cariamiformes"])

$(genParsers "bird" ["order_common_map","Casuariiformes"])
$(genProviders "bird" ["order_common_map","Casuariiformes"])

$(genParsers "bird" ["order_common_map","Cathartiformes"])
$(genProviders "bird" ["order_common_map","Cathartiformes"])

$(genParsers "bird" ["order_common_map","Charadriiformes"])
$(genProviders "bird" ["order_common_map","Charadriiformes"])

$(genParsers "bird" ["order_common_map","Ciconiiformes"])
$(genProviders "bird" ["order_common_map","Ciconiiformes"])

$(genParsers "bird" ["order_common_map","Coliiformes"])
$(genProviders "bird" ["order_common_map","Coliiformes"])

$(genParsers "bird" ["order_common_map","Columbiformes"])
$(genProviders "bird" ["order_common_map","Columbiformes"])

$(genParsers "bird" ["order_common_map","Coraciiformes"])
$(genProviders "bird" ["order_common_map","Coraciiformes"])

$(genParsers "bird" ["order_common_map","Cuculiformes"])
$(genProviders "bird" ["order_common_map","Cuculiformes"])

$(genParsers "bird" ["order_common_map","Eurypygiformes"])
$(genProviders "bird" ["order_common_map","Eurypygiformes"])

$(genParsers "bird" ["order_common_map","Falconiformes"])
$(genProviders "bird" ["order_common_map","Falconiformes"])

$(genParsers "bird" ["order_common_map","Galbuliformes"])
$(genProviders "bird" ["order_common_map","Galbuliformes"])

$(genParsers "bird" ["order_common_map","Galliformes"])
$(genProviders "bird" ["order_common_map","Galliformes"])

$(genParsers "bird" ["order_common_map","Gaviiformes"])
$(genProviders "bird" ["order_common_map","Gaviiformes"])

$(genParsers "bird" ["order_common_map","Gruiformes"])
$(genProviders "bird" ["order_common_map","Gruiformes"])

$(genParsers "bird" ["order_common_map","Mesitornithiformes"])
$(genProviders "bird" ["order_common_map","Mesitornithiformes"])

$(genParsers "bird" ["order_common_map","Musophagiformes"])
$(genProviders "bird" ["order_common_map","Musophagiformes"])

$(genParsers "bird" ["order_common_map","Opisthocomiformes"])
$(genProviders "bird" ["order_common_map","Opisthocomiformes"])

$(genParsers "bird" ["order_common_map","Otidiformes"])
$(genProviders "bird" ["order_common_map","Otidiformes"])

$(genParsers "bird" ["order_common_map","Passeriformes"])
$(genProviders "bird" ["order_common_map","Passeriformes"])

$(genParsers "bird" ["order_common_map","Pelecaniformes"])
$(genProviders "bird" ["order_common_map","Pelecaniformes"])

$(genParsers "bird" ["order_common_map","Phaethontiformes"])
$(genProviders "bird" ["order_common_map","Phaethontiformes"])

$(genParsers "bird" ["order_common_map","Phoenicopteriformes"])
$(genProviders "bird" ["order_common_map","Phoenicopteriformes"])

$(genParsers "bird" ["order_common_map","Piciformes"])
$(genProviders "bird" ["order_common_map","Piciformes"])

$(genParsers "bird" ["order_common_map","Podicipediformes"])
$(genProviders "bird" ["order_common_map","Podicipediformes"])

$(genParsers "bird" ["order_common_map","Procellariiformes"])
$(genProviders "bird" ["order_common_map","Procellariiformes"])

$(genParsers "bird" ["order_common_map","Psittaciformes"])
$(genProviders "bird" ["order_common_map","Psittaciformes"])

$(genParsers "bird" ["order_common_map","Pterocliformes"])
$(genProviders "bird" ["order_common_map","Pterocliformes"])

$(genParsers "bird" ["order_common_map","Rheiformes"])
$(genProviders "bird" ["order_common_map","Rheiformes"])

$(genParsers "bird" ["order_common_map","Sphenisciformes"])
$(genProviders "bird" ["order_common_map","Sphenisciformes"])

$(genParsers "bird" ["order_common_map","Strigiformes"])
$(genProviders "bird" ["order_common_map","Strigiformes"])

$(genParsers "bird" ["order_common_map","Struthioniformes"])
$(genProviders "bird" ["order_common_map","Struthioniformes"])

$(genParsers "bird" ["order_common_map","Suliformes"])
$(genProviders "bird" ["order_common_map","Suliformes"])

$(genParsers "bird" ["order_common_map","Tinamiformes"])
$(genProviders "bird" ["order_common_map","Tinamiformes"])

$(genParsers "bird" ["order_common_map","Trogoniformes"])
$(genProviders "bird" ["order_common_map","Trogoniformes"])