{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Faker.Provider.Compass 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 parseCompass :: FromJSON a => FakerSettings -> Value -> Parser a parseCompass :: forall a. FromJSON a => FakerSettings -> Value -> Parser a parseCompass 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 compass <- Object faker Object -> Key -> Parser a forall a. FromJSON a => Object -> Key -> Parser a .: Key "compass" a -> Parser a forall a. a -> Parser a forall (f :: * -> *) a. Applicative f => a -> f a pure a compass parseCompass 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) parseCompassField :: (FromJSON a, Monoid a) => FakerSettings -> AesonKey -> Value -> Parser a parseCompassField :: forall a. (FromJSON a, Monoid a) => FakerSettings -> Key -> Value -> Parser a parseCompassField FakerSettings settings Key txt Value val = do Object compass <- FakerSettings -> Value -> Parser Object forall a. FromJSON a => FakerSettings -> Value -> Parser a parseCompass FakerSettings settings Value val a field <- Object compass 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 a. a -> Parser a forall (f :: * -> *) a. Applicative f => a -> f a pure a field parseCompassFields :: (FromJSON a, Monoid a) => FakerSettings -> [AesonKey] -> Value -> Parser a parseCompassFields :: forall a. (FromJSON a, Monoid a) => FakerSettings -> [Key] -> Value -> Parser a parseCompassFields FakerSettings settings [Key] txts Value val = do Value compass <- FakerSettings -> Value -> Parser Value forall a. FromJSON a => FakerSettings -> Value -> Parser a parseCompass FakerSettings settings Value val Value -> [Key] -> Parser a forall a. FromJSON a => Value -> [Key] -> Parser a helper Value compass [Key] txts where helper :: (FromJSON a) => Value -> [AesonKey] -> Parser a helper :: forall a. FromJSON a => Value -> [Key] -> Parser a helper Value a [] = Value -> Parser a forall a. FromJSON a => Value -> Parser a parseJSON Value a helper (Object Object a) (Key x:[Key] xs) = do Value field <- Object a Object -> Key -> Parser Value forall a. FromJSON a => Object -> Key -> Parser a .: Key x Value -> [Key] -> Parser a forall a. FromJSON a => Value -> [Key] -> Parser a helper Value field [Key] xs helper Value a (Key x:[Key] 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) parseUnresolvedCompassField :: (FromJSON a, Monoid a) => FakerSettings -> AesonKey -> Value -> Parser (Unresolved a) parseUnresolvedCompassField :: forall a. (FromJSON a, Monoid a) => FakerSettings -> Key -> Value -> Parser (Unresolved a) parseUnresolvedCompassField FakerSettings settings Key txt Value val = do Object compass <- FakerSettings -> Value -> Parser Object forall a. FromJSON a => FakerSettings -> Value -> Parser a parseCompass FakerSettings settings Value val a field <- Object compass 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 Unresolved a -> Parser (Unresolved a) forall a. a -> Parser 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 a. a -> Unresolved a forall (f :: * -> *) a. Applicative f => a -> f a pure a field $(genParserUnresolved "compass" "direction") $(genProviderUnresolved "compass" "direction") $(genParserUnresolved "compass" "abbreviation") $(genProviderUnresolved "compass" "abbreviation") $(genParserUnresolved "compass" "azimuth") $(genProviderUnresolved "compass" "azimuth") $(genParsers "compass" ["cardinal", "word"]) $(genProviders "compass" ["cardinal", "word"]) $(genParsers "compass" ["cardinal", "abbreviation"]) $(genProviders "compass" ["cardinal", "abbreviation"]) $(genParsers "compass" ["cardinal", "azimuth"]) $(genProviders "compass" ["cardinal", "azimuth"]) $(genParsers "compass" ["ordinal", "word"]) $(genProviders "compass" ["ordinal", "word"]) $(genParsers "compass" ["ordinal", "abbreviation"]) $(genProviders "compass" ["ordinal", "abbreviation"]) $(genParsers "compass" ["ordinal", "azimuth"]) $(genProviders "compass" ["ordinal", "azimuth"]) $(genParsers "compass" ["half-wind", "word"]) $(genProviders "compass" ["half-wind", "word"]) $(genParsers "compass" ["half-wind", "abbreviation"]) $(genProviders "compass" ["half-wind", "abbreviation"]) $(genParsers "compass" ["half-wind", "azimuth"]) $(genProviders "compass" ["half-wind", "azimuth"]) $(genParsers "compass" ["quarter-wind", "word"]) $(genProviders "compass" ["quarter-wind", "word"]) $(genParsers "compass" ["quarter-wind", "abbreviation"]) $(genProviders "compass" ["quarter-wind", "abbreviation"]) $(genParsers "compass" ["quarter-wind", "azimuth"]) $(genProviders "compass" ["quarter-wind", "azimuth"]) resolveCompassText :: (MonadIO m, MonadThrow m) => FakerSettings -> AesonKey -> m Text resolveCompassText :: forall (m :: * -> *). (MonadIO m, MonadThrow m) => FakerSettings -> Key -> m Text resolveCompassText = (FakerSettings -> Key -> m Text) -> FakerSettings -> Key -> m Text forall (m :: * -> *). (MonadIO m, MonadThrow m) => (FakerSettings -> Key -> m Text) -> FakerSettings -> Key -> m Text genericResolver' FakerSettings -> Key -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> Key -> m Text resolveCompassField cardinalProvider :: (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) cardinalProvider :: forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) cardinalProvider FakerSettings settings = do Vector Text cw <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassCardinalWordProvider FakerSettings settings Vector Text ca <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassCardinalAbbreviationProvider FakerSettings settings Vector Text caz <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassCardinalAzimuthProvider FakerSettings settings Vector Text -> m (Vector Text) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Vector Text -> m (Vector Text)) -> Vector Text -> m (Vector Text) forall a b. (a -> b) -> a -> b $ Vector Text cw Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text ca Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text caz ordinalProvider :: (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) ordinalProvider :: forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) ordinalProvider FakerSettings settings = do Vector Text cw <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassOrdinalWordProvider FakerSettings settings Vector Text ca <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassOrdinalAbbreviationProvider FakerSettings settings Vector Text caz <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassOrdinalAzimuthProvider FakerSettings settings Vector Text -> m (Vector Text) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Vector Text -> m (Vector Text)) -> Vector Text -> m (Vector Text) forall a b. (a -> b) -> a -> b $ Vector Text cw Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text ca Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text caz halfWindProvider :: (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) halfWindProvider :: forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) halfWindProvider FakerSettings settings = do Vector Text cw <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassHalfWindWordProvider FakerSettings settings Vector Text ca <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassHalfWindAbbreviationProvider FakerSettings settings Vector Text caz <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassHalfWindAzimuthProvider FakerSettings settings Vector Text -> m (Vector Text) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Vector Text -> m (Vector Text)) -> Vector Text -> m (Vector Text) forall a b. (a -> b) -> a -> b $ Vector Text cw Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text ca Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text caz quarterWindProvider :: (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) quarterWindProvider :: forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) quarterWindProvider FakerSettings settings = do Vector Text cw <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassQuarterWindWordProvider FakerSettings settings Vector Text ca <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassQuarterWindAbbreviationProvider FakerSettings settings Vector Text caz <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassQuarterWindAzimuthProvider FakerSettings settings Vector Text -> m (Vector Text) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Vector Text -> m (Vector Text)) -> Vector Text -> m (Vector Text) forall a b. (a -> b) -> a -> b $ Vector Text cw Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text ca Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text caz abbreviationProvider :: (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) abbreviationProvider :: forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) abbreviationProvider FakerSettings settings = do Vector Text cw <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassCardinalAbbreviationProvider FakerSettings settings Vector Text ca <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassOrdinalAbbreviationProvider FakerSettings settings Vector Text caz <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassHalfWindAbbreviationProvider FakerSettings settings Vector Text qw <- FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassQuarterWindAbbreviationProvider FakerSettings settings Vector Text -> m (Vector Text) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Vector Text -> m (Vector Text)) -> Vector Text -> m (Vector Text) forall a b. (a -> b) -> a -> b $ Vector Text cw Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text ca Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text caz Vector Text -> Vector Text -> Vector Text forall a. Semigroup a => a -> a -> a <> Vector Text qw resolveCompassField :: (MonadThrow m, MonadIO m) => FakerSettings -> AesonKey -> m Text resolveCompassField :: forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> Key -> m Text resolveCompassField FakerSettings settings field :: Key field@Key "cardinal" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) cardinalProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "ordinal" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) ordinalProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "half_wind" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) halfWindProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "quarter_wind" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) quarterWindProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "cardinal_abbreviation" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassCardinalAbbreviationProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "ordinal_abbreviation" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassOrdinalAbbreviationProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "half_wind_abbreviation" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassHalfWindAbbreviationProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "quarter_wind_abbreviation" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassQuarterWindAbbreviationProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "cardinal_azimuth" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassCardinalAzimuthProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "ordinal_azimuth" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassOrdinalAzimuthProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "half_wind_azimuth" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassHalfWindAzimuthProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "quarter_wind_azimuth" = Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Vector Text)) -> FakerSettings -> m Text cachedRandomVec Text "compass" Key field FakerSettings -> m (Vector Text) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Vector Text) compassQuarterWindAzimuthProvider FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "direction" = Text -> Key -> (FakerSettings -> m (Unresolved (Vector Text))) -> (FakerSettings -> Key -> m Text) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Unresolved (Vector Text))) -> (FakerSettings -> Key -> m Text) -> FakerSettings -> m Text cachedRandomUnresolvedVec Text "compass" Key field FakerSettings -> m (Unresolved (Vector Text)) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Unresolved (Vector Text)) compassDirectionProvider FakerSettings -> Key -> m Text forall (m :: * -> *). (MonadIO m, MonadThrow m) => FakerSettings -> Key -> m Text resolveCompassText FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "abbreviation" = Text -> Key -> (FakerSettings -> m (Unresolved (Vector Text))) -> (FakerSettings -> Key -> m Text) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Unresolved (Vector Text))) -> (FakerSettings -> Key -> m Text) -> FakerSettings -> m Text cachedRandomUnresolvedVec Text "compass" Key field FakerSettings -> m (Unresolved (Vector Text)) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Unresolved (Vector Text)) compassAbbreviationProvider FakerSettings -> Key -> m Text forall (m :: * -> *). (MonadIO m, MonadThrow m) => FakerSettings -> Key -> m Text resolveCompassText FakerSettings settings resolveCompassField FakerSettings settings field :: Key field@Key "azimuth" = Text -> Key -> (FakerSettings -> m (Unresolved (Vector Text))) -> (FakerSettings -> Key -> m Text) -> FakerSettings -> m Text forall (m :: * -> *). (MonadThrow m, MonadIO m) => Text -> Key -> (FakerSettings -> m (Unresolved (Vector Text))) -> (FakerSettings -> Key -> m Text) -> FakerSettings -> m Text cachedRandomUnresolvedVec Text "compass" Key field FakerSettings -> m (Unresolved (Vector Text)) forall (m :: * -> *). (MonadThrow m, MonadIO m) => FakerSettings -> m (Unresolved (Vector Text)) compassAzimuthProvider FakerSettings -> Key -> m Text forall (m :: * -> *). (MonadIO m, MonadThrow m) => FakerSettings -> Key -> m Text resolveCompassText FakerSettings settings resolveCompassField FakerSettings settings Key str = FakerException -> m Text forall e a. (HasCallStack, Exception e) => e -> m a forall (m :: * -> *) e a. (MonadThrow m, HasCallStack, Exception e) => e -> m a throwM (FakerException -> m Text) -> FakerException -> m Text forall a b. (a -> b) -> a -> b $ String -> Key -> FakerException InvalidField String "compass" Key str