{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Faker.Provider.Nation 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.Word (Word8) import Data.Yaml import Faker import Faker.Internal import Faker.Provider.TH import Language.Haskell.TH parseNation :: FromJSON a => FakerSettings -> Value -> Parser a parseNation :: forall a. FromJSON a => FakerSettings -> Value -> Parser a parseNation FakerSettings settings (Object Object obj) = do Object en <- Object obj Object -> AesonKey -> Parser Object forall a. FromJSON a => Object -> AesonKey -> Parser a .: (FakerSettings -> AesonKey getLocaleKey FakerSettings settings) Object faker <- Object en Object -> AesonKey -> Parser Object forall a. FromJSON a => Object -> AesonKey -> Parser a .: AesonKey "faker" a nation <- Object faker Object -> AesonKey -> Parser a forall a. FromJSON a => Object -> AesonKey -> Parser a .: AesonKey "nation" a -> Parser a forall a. a -> Parser a forall (f :: * -> *) a. Applicative f => a -> f a pure a nation parseNation FakerSettings settings Value val = String -> Parser a forall a. 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) parseNationField :: (FromJSON a, Monoid a) => FakerSettings -> AesonKey -> Value -> Parser a parseNationField :: forall a. (FromJSON a, Monoid a) => FakerSettings -> AesonKey -> Value -> Parser a parseNationField FakerSettings settings AesonKey txt Value val = do Object nation <- FakerSettings -> Value -> Parser Object forall a. FromJSON a => FakerSettings -> Value -> Parser a parseNation FakerSettings settings Value val a field <- Object nation Object -> AesonKey -> Parser (Maybe a) forall a. FromJSON a => Object -> AesonKey -> Parser (Maybe a) .:? AesonKey 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 a. a -> Parser a forall (f :: * -> *) a. Applicative f => a -> f a pure a field parseNationFields :: (FromJSON a, Monoid a) => FakerSettings -> [AesonKey] -> Value -> Parser a parseNationFields :: forall a. (FromJSON a, Monoid a) => FakerSettings -> [AesonKey] -> Value -> Parser a parseNationFields FakerSettings settings [AesonKey] txts Value val = do Value nation <- FakerSettings -> Value -> Parser Value forall a. FromJSON a => FakerSettings -> Value -> Parser a parseNation FakerSettings settings Value val Value -> [AesonKey] -> Parser a forall a. FromJSON a => Value -> [AesonKey] -> Parser a helper Value nation [AesonKey] txts where helper :: (FromJSON a) => Value -> [AesonKey] -> Parser a helper :: forall a. FromJSON a => Value -> [AesonKey] -> Parser a helper Value a [] = Value -> Parser a forall a. FromJSON a => Value -> Parser a parseJSON Value a helper (Object Object a) (AesonKey x:[AesonKey] xs) = do Value field <- Object a Object -> AesonKey -> Parser Value forall a. FromJSON a => Object -> AesonKey -> Parser a .: AesonKey x Value -> [AesonKey] -> Parser a forall a. FromJSON a => Value -> [AesonKey] -> Parser a helper Value field [AesonKey] xs helper Value a (AesonKey x:[AesonKey] xs) = String -> Parser a forall a. 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) $(genParser "nation" "nationality") $(genProvider "nation" "nationality") $(genParser "nation" "language") $(genProvider "nation" "language") $(genParser "nation" "capital_city") $(genProvider "nation" "capital_city") parseNationFlagEmoji :: FakerSettings -> Value -> Parser (Vector (Vector Word8)) parseNationFlagEmoji :: FakerSettings -> Value -> Parser (Vector (Vector Word8)) parseNationFlagEmoji FakerSettings settings = FakerSettings -> AesonKey -> Value -> Parser (Vector (Vector Word8)) forall a. (FromJSON a, Monoid a) => FakerSettings -> AesonKey -> Value -> Parser a parseNationField FakerSettings settings AesonKey "flag" nationFlagEmojiProvider :: (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector (Vector Word8)) nationFlagEmojiProvider :: forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector (Vector Word8)) nationFlagEmojiProvider FakerSettings settings = FakerSettings -> SourceData -> (FakerSettings -> Value -> Parser (Vector (Vector Word8))) -> m (Vector (Vector Word8)) forall (m :: * -> *) a. (MonadThrow m, MonadIO m) => FakerSettings -> SourceData -> (FakerSettings -> Value -> Parser a) -> m a fetchData FakerSettings settings SourceData Nation FakerSettings -> Value -> Parser (Vector (Vector Word8)) parseNationFlagEmoji