{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Faker.Provider.Barcode where
import Config
import Control.Monad.Catch
import Control.Monad.IO.Class
import Data.Text (Text)
import Data.Vector (Vector)
import Data.Monoid ((<>))
import Data.Yaml
import Faker
import Faker.Internal
import Faker.Provider.TH
import Language.Haskell.TH
parseBarcode :: FromJSON a => FakerSettings -> Value -> Parser a
parseBarcode :: forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseBarcode 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
barcode <- Object
faker Object -> AesonKey -> Parser a
forall a. FromJSON a => Object -> AesonKey -> Parser a
.: AesonKey
"barcode"
a -> Parser a
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
barcode
parseBarcode 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)
parseBarcodeField ::
(FromJSON a, Monoid a) => FakerSettings -> AesonKey -> Value -> Parser a
parseBarcodeField :: forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> AesonKey -> Value -> Parser a
parseBarcodeField FakerSettings
settings AesonKey
txt Value
val = do
Object
barcode <- FakerSettings -> Value -> Parser Object
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseBarcode FakerSettings
settings Value
val
a
field <- Object
barcode 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
parseBarcodeFields ::
(FromJSON a, Monoid a) => FakerSettings -> [AesonKey] -> Value -> Parser a
parseBarcodeFields :: forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> [AesonKey] -> Value -> Parser a
parseBarcodeFields FakerSettings
settings [AesonKey]
txts Value
val = do
Value
barcode <- FakerSettings -> Value -> Parser Value
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseBarcode FakerSettings
settings Value
val
Value -> [AesonKey] -> Parser a
forall a. FromJSON a => Value -> [AesonKey] -> Parser a
helper Value
barcode [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)
parseUnresolvedBarcodeField ::
(FromJSON a, Monoid a)
=> FakerSettings
-> AesonKey
-> Value
-> Parser (Unresolved a)
parseUnresolvedBarcodeField :: forall a.
(FromJSON a, Monoid a) =>
FakerSettings -> AesonKey -> Value -> Parser (Unresolved a)
parseUnresolvedBarcodeField FakerSettings
settings AesonKey
txt Value
val = do
Object
barcode <- FakerSettings -> Value -> Parser Object
forall a. FromJSON a => FakerSettings -> Value -> Parser a
parseBarcode FakerSettings
settings Value
val
a
field <- Object
barcode 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
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
$(genParserSingleUnresolved "barcode" "ean_8")
$(genProvidersSingleUnresolved "barcode" ["ean_8"])
$(genParserSingleUnresolved "barcode" "ean_13")
$(genProvidersSingleUnresolved "barcode" ["ean_13"])
$(genParserSingleUnresolved "barcode" "upc_a")
$(genProvidersSingleUnresolved "barcode" ["upc_a"])
$(genParserUnresolved "barcode" "upc_e")
$(genProviderUnresolved "barcode" "upc_e")
$(genParserUnresolved "barcode" "composite_symbol")
$(genProviderUnresolved "barcode" "composite_symbol")
$(genParserUnresolved "barcode" "isbn")
$(genProviderUnresolved "barcode" "isbn")
$(genParserSingleUnresolved "barcode" "ismn")
$(genProvidersSingleUnresolved "barcode" ["ismn"])
$(genParserSingleUnresolved "barcode" "issn")
$(genProvidersSingleUnresolved "barcode" ["issn"])
resolveBarcodeText :: (MonadIO m, MonadThrow m) => FakerSettings -> AesonKey -> m Text
resolveBarcodeText :: forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
FakerSettings -> AesonKey -> m Text
resolveBarcodeText = (FakerSettings -> AesonKey -> m Text)
-> FakerSettings -> AesonKey -> m Text
forall (m :: * -> *).
(MonadIO m, MonadThrow m) =>
(FakerSettings -> AesonKey -> m Text)
-> FakerSettings -> AesonKey -> m Text
genericResolver' FakerSettings -> AesonKey -> m Text
forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> AesonKey -> m Text
resolveBarcodeField
resolveBarcodeField :: (MonadThrow m, MonadIO m) => FakerSettings -> AesonKey -> m Text
resolveBarcodeField :: forall (m :: * -> *).
(MonadThrow m, MonadIO m) =>
FakerSettings -> AesonKey -> m Text
resolveBarcodeField FakerSettings
settings AesonKey
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 -> AesonKey -> FakerException
InvalidField String
"barcode" AesonKey
str