{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Types.GelatoVerifiedOutputs where
import qualified Control.Monad.Fail
import qualified Data.Aeson
import qualified Data.Aeson as Data.Aeson.Encoding.Internal
import qualified Data.Aeson as Data.Aeson.Types
import qualified Data.Aeson as Data.Aeson.Types.FromJSON
import qualified Data.Aeson as Data.Aeson.Types.Internal
import qualified Data.Aeson as Data.Aeson.Types.ToJSON
import qualified Data.ByteString.Char8
import qualified Data.ByteString.Char8 as Data.ByteString.Internal
import qualified Data.Functor
import qualified Data.Scientific
import qualified Data.Text
import qualified Data.Text.Internal
import qualified Data.Time.Calendar as Data.Time.Calendar.Days
import qualified Data.Time.LocalTime as Data.Time.LocalTime.Internal.ZonedTime
import qualified GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified StripeAPI.Common
import StripeAPI.TypeAlias
import {-# SOURCE #-} StripeAPI.Types.Address
import {-# SOURCE #-} StripeAPI.Types.GelatoDataVerifiedOutputsDate
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data GelatoVerifiedOutputs = GelatoVerifiedOutputs
{
GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsAddress'
gelatoVerifiedOutputsAddress :: (GHC.Maybe.Maybe GelatoVerifiedOutputsAddress'),
GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsDob'
gelatoVerifiedOutputsDob :: (GHC.Maybe.Maybe GelatoVerifiedOutputsDob'),
GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsFirstName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsIdNumber :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsIdNumberType'
gelatoVerifiedOutputsIdNumberType :: (GHC.Maybe.Maybe GelatoVerifiedOutputsIdNumberType'),
GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsLastName :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> GelatoVerifiedOutputs -> ShowS
[GelatoVerifiedOutputs] -> ShowS
GelatoVerifiedOutputs -> String
(Int -> GelatoVerifiedOutputs -> ShowS)
-> (GelatoVerifiedOutputs -> String)
-> ([GelatoVerifiedOutputs] -> ShowS)
-> Show GelatoVerifiedOutputs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GelatoVerifiedOutputs] -> ShowS
$cshowList :: [GelatoVerifiedOutputs] -> ShowS
show :: GelatoVerifiedOutputs -> String
$cshow :: GelatoVerifiedOutputs -> String
showsPrec :: Int -> GelatoVerifiedOutputs -> ShowS
$cshowsPrec :: Int -> GelatoVerifiedOutputs -> ShowS
GHC.Show.Show,
GelatoVerifiedOutputs -> GelatoVerifiedOutputs -> Bool
(GelatoVerifiedOutputs -> GelatoVerifiedOutputs -> Bool)
-> (GelatoVerifiedOutputs -> GelatoVerifiedOutputs -> Bool)
-> Eq GelatoVerifiedOutputs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GelatoVerifiedOutputs -> GelatoVerifiedOutputs -> Bool
$c/= :: GelatoVerifiedOutputs -> GelatoVerifiedOutputs -> Bool
== :: GelatoVerifiedOutputs -> GelatoVerifiedOutputs -> Bool
$c== :: GelatoVerifiedOutputs -> GelatoVerifiedOutputs -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON GelatoVerifiedOutputs where
toJSON :: GelatoVerifiedOutputs -> Value
toJSON GelatoVerifiedOutputs
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"address" Text -> Maybe GelatoVerifiedOutputsAddress' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsAddress'
gelatoVerifiedOutputsAddress GelatoVerifiedOutputs
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"dob" Text -> Maybe GelatoVerifiedOutputsDob' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsDob'
gelatoVerifiedOutputsDob GelatoVerifiedOutputs
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"first_name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsFirstName GelatoVerifiedOutputs
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id_number" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsIdNumber GelatoVerifiedOutputs
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id_number_type" Text -> Maybe GelatoVerifiedOutputsIdNumberType' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsIdNumberType'
gelatoVerifiedOutputsIdNumberType GelatoVerifiedOutputs
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"last_name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsLastName GelatoVerifiedOutputs
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: GelatoVerifiedOutputs -> Encoding
toEncoding GelatoVerifiedOutputs
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"address" Text -> Maybe GelatoVerifiedOutputsAddress' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsAddress'
gelatoVerifiedOutputsAddress GelatoVerifiedOutputs
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"dob" Text -> Maybe GelatoVerifiedOutputsDob' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsDob'
gelatoVerifiedOutputsDob GelatoVerifiedOutputs
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"first_name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsFirstName GelatoVerifiedOutputs
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id_number" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsIdNumber GelatoVerifiedOutputs
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id_number_type" Text -> Maybe GelatoVerifiedOutputsIdNumberType' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe GelatoVerifiedOutputsIdNumberType'
gelatoVerifiedOutputsIdNumberType GelatoVerifiedOutputs
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"last_name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputs -> Maybe Text
gelatoVerifiedOutputsLastName GelatoVerifiedOutputs
obj))))))
instance Data.Aeson.Types.FromJSON.FromJSON GelatoVerifiedOutputs where
parseJSON :: Value -> Parser GelatoVerifiedOutputs
parseJSON = String
-> (Object -> Parser GelatoVerifiedOutputs)
-> Value
-> Parser GelatoVerifiedOutputs
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GelatoVerifiedOutputs" (\Object
obj -> ((((((Maybe GelatoVerifiedOutputsAddress'
-> Maybe GelatoVerifiedOutputsDob'
-> Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
-> Parser
(Maybe GelatoVerifiedOutputsAddress'
-> Maybe GelatoVerifiedOutputsDob'
-> Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe GelatoVerifiedOutputsAddress'
-> Maybe GelatoVerifiedOutputsDob'
-> Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs
GelatoVerifiedOutputs Parser
(Maybe GelatoVerifiedOutputsAddress'
-> Maybe GelatoVerifiedOutputsDob'
-> Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
-> Parser (Maybe GelatoVerifiedOutputsAddress')
-> Parser
(Maybe GelatoVerifiedOutputsDob'
-> Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe GelatoVerifiedOutputsAddress')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address")) Parser
(Maybe GelatoVerifiedOutputsDob'
-> Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
-> Parser (Maybe GelatoVerifiedOutputsDob')
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe GelatoVerifiedOutputsDob')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"dob")) Parser
(Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"first_name")) Parser
(Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs)
-> Parser (Maybe Text)
-> Parser
(Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text -> GelatoVerifiedOutputs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"id_number")) Parser
(Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text -> GelatoVerifiedOutputs)
-> Parser (Maybe GelatoVerifiedOutputsIdNumberType')
-> Parser (Maybe Text -> GelatoVerifiedOutputs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe GelatoVerifiedOutputsIdNumberType')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"id_number_type")) Parser (Maybe Text -> GelatoVerifiedOutputs)
-> Parser (Maybe Text) -> Parser GelatoVerifiedOutputs
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"last_name"))
mkGelatoVerifiedOutputs :: GelatoVerifiedOutputs
mkGelatoVerifiedOutputs :: GelatoVerifiedOutputs
mkGelatoVerifiedOutputs =
GelatoVerifiedOutputs :: Maybe GelatoVerifiedOutputsAddress'
-> Maybe GelatoVerifiedOutputsDob'
-> Maybe Text
-> Maybe Text
-> Maybe GelatoVerifiedOutputsIdNumberType'
-> Maybe Text
-> GelatoVerifiedOutputs
GelatoVerifiedOutputs
{ gelatoVerifiedOutputsAddress :: Maybe GelatoVerifiedOutputsAddress'
gelatoVerifiedOutputsAddress = Maybe GelatoVerifiedOutputsAddress'
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsDob :: Maybe GelatoVerifiedOutputsDob'
gelatoVerifiedOutputsDob = Maybe GelatoVerifiedOutputsDob'
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsFirstName :: Maybe Text
gelatoVerifiedOutputsFirstName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsIdNumber :: Maybe Text
gelatoVerifiedOutputsIdNumber = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsIdNumberType :: Maybe GelatoVerifiedOutputsIdNumberType'
gelatoVerifiedOutputsIdNumberType = Maybe GelatoVerifiedOutputsIdNumberType'
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsLastName :: Maybe Text
gelatoVerifiedOutputsLastName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}
data GelatoVerifiedOutputsAddress' = GelatoVerifiedOutputsAddress'
{
GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'City :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Country :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Line1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Line2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'PostalCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'State :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> GelatoVerifiedOutputsAddress' -> ShowS
[GelatoVerifiedOutputsAddress'] -> ShowS
GelatoVerifiedOutputsAddress' -> String
(Int -> GelatoVerifiedOutputsAddress' -> ShowS)
-> (GelatoVerifiedOutputsAddress' -> String)
-> ([GelatoVerifiedOutputsAddress'] -> ShowS)
-> Show GelatoVerifiedOutputsAddress'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GelatoVerifiedOutputsAddress'] -> ShowS
$cshowList :: [GelatoVerifiedOutputsAddress'] -> ShowS
show :: GelatoVerifiedOutputsAddress' -> String
$cshow :: GelatoVerifiedOutputsAddress' -> String
showsPrec :: Int -> GelatoVerifiedOutputsAddress' -> ShowS
$cshowsPrec :: Int -> GelatoVerifiedOutputsAddress' -> ShowS
GHC.Show.Show,
GelatoVerifiedOutputsAddress'
-> GelatoVerifiedOutputsAddress' -> Bool
(GelatoVerifiedOutputsAddress'
-> GelatoVerifiedOutputsAddress' -> Bool)
-> (GelatoVerifiedOutputsAddress'
-> GelatoVerifiedOutputsAddress' -> Bool)
-> Eq GelatoVerifiedOutputsAddress'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GelatoVerifiedOutputsAddress'
-> GelatoVerifiedOutputsAddress' -> Bool
$c/= :: GelatoVerifiedOutputsAddress'
-> GelatoVerifiedOutputsAddress' -> Bool
== :: GelatoVerifiedOutputsAddress'
-> GelatoVerifiedOutputsAddress' -> Bool
$c== :: GelatoVerifiedOutputsAddress'
-> GelatoVerifiedOutputsAddress' -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON GelatoVerifiedOutputsAddress' where
toJSON :: GelatoVerifiedOutputsAddress' -> Value
toJSON GelatoVerifiedOutputsAddress'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'City GelatoVerifiedOutputsAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Country GelatoVerifiedOutputsAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line1" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Line1 GelatoVerifiedOutputsAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line2" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Line2 GelatoVerifiedOutputsAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"postal_code" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'PostalCode GelatoVerifiedOutputsAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"state" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'State GelatoVerifiedOutputsAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: GelatoVerifiedOutputsAddress' -> Encoding
toEncoding GelatoVerifiedOutputsAddress'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'City GelatoVerifiedOutputsAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Country GelatoVerifiedOutputsAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line1" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Line1 GelatoVerifiedOutputsAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line2" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'Line2 GelatoVerifiedOutputsAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"postal_code" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'PostalCode GelatoVerifiedOutputsAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"state" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsAddress' -> Maybe Text
gelatoVerifiedOutputsAddress'State GelatoVerifiedOutputsAddress'
obj))))))
instance Data.Aeson.Types.FromJSON.FromJSON GelatoVerifiedOutputsAddress' where
parseJSON :: Value -> Parser GelatoVerifiedOutputsAddress'
parseJSON = String
-> (Object -> Parser GelatoVerifiedOutputsAddress')
-> Value
-> Parser GelatoVerifiedOutputsAddress'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GelatoVerifiedOutputsAddress'" (\Object
obj -> ((((((Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress')
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress'
GelatoVerifiedOutputsAddress' Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress')
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"city")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress')
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"country")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress')
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text -> Maybe Text -> GelatoVerifiedOutputsAddress')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"line1")) Parser
(Maybe Text
-> Maybe Text -> Maybe Text -> GelatoVerifiedOutputsAddress')
-> Parser (Maybe Text)
-> Parser
(Maybe Text -> Maybe Text -> GelatoVerifiedOutputsAddress')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"line2")) Parser (Maybe Text -> Maybe Text -> GelatoVerifiedOutputsAddress')
-> Parser (Maybe Text)
-> Parser (Maybe Text -> GelatoVerifiedOutputsAddress')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"postal_code")) Parser (Maybe Text -> GelatoVerifiedOutputsAddress')
-> Parser (Maybe Text) -> Parser GelatoVerifiedOutputsAddress'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"state"))
mkGelatoVerifiedOutputsAddress' :: GelatoVerifiedOutputsAddress'
mkGelatoVerifiedOutputsAddress' :: GelatoVerifiedOutputsAddress'
mkGelatoVerifiedOutputsAddress' =
GelatoVerifiedOutputsAddress' :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> GelatoVerifiedOutputsAddress'
GelatoVerifiedOutputsAddress'
{ gelatoVerifiedOutputsAddress'City :: Maybe Text
gelatoVerifiedOutputsAddress'City = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsAddress'Country :: Maybe Text
gelatoVerifiedOutputsAddress'Country = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsAddress'Line1 :: Maybe Text
gelatoVerifiedOutputsAddress'Line1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsAddress'Line2 :: Maybe Text
gelatoVerifiedOutputsAddress'Line2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsAddress'PostalCode :: Maybe Text
gelatoVerifiedOutputsAddress'PostalCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsAddress'State :: Maybe Text
gelatoVerifiedOutputsAddress'State = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}
data GelatoVerifiedOutputsDob' = GelatoVerifiedOutputsDob'
{
GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Day :: (GHC.Maybe.Maybe GHC.Types.Int),
GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Month :: (GHC.Maybe.Maybe GHC.Types.Int),
GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Year :: (GHC.Maybe.Maybe GHC.Types.Int)
}
deriving
( Int -> GelatoVerifiedOutputsDob' -> ShowS
[GelatoVerifiedOutputsDob'] -> ShowS
GelatoVerifiedOutputsDob' -> String
(Int -> GelatoVerifiedOutputsDob' -> ShowS)
-> (GelatoVerifiedOutputsDob' -> String)
-> ([GelatoVerifiedOutputsDob'] -> ShowS)
-> Show GelatoVerifiedOutputsDob'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GelatoVerifiedOutputsDob'] -> ShowS
$cshowList :: [GelatoVerifiedOutputsDob'] -> ShowS
show :: GelatoVerifiedOutputsDob' -> String
$cshow :: GelatoVerifiedOutputsDob' -> String
showsPrec :: Int -> GelatoVerifiedOutputsDob' -> ShowS
$cshowsPrec :: Int -> GelatoVerifiedOutputsDob' -> ShowS
GHC.Show.Show,
GelatoVerifiedOutputsDob' -> GelatoVerifiedOutputsDob' -> Bool
(GelatoVerifiedOutputsDob' -> GelatoVerifiedOutputsDob' -> Bool)
-> (GelatoVerifiedOutputsDob' -> GelatoVerifiedOutputsDob' -> Bool)
-> Eq GelatoVerifiedOutputsDob'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GelatoVerifiedOutputsDob' -> GelatoVerifiedOutputsDob' -> Bool
$c/= :: GelatoVerifiedOutputsDob' -> GelatoVerifiedOutputsDob' -> Bool
== :: GelatoVerifiedOutputsDob' -> GelatoVerifiedOutputsDob' -> Bool
$c== :: GelatoVerifiedOutputsDob' -> GelatoVerifiedOutputsDob' -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON GelatoVerifiedOutputsDob' where
toJSON :: GelatoVerifiedOutputsDob' -> Value
toJSON GelatoVerifiedOutputsDob'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"day" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Day GelatoVerifiedOutputsDob'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"month" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Month GelatoVerifiedOutputsDob'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"year" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Year GelatoVerifiedOutputsDob'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: GelatoVerifiedOutputsDob' -> Encoding
toEncoding GelatoVerifiedOutputsDob'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"day" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Day GelatoVerifiedOutputsDob'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"month" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Month GelatoVerifiedOutputsDob'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"year" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= GelatoVerifiedOutputsDob' -> Maybe Int
gelatoVerifiedOutputsDob'Year GelatoVerifiedOutputsDob'
obj)))
instance Data.Aeson.Types.FromJSON.FromJSON GelatoVerifiedOutputsDob' where
parseJSON :: Value -> Parser GelatoVerifiedOutputsDob'
parseJSON = String
-> (Object -> Parser GelatoVerifiedOutputsDob')
-> Value
-> Parser GelatoVerifiedOutputsDob'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GelatoVerifiedOutputsDob'" (\Object
obj -> (((Maybe Int -> Maybe Int -> Maybe Int -> GelatoVerifiedOutputsDob')
-> Parser
(Maybe Int -> Maybe Int -> Maybe Int -> GelatoVerifiedOutputsDob')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int -> Maybe Int -> Maybe Int -> GelatoVerifiedOutputsDob'
GelatoVerifiedOutputsDob' Parser
(Maybe Int -> Maybe Int -> Maybe Int -> GelatoVerifiedOutputsDob')
-> Parser (Maybe Int)
-> Parser (Maybe Int -> Maybe Int -> GelatoVerifiedOutputsDob')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"day")) Parser (Maybe Int -> Maybe Int -> GelatoVerifiedOutputsDob')
-> Parser (Maybe Int)
-> Parser (Maybe Int -> GelatoVerifiedOutputsDob')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"month")) Parser (Maybe Int -> GelatoVerifiedOutputsDob')
-> Parser (Maybe Int) -> Parser GelatoVerifiedOutputsDob'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"year"))
mkGelatoVerifiedOutputsDob' :: GelatoVerifiedOutputsDob'
mkGelatoVerifiedOutputsDob' :: GelatoVerifiedOutputsDob'
mkGelatoVerifiedOutputsDob' =
GelatoVerifiedOutputsDob' :: Maybe Int -> Maybe Int -> Maybe Int -> GelatoVerifiedOutputsDob'
GelatoVerifiedOutputsDob'
{ gelatoVerifiedOutputsDob'Day :: Maybe Int
gelatoVerifiedOutputsDob'Day = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsDob'Month :: Maybe Int
gelatoVerifiedOutputsDob'Month = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
gelatoVerifiedOutputsDob'Year :: Maybe Int
gelatoVerifiedOutputsDob'Year = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
}
data GelatoVerifiedOutputsIdNumberType'
=
GelatoVerifiedOutputsIdNumberType'Other Data.Aeson.Types.Internal.Value
|
GelatoVerifiedOutputsIdNumberType'Typed Data.Text.Internal.Text
|
GelatoVerifiedOutputsIdNumberType'EnumBrCpf
|
GelatoVerifiedOutputsIdNumberType'EnumSgNric
|
GelatoVerifiedOutputsIdNumberType'EnumUsSsn
deriving (Int -> GelatoVerifiedOutputsIdNumberType' -> ShowS
[GelatoVerifiedOutputsIdNumberType'] -> ShowS
GelatoVerifiedOutputsIdNumberType' -> String
(Int -> GelatoVerifiedOutputsIdNumberType' -> ShowS)
-> (GelatoVerifiedOutputsIdNumberType' -> String)
-> ([GelatoVerifiedOutputsIdNumberType'] -> ShowS)
-> Show GelatoVerifiedOutputsIdNumberType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GelatoVerifiedOutputsIdNumberType'] -> ShowS
$cshowList :: [GelatoVerifiedOutputsIdNumberType'] -> ShowS
show :: GelatoVerifiedOutputsIdNumberType' -> String
$cshow :: GelatoVerifiedOutputsIdNumberType' -> String
showsPrec :: Int -> GelatoVerifiedOutputsIdNumberType' -> ShowS
$cshowsPrec :: Int -> GelatoVerifiedOutputsIdNumberType' -> ShowS
GHC.Show.Show, GelatoVerifiedOutputsIdNumberType'
-> GelatoVerifiedOutputsIdNumberType' -> Bool
(GelatoVerifiedOutputsIdNumberType'
-> GelatoVerifiedOutputsIdNumberType' -> Bool)
-> (GelatoVerifiedOutputsIdNumberType'
-> GelatoVerifiedOutputsIdNumberType' -> Bool)
-> Eq GelatoVerifiedOutputsIdNumberType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GelatoVerifiedOutputsIdNumberType'
-> GelatoVerifiedOutputsIdNumberType' -> Bool
$c/= :: GelatoVerifiedOutputsIdNumberType'
-> GelatoVerifiedOutputsIdNumberType' -> Bool
== :: GelatoVerifiedOutputsIdNumberType'
-> GelatoVerifiedOutputsIdNumberType' -> Bool
$c== :: GelatoVerifiedOutputsIdNumberType'
-> GelatoVerifiedOutputsIdNumberType' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON GelatoVerifiedOutputsIdNumberType' where
toJSON :: GelatoVerifiedOutputsIdNumberType' -> Value
toJSON (GelatoVerifiedOutputsIdNumberType'Other Value
val) = Value
val
toJSON (GelatoVerifiedOutputsIdNumberType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (GelatoVerifiedOutputsIdNumberType'
GelatoVerifiedOutputsIdNumberType'EnumBrCpf) = Value
"br_cpf"
toJSON (GelatoVerifiedOutputsIdNumberType'
GelatoVerifiedOutputsIdNumberType'EnumSgNric) = Value
"sg_nric"
toJSON (GelatoVerifiedOutputsIdNumberType'
GelatoVerifiedOutputsIdNumberType'EnumUsSsn) = Value
"us_ssn"
instance Data.Aeson.Types.FromJSON.FromJSON GelatoVerifiedOutputsIdNumberType' where
parseJSON :: Value -> Parser GelatoVerifiedOutputsIdNumberType'
parseJSON Value
val =
GelatoVerifiedOutputsIdNumberType'
-> Parser GelatoVerifiedOutputsIdNumberType'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
( if
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"br_cpf" -> GelatoVerifiedOutputsIdNumberType'
GelatoVerifiedOutputsIdNumberType'EnumBrCpf
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sg_nric" -> GelatoVerifiedOutputsIdNumberType'
GelatoVerifiedOutputsIdNumberType'EnumSgNric
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"us_ssn" -> GelatoVerifiedOutputsIdNumberType'
GelatoVerifiedOutputsIdNumberType'EnumUsSsn
| Bool
GHC.Base.otherwise -> Value -> GelatoVerifiedOutputsIdNumberType'
GelatoVerifiedOutputsIdNumberType'Other Value
val
)