{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Types.Identity_VerificationSession 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 {-# SOURCE #-} StripeAPI.Types.GelatoSessionLastError
import {-# SOURCE #-} StripeAPI.Types.GelatoVerificationSessionOptions
import {-# SOURCE #-} StripeAPI.Types.GelatoVerifiedOutputs
import {-# SOURCE #-} StripeAPI.Types.Identity_VerificationReport
import {-# SOURCE #-} StripeAPI.Types.VerificationSessionRedaction
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data Identity'verificationSession = Identity'verificationSession
  { 
    
    
    
    
    Identity'verificationSession -> Maybe Text
identity'verificationSessionClientSecret :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Identity'verificationSession -> Int
identity'verificationSessionCreated :: GHC.Types.Int,
    
    
    
    
    
    Identity'verificationSession -> Text
identity'verificationSessionId :: Data.Text.Internal.Text,
    
    Identity'verificationSession
-> Maybe Identity'verificationSessionLastError'
identity'verificationSessionLastError :: (GHC.Maybe.Maybe Identity'verificationSessionLastError'),
    
    Identity'verificationSession
-> Maybe
     Identity'verificationSessionLastVerificationReport'Variants
identity'verificationSessionLastVerificationReport :: (GHC.Maybe.Maybe Identity'verificationSessionLastVerificationReport'Variants),
    
    Identity'verificationSession -> Bool
identity'verificationSessionLivemode :: GHC.Types.Bool,
    
    Identity'verificationSession -> Object
identity'verificationSessionMetadata :: Data.Aeson.Types.Internal.Object,
    
    Identity'verificationSession -> GelatoVerificationSessionOptions
identity'verificationSessionOptions :: GelatoVerificationSessionOptions,
    
    Identity'verificationSession
-> Maybe Identity'verificationSessionRedaction'
identity'verificationSessionRedaction :: (GHC.Maybe.Maybe Identity'verificationSessionRedaction'),
    
    Identity'verificationSession -> Identity'verificationSessionStatus'
identity'verificationSessionStatus :: Identity'verificationSessionStatus',
    
    Identity'verificationSession -> Identity'verificationSessionType'
identity'verificationSessionType :: Identity'verificationSessionType',
    
    
    
    
    
    Identity'verificationSession -> Maybe Text
identity'verificationSessionUrl :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Identity'verificationSession
-> Maybe Identity'verificationSessionVerifiedOutputs'
identity'verificationSessionVerifiedOutputs :: (GHC.Maybe.Maybe Identity'verificationSessionVerifiedOutputs')
  }
  deriving
    ( Int -> Identity'verificationSession -> ShowS
[Identity'verificationSession] -> ShowS
Identity'verificationSession -> String
(Int -> Identity'verificationSession -> ShowS)
-> (Identity'verificationSession -> String)
-> ([Identity'verificationSession] -> ShowS)
-> Show Identity'verificationSession
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSession] -> ShowS
$cshowList :: [Identity'verificationSession] -> ShowS
show :: Identity'verificationSession -> String
$cshow :: Identity'verificationSession -> String
showsPrec :: Int -> Identity'verificationSession -> ShowS
$cshowsPrec :: Int -> Identity'verificationSession -> ShowS
GHC.Show.Show,
      Identity'verificationSession
-> Identity'verificationSession -> Bool
(Identity'verificationSession
 -> Identity'verificationSession -> Bool)
-> (Identity'verificationSession
    -> Identity'verificationSession -> Bool)
-> Eq Identity'verificationSession
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSession
-> Identity'verificationSession -> Bool
$c/= :: Identity'verificationSession
-> Identity'verificationSession -> Bool
== :: Identity'verificationSession
-> Identity'verificationSession -> Bool
$c== :: Identity'verificationSession
-> Identity'verificationSession -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSession where
  toJSON :: Identity'verificationSession -> Value
toJSON Identity'verificationSession
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"client_secret" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Maybe Text
identity'verificationSessionClientSecret Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"created" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Int
identity'verificationSessionCreated Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Text
identity'verificationSessionId Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"last_error" Text -> Maybe Identity'verificationSessionLastError' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe Identity'verificationSessionLastError'
identity'verificationSessionLastError Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"last_verification_report" Text
-> Maybe
     Identity'verificationSessionLastVerificationReport'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe
     Identity'verificationSessionLastVerificationReport'Variants
identity'verificationSessionLastVerificationReport Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"livemode" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Bool
identity'verificationSessionLivemode Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Object
identity'verificationSessionMetadata Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"options" Text -> GelatoVerificationSessionOptions -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> GelatoVerificationSessionOptions
identity'verificationSessionOptions Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"redaction" Text -> Maybe Identity'verificationSessionRedaction' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe Identity'verificationSessionRedaction'
identity'verificationSessionRedaction Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"status" Text -> Identity'verificationSessionStatus' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Identity'verificationSessionStatus'
identity'verificationSessionStatus Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"type" Text -> Identity'verificationSessionType' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Identity'verificationSessionType'
identity'verificationSessionType Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"url" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Maybe Text
identity'verificationSessionUrl Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"verified_outputs" Text -> Maybe Identity'verificationSessionVerifiedOutputs' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe Identity'verificationSessionVerifiedOutputs'
identity'verificationSessionVerifiedOutputs Identity'verificationSession
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"object" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"identity.verification_session" Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Identity'verificationSession -> Encoding
toEncoding Identity'verificationSession
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"client_secret" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Maybe Text
identity'verificationSessionClientSecret Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"created" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Int
identity'verificationSessionCreated Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Text
identity'verificationSessionId Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"last_error" Text -> Maybe Identity'verificationSessionLastError' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe Identity'verificationSessionLastError'
identity'verificationSessionLastError Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"last_verification_report" Text
-> Maybe
     Identity'verificationSessionLastVerificationReport'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe
     Identity'verificationSessionLastVerificationReport'Variants
identity'verificationSessionLastVerificationReport Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"livemode" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Bool
identity'verificationSessionLivemode Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Object
identity'verificationSessionMetadata Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"options" Text -> GelatoVerificationSessionOptions -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> GelatoVerificationSessionOptions
identity'verificationSessionOptions Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"redaction" Text -> Maybe Identity'verificationSessionRedaction' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe Identity'verificationSessionRedaction'
identity'verificationSessionRedaction Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"status" Text -> Identity'verificationSessionStatus' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Identity'verificationSessionStatus'
identity'verificationSessionStatus Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"type" Text -> Identity'verificationSessionType' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Identity'verificationSessionType'
identity'verificationSessionType Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"url" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession -> Maybe Text
identity'verificationSessionUrl Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"verified_outputs" Text
-> Maybe Identity'verificationSessionVerifiedOutputs' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSession
-> Maybe Identity'verificationSessionVerifiedOutputs'
identity'verificationSessionVerifiedOutputs Identity'verificationSession
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"object" Text -> Value -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"identity.verification_session"))))))))))))))
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSession where
  parseJSON :: Value -> Parser Identity'verificationSession
parseJSON = String
-> (Object -> Parser Identity'verificationSession)
-> Value
-> Parser Identity'verificationSession
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Identity'verificationSession" (\Object
obj -> (((((((((((((Maybe Text
 -> Int
 -> Text
 -> Maybe Identity'verificationSessionLastError'
 -> Maybe
      Identity'verificationSessionLastVerificationReport'Variants
 -> Bool
 -> Object
 -> GelatoVerificationSessionOptions
 -> Maybe Identity'verificationSessionRedaction'
 -> Identity'verificationSessionStatus'
 -> Identity'verificationSessionType'
 -> Maybe Text
 -> Maybe Identity'verificationSessionVerifiedOutputs'
 -> Identity'verificationSession)
-> Parser
     (Maybe Text
      -> Int
      -> Text
      -> Maybe Identity'verificationSessionLastError'
      -> Maybe
           Identity'verificationSessionLastVerificationReport'Variants
      -> Bool
      -> Object
      -> GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Int
-> Text
-> Maybe Identity'verificationSessionLastError'
-> Maybe
     Identity'verificationSessionLastVerificationReport'Variants
-> Bool
-> Object
-> GelatoVerificationSessionOptions
-> Maybe Identity'verificationSessionRedaction'
-> Identity'verificationSessionStatus'
-> Identity'verificationSessionType'
-> Maybe Text
-> Maybe Identity'verificationSessionVerifiedOutputs'
-> Identity'verificationSession
Identity'verificationSession Parser
  (Maybe Text
   -> Int
   -> Text
   -> Maybe Identity'verificationSessionLastError'
   -> Maybe
        Identity'verificationSessionLastVerificationReport'Variants
   -> Bool
   -> Object
   -> GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser (Maybe Text)
-> Parser
     (Int
      -> Text
      -> Maybe Identity'verificationSessionLastError'
      -> Maybe
           Identity'verificationSessionLastVerificationReport'Variants
      -> Bool
      -> Object
      -> GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
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
"client_secret")) Parser
  (Int
   -> Text
   -> Maybe Identity'verificationSessionLastError'
   -> Maybe
        Identity'verificationSessionLastVerificationReport'Variants
   -> Bool
   -> Object
   -> GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser Int
-> Parser
     (Text
      -> Maybe Identity'verificationSessionLastError'
      -> Maybe
           Identity'verificationSessionLastVerificationReport'Variants
      -> Bool
      -> Object
      -> GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"created")) Parser
  (Text
   -> Maybe Identity'verificationSessionLastError'
   -> Maybe
        Identity'verificationSessionLastVerificationReport'Variants
   -> Bool
   -> Object
   -> GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser Text
-> Parser
     (Maybe Identity'verificationSessionLastError'
      -> Maybe
           Identity'verificationSessionLastVerificationReport'Variants
      -> Bool
      -> Object
      -> GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"id")) Parser
  (Maybe Identity'verificationSessionLastError'
   -> Maybe
        Identity'verificationSessionLastVerificationReport'Variants
   -> Bool
   -> Object
   -> GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser (Maybe Identity'verificationSessionLastError')
-> Parser
     (Maybe Identity'verificationSessionLastVerificationReport'Variants
      -> Bool
      -> Object
      -> GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe Identity'verificationSessionLastError')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"last_error")) Parser
  (Maybe Identity'verificationSessionLastVerificationReport'Variants
   -> Bool
   -> Object
   -> GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser
     (Maybe Identity'verificationSessionLastVerificationReport'Variants)
-> Parser
     (Bool
      -> Object
      -> GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe Identity'verificationSessionLastVerificationReport'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"last_verification_report")) Parser
  (Bool
   -> Object
   -> GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser Bool
-> Parser
     (Object
      -> GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"livemode")) Parser
  (Object
   -> GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser Object
-> Parser
     (GelatoVerificationSessionOptions
      -> Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"metadata")) Parser
  (GelatoVerificationSessionOptions
   -> Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser GelatoVerificationSessionOptions
-> Parser
     (Maybe Identity'verificationSessionRedaction'
      -> Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser GelatoVerificationSessionOptions
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"options")) Parser
  (Maybe Identity'verificationSessionRedaction'
   -> Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser (Maybe Identity'verificationSessionRedaction')
-> Parser
     (Identity'verificationSessionStatus'
      -> Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe Identity'verificationSessionRedaction')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"redaction")) Parser
  (Identity'verificationSessionStatus'
   -> Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser Identity'verificationSessionStatus'
-> Parser
     (Identity'verificationSessionType'
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Identity'verificationSessionStatus'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"status")) Parser
  (Identity'verificationSessionType'
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser Identity'verificationSessionType'
-> Parser
     (Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Identity'verificationSessionType'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"type")) Parser
  (Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser (Maybe Text)
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'
      -> Identity'verificationSession)
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
"url")) Parser
  (Maybe Identity'verificationSessionVerifiedOutputs'
   -> Identity'verificationSession)
-> Parser (Maybe Identity'verificationSessionVerifiedOutputs')
-> Parser Identity'verificationSession
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe Identity'verificationSessionVerifiedOutputs')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"verified_outputs"))
mkIdentity'verificationSession ::
  
  GHC.Types.Int ->
  
  Data.Text.Internal.Text ->
  
  GHC.Types.Bool ->
  
  Data.Aeson.Types.Internal.Object ->
  
  GelatoVerificationSessionOptions ->
  
  Identity'verificationSessionStatus' ->
  
  Identity'verificationSessionType' ->
  Identity'verificationSession
mkIdentity'verificationSession :: Int
-> Text
-> Bool
-> Object
-> GelatoVerificationSessionOptions
-> Identity'verificationSessionStatus'
-> Identity'verificationSessionType'
-> Identity'verificationSession
mkIdentity'verificationSession Int
identity'verificationSessionCreated Text
identity'verificationSessionId Bool
identity'verificationSessionLivemode Object
identity'verificationSessionMetadata GelatoVerificationSessionOptions
identity'verificationSessionOptions Identity'verificationSessionStatus'
identity'verificationSessionStatus Identity'verificationSessionType'
identity'verificationSessionType =
  Identity'verificationSession :: Maybe Text
-> Int
-> Text
-> Maybe Identity'verificationSessionLastError'
-> Maybe
     Identity'verificationSessionLastVerificationReport'Variants
-> Bool
-> Object
-> GelatoVerificationSessionOptions
-> Maybe Identity'verificationSessionRedaction'
-> Identity'verificationSessionStatus'
-> Identity'verificationSessionType'
-> Maybe Text
-> Maybe Identity'verificationSessionVerifiedOutputs'
-> Identity'verificationSession
Identity'verificationSession
    { identity'verificationSessionClientSecret :: Maybe Text
identity'verificationSessionClientSecret = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionCreated :: Int
identity'verificationSessionCreated = Int
identity'verificationSessionCreated,
      identity'verificationSessionId :: Text
identity'verificationSessionId = Text
identity'verificationSessionId,
      identity'verificationSessionLastError :: Maybe Identity'verificationSessionLastError'
identity'verificationSessionLastError = Maybe Identity'verificationSessionLastError'
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionLastVerificationReport :: Maybe Identity'verificationSessionLastVerificationReport'Variants
identity'verificationSessionLastVerificationReport = Maybe Identity'verificationSessionLastVerificationReport'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionLivemode :: Bool
identity'verificationSessionLivemode = Bool
identity'verificationSessionLivemode,
      identity'verificationSessionMetadata :: Object
identity'verificationSessionMetadata = Object
identity'verificationSessionMetadata,
      identity'verificationSessionOptions :: GelatoVerificationSessionOptions
identity'verificationSessionOptions = GelatoVerificationSessionOptions
identity'verificationSessionOptions,
      identity'verificationSessionRedaction :: Maybe Identity'verificationSessionRedaction'
identity'verificationSessionRedaction = Maybe Identity'verificationSessionRedaction'
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionStatus :: Identity'verificationSessionStatus'
identity'verificationSessionStatus = Identity'verificationSessionStatus'
identity'verificationSessionStatus,
      identity'verificationSessionType :: Identity'verificationSessionType'
identity'verificationSessionType = Identity'verificationSessionType'
identity'verificationSessionType,
      identity'verificationSessionUrl :: Maybe Text
identity'verificationSessionUrl = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs :: Maybe Identity'verificationSessionVerifiedOutputs'
identity'verificationSessionVerifiedOutputs = Maybe Identity'verificationSessionVerifiedOutputs'
forall a. Maybe a
GHC.Maybe.Nothing
    }
data Identity'verificationSessionLastError' = Identity'verificationSessionLastError'
  { 
    Identity'verificationSessionLastError'
-> Maybe Identity'verificationSessionLastError'Code'
identity'verificationSessionLastError'Code :: (GHC.Maybe.Maybe Identity'verificationSessionLastError'Code'),
    
    
    
    
    
    Identity'verificationSessionLastError' -> Maybe Text
identity'verificationSessionLastError'Reason :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> Identity'verificationSessionLastError' -> ShowS
[Identity'verificationSessionLastError'] -> ShowS
Identity'verificationSessionLastError' -> String
(Int -> Identity'verificationSessionLastError' -> ShowS)
-> (Identity'verificationSessionLastError' -> String)
-> ([Identity'verificationSessionLastError'] -> ShowS)
-> Show Identity'verificationSessionLastError'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionLastError'] -> ShowS
$cshowList :: [Identity'verificationSessionLastError'] -> ShowS
show :: Identity'verificationSessionLastError' -> String
$cshow :: Identity'verificationSessionLastError' -> String
showsPrec :: Int -> Identity'verificationSessionLastError' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionLastError' -> ShowS
GHC.Show.Show,
      Identity'verificationSessionLastError'
-> Identity'verificationSessionLastError' -> Bool
(Identity'verificationSessionLastError'
 -> Identity'verificationSessionLastError' -> Bool)
-> (Identity'verificationSessionLastError'
    -> Identity'verificationSessionLastError' -> Bool)
-> Eq Identity'verificationSessionLastError'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionLastError'
-> Identity'verificationSessionLastError' -> Bool
$c/= :: Identity'verificationSessionLastError'
-> Identity'verificationSessionLastError' -> Bool
== :: Identity'verificationSessionLastError'
-> Identity'verificationSessionLastError' -> Bool
$c== :: Identity'verificationSessionLastError'
-> Identity'verificationSessionLastError' -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionLastError' where
  toJSON :: Identity'verificationSessionLastError' -> Value
toJSON Identity'verificationSessionLastError'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"code" Text -> Maybe Identity'verificationSessionLastError'Code' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionLastError'
-> Maybe Identity'verificationSessionLastError'Code'
identity'verificationSessionLastError'Code Identity'verificationSessionLastError'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"reason" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionLastError' -> Maybe Text
identity'verificationSessionLastError'Reason Identity'verificationSessionLastError'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Identity'verificationSessionLastError' -> Encoding
toEncoding Identity'verificationSessionLastError'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"code" Text -> Maybe Identity'verificationSessionLastError'Code' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionLastError'
-> Maybe Identity'verificationSessionLastError'Code'
identity'verificationSessionLastError'Code Identity'verificationSessionLastError'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"reason" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionLastError' -> Maybe Text
identity'verificationSessionLastError'Reason Identity'verificationSessionLastError'
obj))
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionLastError' where
  parseJSON :: Value -> Parser Identity'verificationSessionLastError'
parseJSON = String
-> (Object -> Parser Identity'verificationSessionLastError')
-> Value
-> Parser Identity'verificationSessionLastError'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Identity'verificationSessionLastError'" (\Object
obj -> ((Maybe Identity'verificationSessionLastError'Code'
 -> Maybe Text -> Identity'verificationSessionLastError')
-> Parser
     (Maybe Identity'verificationSessionLastError'Code'
      -> Maybe Text -> Identity'verificationSessionLastError')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Identity'verificationSessionLastError'Code'
-> Maybe Text -> Identity'verificationSessionLastError'
Identity'verificationSessionLastError' Parser
  (Maybe Identity'verificationSessionLastError'Code'
   -> Maybe Text -> Identity'verificationSessionLastError')
-> Parser (Maybe Identity'verificationSessionLastError'Code')
-> Parser (Maybe Text -> Identity'verificationSessionLastError')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe Identity'verificationSessionLastError'Code')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"code")) Parser (Maybe Text -> Identity'verificationSessionLastError')
-> Parser (Maybe Text)
-> Parser Identity'verificationSessionLastError'
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
"reason"))
mkIdentity'verificationSessionLastError' :: Identity'verificationSessionLastError'
mkIdentity'verificationSessionLastError' :: Identity'verificationSessionLastError'
mkIdentity'verificationSessionLastError' =
  Identity'verificationSessionLastError' :: Maybe Identity'verificationSessionLastError'Code'
-> Maybe Text -> Identity'verificationSessionLastError'
Identity'verificationSessionLastError'
    { identity'verificationSessionLastError'Code :: Maybe Identity'verificationSessionLastError'Code'
identity'verificationSessionLastError'Code = Maybe Identity'verificationSessionLastError'Code'
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionLastError'Reason :: Maybe Text
identity'verificationSessionLastError'Reason = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }
data Identity'verificationSessionLastError'Code'
  = 
    Identity'verificationSessionLastError'Code'Other Data.Aeson.Types.Internal.Value
  | 
    Identity'verificationSessionLastError'Code'Typed Data.Text.Internal.Text
  | 
    Identity'verificationSessionLastError'Code'EnumAbandoned
  | 
    Identity'verificationSessionLastError'Code'EnumConsentDeclined
  | 
    Identity'verificationSessionLastError'Code'EnumCountryNotSupported
  | 
    Identity'verificationSessionLastError'Code'EnumDeviceNotSupported
  | 
    Identity'verificationSessionLastError'Code'EnumDocumentExpired
  | 
    Identity'verificationSessionLastError'Code'EnumDocumentTypeNotSupported
  | 
    Identity'verificationSessionLastError'Code'EnumDocumentUnverifiedOther
  | 
    Identity'verificationSessionLastError'Code'EnumIdNumberInsufficientDocumentData
  | 
    Identity'verificationSessionLastError'Code'EnumIdNumberMismatch
  | 
    Identity'verificationSessionLastError'Code'EnumIdNumberUnverifiedOther
  | 
    Identity'verificationSessionLastError'Code'EnumSelfieDocumentMissingPhoto
  | 
    Identity'verificationSessionLastError'Code'EnumSelfieFaceMismatch
  | 
    Identity'verificationSessionLastError'Code'EnumSelfieManipulated
  | 
    Identity'verificationSessionLastError'Code'EnumSelfieUnverifiedOther
  | 
    Identity'verificationSessionLastError'Code'EnumUnderSupportedAge
  deriving (Int -> Identity'verificationSessionLastError'Code' -> ShowS
[Identity'verificationSessionLastError'Code'] -> ShowS
Identity'verificationSessionLastError'Code' -> String
(Int -> Identity'verificationSessionLastError'Code' -> ShowS)
-> (Identity'verificationSessionLastError'Code' -> String)
-> ([Identity'verificationSessionLastError'Code'] -> ShowS)
-> Show Identity'verificationSessionLastError'Code'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionLastError'Code'] -> ShowS
$cshowList :: [Identity'verificationSessionLastError'Code'] -> ShowS
show :: Identity'verificationSessionLastError'Code' -> String
$cshow :: Identity'verificationSessionLastError'Code' -> String
showsPrec :: Int -> Identity'verificationSessionLastError'Code' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionLastError'Code' -> ShowS
GHC.Show.Show, Identity'verificationSessionLastError'Code'
-> Identity'verificationSessionLastError'Code' -> Bool
(Identity'verificationSessionLastError'Code'
 -> Identity'verificationSessionLastError'Code' -> Bool)
-> (Identity'verificationSessionLastError'Code'
    -> Identity'verificationSessionLastError'Code' -> Bool)
-> Eq Identity'verificationSessionLastError'Code'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionLastError'Code'
-> Identity'verificationSessionLastError'Code' -> Bool
$c/= :: Identity'verificationSessionLastError'Code'
-> Identity'verificationSessionLastError'Code' -> Bool
== :: Identity'verificationSessionLastError'Code'
-> Identity'verificationSessionLastError'Code' -> Bool
$c== :: Identity'verificationSessionLastError'Code'
-> Identity'verificationSessionLastError'Code' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionLastError'Code' where
  toJSON :: Identity'verificationSessionLastError'Code' -> Value
toJSON (Identity'verificationSessionLastError'Code'Other Value
val) = Value
val
  toJSON (Identity'verificationSessionLastError'Code'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumAbandoned) = Value
"abandoned"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumConsentDeclined) = Value
"consent_declined"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumCountryNotSupported) = Value
"country_not_supported"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDeviceNotSupported) = Value
"device_not_supported"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDocumentExpired) = Value
"document_expired"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDocumentTypeNotSupported) = Value
"document_type_not_supported"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDocumentUnverifiedOther) = Value
"document_unverified_other"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumIdNumberInsufficientDocumentData) = Value
"id_number_insufficient_document_data"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumIdNumberMismatch) = Value
"id_number_mismatch"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumIdNumberUnverifiedOther) = Value
"id_number_unverified_other"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieDocumentMissingPhoto) = Value
"selfie_document_missing_photo"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieFaceMismatch) = Value
"selfie_face_mismatch"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieManipulated) = Value
"selfie_manipulated"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieUnverifiedOther) = Value
"selfie_unverified_other"
  toJSON (Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumUnderSupportedAge) = Value
"under_supported_age"
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionLastError'Code' where
  parseJSON :: Value -> Parser Identity'verificationSessionLastError'Code'
parseJSON Value
val =
    Identity'verificationSessionLastError'Code'
-> Parser Identity'verificationSessionLastError'Code'
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
"abandoned" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumAbandoned
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"consent_declined" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumConsentDeclined
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"country_not_supported" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumCountryNotSupported
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"device_not_supported" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDeviceNotSupported
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"document_expired" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDocumentExpired
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"document_type_not_supported" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDocumentTypeNotSupported
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"document_unverified_other" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumDocumentUnverifiedOther
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"id_number_insufficient_document_data" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumIdNumberInsufficientDocumentData
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"id_number_mismatch" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumIdNumberMismatch
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"id_number_unverified_other" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumIdNumberUnverifiedOther
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"selfie_document_missing_photo" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieDocumentMissingPhoto
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"selfie_face_mismatch" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieFaceMismatch
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"selfie_manipulated" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieManipulated
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"selfie_unverified_other" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumSelfieUnverifiedOther
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"under_supported_age" -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'EnumUnderSupportedAge
            | Bool
GHC.Base.otherwise -> Value -> Identity'verificationSessionLastError'Code'
Identity'verificationSessionLastError'Code'Other Value
val
      )
data Identity'verificationSessionLastVerificationReport'Variants
  = Identity'verificationSessionLastVerificationReport'Text Data.Text.Internal.Text
  | Identity'verificationSessionLastVerificationReport'Identity'verificationReport Identity'verificationReport
  deriving (Int
-> Identity'verificationSessionLastVerificationReport'Variants
-> ShowS
[Identity'verificationSessionLastVerificationReport'Variants]
-> ShowS
Identity'verificationSessionLastVerificationReport'Variants
-> String
(Int
 -> Identity'verificationSessionLastVerificationReport'Variants
 -> ShowS)
-> (Identity'verificationSessionLastVerificationReport'Variants
    -> String)
-> ([Identity'verificationSessionLastVerificationReport'Variants]
    -> ShowS)
-> Show Identity'verificationSessionLastVerificationReport'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionLastVerificationReport'Variants]
-> ShowS
$cshowList :: [Identity'verificationSessionLastVerificationReport'Variants]
-> ShowS
show :: Identity'verificationSessionLastVerificationReport'Variants
-> String
$cshow :: Identity'verificationSessionLastVerificationReport'Variants
-> String
showsPrec :: Int
-> Identity'verificationSessionLastVerificationReport'Variants
-> ShowS
$cshowsPrec :: Int
-> Identity'verificationSessionLastVerificationReport'Variants
-> ShowS
GHC.Show.Show, Identity'verificationSessionLastVerificationReport'Variants
-> Identity'verificationSessionLastVerificationReport'Variants
-> Bool
(Identity'verificationSessionLastVerificationReport'Variants
 -> Identity'verificationSessionLastVerificationReport'Variants
 -> Bool)
-> (Identity'verificationSessionLastVerificationReport'Variants
    -> Identity'verificationSessionLastVerificationReport'Variants
    -> Bool)
-> Eq Identity'verificationSessionLastVerificationReport'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionLastVerificationReport'Variants
-> Identity'verificationSessionLastVerificationReport'Variants
-> Bool
$c/= :: Identity'verificationSessionLastVerificationReport'Variants
-> Identity'verificationSessionLastVerificationReport'Variants
-> Bool
== :: Identity'verificationSessionLastVerificationReport'Variants
-> Identity'verificationSessionLastVerificationReport'Variants
-> Bool
$c== :: Identity'verificationSessionLastVerificationReport'Variants
-> Identity'verificationSessionLastVerificationReport'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionLastVerificationReport'Variants where
  toJSON :: Identity'verificationSessionLastVerificationReport'Variants
-> Value
toJSON (Identity'verificationSessionLastVerificationReport'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
  toJSON (Identity'verificationSessionLastVerificationReport'Identity'verificationReport Identity'verificationReport
a) = Identity'verificationReport -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Identity'verificationReport
a
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionLastVerificationReport'Variants where
  parseJSON :: Value
-> Parser
     Identity'verificationSessionLastVerificationReport'Variants
parseJSON Value
val = case (Text -> Identity'verificationSessionLastVerificationReport'Variants
Identity'verificationSessionLastVerificationReport'Text (Text
 -> Identity'verificationSessionLastVerificationReport'Variants)
-> Result Text
-> Result
     Identity'verificationSessionLastVerificationReport'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Text
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result Identity'verificationSessionLastVerificationReport'Variants
-> Result
     Identity'verificationSessionLastVerificationReport'Variants
-> Result
     Identity'verificationSessionLastVerificationReport'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Identity'verificationReport
-> Identity'verificationSessionLastVerificationReport'Variants
Identity'verificationSessionLastVerificationReport'Identity'verificationReport (Identity'verificationReport
 -> Identity'verificationSessionLastVerificationReport'Variants)
-> Result Identity'verificationReport
-> Result
     Identity'verificationSessionLastVerificationReport'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Identity'verificationReport
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result Identity'verificationSessionLastVerificationReport'Variants
-> Result
     Identity'verificationSessionLastVerificationReport'Variants
-> Result
     Identity'verificationSessionLastVerificationReport'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     Identity'verificationSessionLastVerificationReport'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
    Data.Aeson.Types.Internal.Success Identity'verificationSessionLastVerificationReport'Variants
a -> Identity'verificationSessionLastVerificationReport'Variants
-> Parser
     Identity'verificationSessionLastVerificationReport'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Identity'verificationSessionLastVerificationReport'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     Identity'verificationSessionLastVerificationReport'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data Identity'verificationSessionRedaction' = Identity'verificationSessionRedaction'
  { 
    Identity'verificationSessionRedaction'
-> Maybe Identity'verificationSessionRedaction'Status'
identity'verificationSessionRedaction'Status :: (GHC.Maybe.Maybe Identity'verificationSessionRedaction'Status')
  }
  deriving
    ( Int -> Identity'verificationSessionRedaction' -> ShowS
[Identity'verificationSessionRedaction'] -> ShowS
Identity'verificationSessionRedaction' -> String
(Int -> Identity'verificationSessionRedaction' -> ShowS)
-> (Identity'verificationSessionRedaction' -> String)
-> ([Identity'verificationSessionRedaction'] -> ShowS)
-> Show Identity'verificationSessionRedaction'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionRedaction'] -> ShowS
$cshowList :: [Identity'verificationSessionRedaction'] -> ShowS
show :: Identity'verificationSessionRedaction' -> String
$cshow :: Identity'verificationSessionRedaction' -> String
showsPrec :: Int -> Identity'verificationSessionRedaction' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionRedaction' -> ShowS
GHC.Show.Show,
      Identity'verificationSessionRedaction'
-> Identity'verificationSessionRedaction' -> Bool
(Identity'verificationSessionRedaction'
 -> Identity'verificationSessionRedaction' -> Bool)
-> (Identity'verificationSessionRedaction'
    -> Identity'verificationSessionRedaction' -> Bool)
-> Eq Identity'verificationSessionRedaction'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionRedaction'
-> Identity'verificationSessionRedaction' -> Bool
$c/= :: Identity'verificationSessionRedaction'
-> Identity'verificationSessionRedaction' -> Bool
== :: Identity'verificationSessionRedaction'
-> Identity'verificationSessionRedaction' -> Bool
$c== :: Identity'verificationSessionRedaction'
-> Identity'verificationSessionRedaction' -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionRedaction' where
  toJSON :: Identity'verificationSessionRedaction' -> Value
toJSON Identity'verificationSessionRedaction'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"status" Text -> Maybe Identity'verificationSessionRedaction'Status' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionRedaction'
-> Maybe Identity'verificationSessionRedaction'Status'
identity'verificationSessionRedaction'Status Identity'verificationSessionRedaction'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Identity'verificationSessionRedaction' -> Encoding
toEncoding Identity'verificationSessionRedaction'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"status" Text
-> Maybe Identity'verificationSessionRedaction'Status' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionRedaction'
-> Maybe Identity'verificationSessionRedaction'Status'
identity'verificationSessionRedaction'Status Identity'verificationSessionRedaction'
obj)
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionRedaction' where
  parseJSON :: Value -> Parser Identity'verificationSessionRedaction'
parseJSON = String
-> (Object -> Parser Identity'verificationSessionRedaction')
-> Value
-> Parser Identity'verificationSessionRedaction'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Identity'verificationSessionRedaction'" (\Object
obj -> (Maybe Identity'verificationSessionRedaction'Status'
 -> Identity'verificationSessionRedaction')
-> Parser
     (Maybe Identity'verificationSessionRedaction'Status'
      -> Identity'verificationSessionRedaction')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Identity'verificationSessionRedaction'Status'
-> Identity'verificationSessionRedaction'
Identity'verificationSessionRedaction' Parser
  (Maybe Identity'verificationSessionRedaction'Status'
   -> Identity'verificationSessionRedaction')
-> Parser (Maybe Identity'verificationSessionRedaction'Status')
-> Parser Identity'verificationSessionRedaction'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe Identity'verificationSessionRedaction'Status')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"status"))
mkIdentity'verificationSessionRedaction' :: Identity'verificationSessionRedaction'
mkIdentity'verificationSessionRedaction' :: Identity'verificationSessionRedaction'
mkIdentity'verificationSessionRedaction' = Identity'verificationSessionRedaction' :: Maybe Identity'verificationSessionRedaction'Status'
-> Identity'verificationSessionRedaction'
Identity'verificationSessionRedaction' {identity'verificationSessionRedaction'Status :: Maybe Identity'verificationSessionRedaction'Status'
identity'verificationSessionRedaction'Status = Maybe Identity'verificationSessionRedaction'Status'
forall a. Maybe a
GHC.Maybe.Nothing}
data Identity'verificationSessionRedaction'Status'
  = 
    Identity'verificationSessionRedaction'Status'Other Data.Aeson.Types.Internal.Value
  | 
    Identity'verificationSessionRedaction'Status'Typed Data.Text.Internal.Text
  | 
    Identity'verificationSessionRedaction'Status'EnumProcessing
  | 
    Identity'verificationSessionRedaction'Status'EnumRedacted
  deriving (Int -> Identity'verificationSessionRedaction'Status' -> ShowS
[Identity'verificationSessionRedaction'Status'] -> ShowS
Identity'verificationSessionRedaction'Status' -> String
(Int -> Identity'verificationSessionRedaction'Status' -> ShowS)
-> (Identity'verificationSessionRedaction'Status' -> String)
-> ([Identity'verificationSessionRedaction'Status'] -> ShowS)
-> Show Identity'verificationSessionRedaction'Status'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionRedaction'Status'] -> ShowS
$cshowList :: [Identity'verificationSessionRedaction'Status'] -> ShowS
show :: Identity'verificationSessionRedaction'Status' -> String
$cshow :: Identity'verificationSessionRedaction'Status' -> String
showsPrec :: Int -> Identity'verificationSessionRedaction'Status' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionRedaction'Status' -> ShowS
GHC.Show.Show, Identity'verificationSessionRedaction'Status'
-> Identity'verificationSessionRedaction'Status' -> Bool
(Identity'verificationSessionRedaction'Status'
 -> Identity'verificationSessionRedaction'Status' -> Bool)
-> (Identity'verificationSessionRedaction'Status'
    -> Identity'verificationSessionRedaction'Status' -> Bool)
-> Eq Identity'verificationSessionRedaction'Status'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionRedaction'Status'
-> Identity'verificationSessionRedaction'Status' -> Bool
$c/= :: Identity'verificationSessionRedaction'Status'
-> Identity'verificationSessionRedaction'Status' -> Bool
== :: Identity'verificationSessionRedaction'Status'
-> Identity'verificationSessionRedaction'Status' -> Bool
$c== :: Identity'verificationSessionRedaction'Status'
-> Identity'verificationSessionRedaction'Status' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionRedaction'Status' where
  toJSON :: Identity'verificationSessionRedaction'Status' -> Value
toJSON (Identity'verificationSessionRedaction'Status'Other Value
val) = Value
val
  toJSON (Identity'verificationSessionRedaction'Status'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (Identity'verificationSessionRedaction'Status'
Identity'verificationSessionRedaction'Status'EnumProcessing) = Value
"processing"
  toJSON (Identity'verificationSessionRedaction'Status'
Identity'verificationSessionRedaction'Status'EnumRedacted) = Value
"redacted"
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionRedaction'Status' where
  parseJSON :: Value -> Parser Identity'verificationSessionRedaction'Status'
parseJSON Value
val =
    Identity'verificationSessionRedaction'Status'
-> Parser Identity'verificationSessionRedaction'Status'
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
"processing" -> Identity'verificationSessionRedaction'Status'
Identity'verificationSessionRedaction'Status'EnumProcessing
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"redacted" -> Identity'verificationSessionRedaction'Status'
Identity'verificationSessionRedaction'Status'EnumRedacted
            | Bool
GHC.Base.otherwise -> Value -> Identity'verificationSessionRedaction'Status'
Identity'verificationSessionRedaction'Status'Other Value
val
      )
data Identity'verificationSessionStatus'
  = 
    Identity'verificationSessionStatus'Other Data.Aeson.Types.Internal.Value
  | 
    Identity'verificationSessionStatus'Typed Data.Text.Internal.Text
  | 
    Identity'verificationSessionStatus'EnumCanceled
  | 
    Identity'verificationSessionStatus'EnumProcessing
  | 
    Identity'verificationSessionStatus'EnumRequiresInput
  | 
    Identity'verificationSessionStatus'EnumVerified
  deriving (Int -> Identity'verificationSessionStatus' -> ShowS
[Identity'verificationSessionStatus'] -> ShowS
Identity'verificationSessionStatus' -> String
(Int -> Identity'verificationSessionStatus' -> ShowS)
-> (Identity'verificationSessionStatus' -> String)
-> ([Identity'verificationSessionStatus'] -> ShowS)
-> Show Identity'verificationSessionStatus'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionStatus'] -> ShowS
$cshowList :: [Identity'verificationSessionStatus'] -> ShowS
show :: Identity'verificationSessionStatus' -> String
$cshow :: Identity'verificationSessionStatus' -> String
showsPrec :: Int -> Identity'verificationSessionStatus' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionStatus' -> ShowS
GHC.Show.Show, Identity'verificationSessionStatus'
-> Identity'verificationSessionStatus' -> Bool
(Identity'verificationSessionStatus'
 -> Identity'verificationSessionStatus' -> Bool)
-> (Identity'verificationSessionStatus'
    -> Identity'verificationSessionStatus' -> Bool)
-> Eq Identity'verificationSessionStatus'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionStatus'
-> Identity'verificationSessionStatus' -> Bool
$c/= :: Identity'verificationSessionStatus'
-> Identity'verificationSessionStatus' -> Bool
== :: Identity'verificationSessionStatus'
-> Identity'verificationSessionStatus' -> Bool
$c== :: Identity'verificationSessionStatus'
-> Identity'verificationSessionStatus' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionStatus' where
  toJSON :: Identity'verificationSessionStatus' -> Value
toJSON (Identity'verificationSessionStatus'Other Value
val) = Value
val
  toJSON (Identity'verificationSessionStatus'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumCanceled) = Value
"canceled"
  toJSON (Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumProcessing) = Value
"processing"
  toJSON (Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumRequiresInput) = Value
"requires_input"
  toJSON (Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumVerified) = Value
"verified"
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionStatus' where
  parseJSON :: Value -> Parser Identity'verificationSessionStatus'
parseJSON Value
val =
    Identity'verificationSessionStatus'
-> Parser Identity'verificationSessionStatus'
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
"canceled" -> Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumCanceled
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"processing" -> Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumProcessing
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"requires_input" -> Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumRequiresInput
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"verified" -> Identity'verificationSessionStatus'
Identity'verificationSessionStatus'EnumVerified
            | Bool
GHC.Base.otherwise -> Value -> Identity'verificationSessionStatus'
Identity'verificationSessionStatus'Other Value
val
      )
data Identity'verificationSessionType'
  = 
    Identity'verificationSessionType'Other Data.Aeson.Types.Internal.Value
  | 
    Identity'verificationSessionType'Typed Data.Text.Internal.Text
  | 
    Identity'verificationSessionType'EnumDocument
  | 
    Identity'verificationSessionType'EnumIdNumber
  deriving (Int -> Identity'verificationSessionType' -> ShowS
[Identity'verificationSessionType'] -> ShowS
Identity'verificationSessionType' -> String
(Int -> Identity'verificationSessionType' -> ShowS)
-> (Identity'verificationSessionType' -> String)
-> ([Identity'verificationSessionType'] -> ShowS)
-> Show Identity'verificationSessionType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionType'] -> ShowS
$cshowList :: [Identity'verificationSessionType'] -> ShowS
show :: Identity'verificationSessionType' -> String
$cshow :: Identity'verificationSessionType' -> String
showsPrec :: Int -> Identity'verificationSessionType' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionType' -> ShowS
GHC.Show.Show, Identity'verificationSessionType'
-> Identity'verificationSessionType' -> Bool
(Identity'verificationSessionType'
 -> Identity'verificationSessionType' -> Bool)
-> (Identity'verificationSessionType'
    -> Identity'verificationSessionType' -> Bool)
-> Eq Identity'verificationSessionType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionType'
-> Identity'verificationSessionType' -> Bool
$c/= :: Identity'verificationSessionType'
-> Identity'verificationSessionType' -> Bool
== :: Identity'verificationSessionType'
-> Identity'verificationSessionType' -> Bool
$c== :: Identity'verificationSessionType'
-> Identity'verificationSessionType' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionType' where
  toJSON :: Identity'verificationSessionType' -> Value
toJSON (Identity'verificationSessionType'Other Value
val) = Value
val
  toJSON (Identity'verificationSessionType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (Identity'verificationSessionType'
Identity'verificationSessionType'EnumDocument) = Value
"document"
  toJSON (Identity'verificationSessionType'
Identity'verificationSessionType'EnumIdNumber) = Value
"id_number"
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionType' where
  parseJSON :: Value -> Parser Identity'verificationSessionType'
parseJSON Value
val =
    Identity'verificationSessionType'
-> Parser Identity'verificationSessionType'
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
"document" -> Identity'verificationSessionType'
Identity'verificationSessionType'EnumDocument
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"id_number" -> Identity'verificationSessionType'
Identity'verificationSessionType'EnumIdNumber
            | Bool
GHC.Base.otherwise -> Value -> Identity'verificationSessionType'
Identity'verificationSessionType'Other Value
val
      )
data Identity'verificationSessionVerifiedOutputs' = Identity'verificationSessionVerifiedOutputs'
  { 
    Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'Address'
identity'verificationSessionVerifiedOutputs'Address :: (GHC.Maybe.Maybe Identity'verificationSessionVerifiedOutputs'Address'),
    
    Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
identity'verificationSessionVerifiedOutputs'Dob :: (GHC.Maybe.Maybe Identity'verificationSessionVerifiedOutputs'Dob'),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'FirstName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'IdNumber :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
identity'verificationSessionVerifiedOutputs'IdNumberType :: (GHC.Maybe.Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'LastName :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> Identity'verificationSessionVerifiedOutputs' -> ShowS
[Identity'verificationSessionVerifiedOutputs'] -> ShowS
Identity'verificationSessionVerifiedOutputs' -> String
(Int -> Identity'verificationSessionVerifiedOutputs' -> ShowS)
-> (Identity'verificationSessionVerifiedOutputs' -> String)
-> ([Identity'verificationSessionVerifiedOutputs'] -> ShowS)
-> Show Identity'verificationSessionVerifiedOutputs'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionVerifiedOutputs'] -> ShowS
$cshowList :: [Identity'verificationSessionVerifiedOutputs'] -> ShowS
show :: Identity'verificationSessionVerifiedOutputs' -> String
$cshow :: Identity'verificationSessionVerifiedOutputs' -> String
showsPrec :: Int -> Identity'verificationSessionVerifiedOutputs' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionVerifiedOutputs' -> ShowS
GHC.Show.Show,
      Identity'verificationSessionVerifiedOutputs'
-> Identity'verificationSessionVerifiedOutputs' -> Bool
(Identity'verificationSessionVerifiedOutputs'
 -> Identity'verificationSessionVerifiedOutputs' -> Bool)
-> (Identity'verificationSessionVerifiedOutputs'
    -> Identity'verificationSessionVerifiedOutputs' -> Bool)
-> Eq Identity'verificationSessionVerifiedOutputs'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionVerifiedOutputs'
-> Identity'verificationSessionVerifiedOutputs' -> Bool
$c/= :: Identity'verificationSessionVerifiedOutputs'
-> Identity'verificationSessionVerifiedOutputs' -> Bool
== :: Identity'verificationSessionVerifiedOutputs'
-> Identity'verificationSessionVerifiedOutputs' -> Bool
$c== :: Identity'verificationSessionVerifiedOutputs'
-> Identity'verificationSessionVerifiedOutputs' -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionVerifiedOutputs' where
  toJSON :: Identity'verificationSessionVerifiedOutputs' -> Value
toJSON Identity'verificationSessionVerifiedOutputs'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"address" Text
-> Maybe Identity'verificationSessionVerifiedOutputs'Address'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'Address'
identity'verificationSessionVerifiedOutputs'Address Identity'verificationSessionVerifiedOutputs'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"dob" Text
-> Maybe Identity'verificationSessionVerifiedOutputs'Dob' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
identity'verificationSessionVerifiedOutputs'Dob Identity'verificationSessionVerifiedOutputs'
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..= Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'FirstName Identity'verificationSessionVerifiedOutputs'
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..= Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'IdNumber Identity'verificationSessionVerifiedOutputs'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id_number_type" Text
-> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
identity'verificationSessionVerifiedOutputs'IdNumberType Identity'verificationSessionVerifiedOutputs'
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..= Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'LastName Identity'verificationSessionVerifiedOutputs'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Identity'verificationSessionVerifiedOutputs' -> Encoding
toEncoding Identity'verificationSessionVerifiedOutputs'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"address" Text
-> Maybe Identity'verificationSessionVerifiedOutputs'Address'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'Address'
identity'verificationSessionVerifiedOutputs'Address Identity'verificationSessionVerifiedOutputs'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"dob" Text
-> Maybe Identity'verificationSessionVerifiedOutputs'Dob' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
identity'verificationSessionVerifiedOutputs'Dob Identity'verificationSessionVerifiedOutputs'
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..= Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'FirstName Identity'verificationSessionVerifiedOutputs'
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..= Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'IdNumber Identity'verificationSessionVerifiedOutputs'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id_number_type" Text
-> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Identity'verificationSessionVerifiedOutputs'
-> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
identity'verificationSessionVerifiedOutputs'IdNumberType Identity'verificationSessionVerifiedOutputs'
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..= Identity'verificationSessionVerifiedOutputs' -> Maybe Text
identity'verificationSessionVerifiedOutputs'LastName Identity'verificationSessionVerifiedOutputs'
obj))))))
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionVerifiedOutputs' where
  parseJSON :: Value -> Parser Identity'verificationSessionVerifiedOutputs'
parseJSON = String
-> (Object -> Parser Identity'verificationSessionVerifiedOutputs')
-> Value
-> Parser Identity'verificationSessionVerifiedOutputs'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Identity'verificationSessionVerifiedOutputs'" (\Object
obj -> ((((((Maybe Identity'verificationSessionVerifiedOutputs'Address'
 -> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
 -> Maybe Text
 -> Maybe Text
 -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
 -> Maybe Text
 -> Identity'verificationSessionVerifiedOutputs')
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'Address'
      -> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Identity'verificationSessionVerifiedOutputs'Address'
-> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
-> Maybe Text
-> Maybe Text
-> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Maybe Text
-> Identity'verificationSessionVerifiedOutputs'
Identity'verificationSessionVerifiedOutputs' Parser
  (Maybe Identity'verificationSessionVerifiedOutputs'Address'
   -> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
   -> Maybe Text
   -> Identity'verificationSessionVerifiedOutputs')
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'Address')
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'Dob'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'Address')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address")) Parser
  (Maybe Identity'verificationSessionVerifiedOutputs'Dob'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
   -> Maybe Text
   -> Identity'verificationSessionVerifiedOutputs')
-> Parser (Maybe Identity'verificationSessionVerifiedOutputs'Dob')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe Identity'verificationSessionVerifiedOutputs'Dob')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"dob")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
   -> Maybe Text
   -> Identity'verificationSessionVerifiedOutputs')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs')
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 Identity'verificationSessionVerifiedOutputs'IdNumberType'
   -> Maybe Text
   -> Identity'verificationSessionVerifiedOutputs')
-> Parser (Maybe Text)
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
      -> Maybe Text -> Identity'verificationSessionVerifiedOutputs')
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 Identity'verificationSessionVerifiedOutputs'IdNumberType'
   -> Maybe Text -> Identity'verificationSessionVerifiedOutputs')
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType')
-> Parser
     (Maybe Text -> Identity'verificationSessionVerifiedOutputs')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"id_number_type")) Parser (Maybe Text -> Identity'verificationSessionVerifiedOutputs')
-> Parser (Maybe Text)
-> Parser Identity'verificationSessionVerifiedOutputs'
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"))
mkIdentity'verificationSessionVerifiedOutputs' :: Identity'verificationSessionVerifiedOutputs'
mkIdentity'verificationSessionVerifiedOutputs' :: Identity'verificationSessionVerifiedOutputs'
mkIdentity'verificationSessionVerifiedOutputs' =
  Identity'verificationSessionVerifiedOutputs' :: Maybe Identity'verificationSessionVerifiedOutputs'Address'
-> Maybe Identity'verificationSessionVerifiedOutputs'Dob'
-> Maybe Text
-> Maybe Text
-> Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Maybe Text
-> Identity'verificationSessionVerifiedOutputs'
Identity'verificationSessionVerifiedOutputs'
    { identity'verificationSessionVerifiedOutputs'Address :: Maybe Identity'verificationSessionVerifiedOutputs'Address'
identity'verificationSessionVerifiedOutputs'Address = Maybe Identity'verificationSessionVerifiedOutputs'Address'
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Dob :: Maybe Identity'verificationSessionVerifiedOutputs'Dob'
identity'verificationSessionVerifiedOutputs'Dob = Maybe Identity'verificationSessionVerifiedOutputs'Dob'
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'FirstName :: Maybe Text
identity'verificationSessionVerifiedOutputs'FirstName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'IdNumber :: Maybe Text
identity'verificationSessionVerifiedOutputs'IdNumber = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'IdNumberType :: Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
identity'verificationSessionVerifiedOutputs'IdNumberType = Maybe Identity'verificationSessionVerifiedOutputs'IdNumberType'
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'LastName :: Maybe Text
identity'verificationSessionVerifiedOutputs'LastName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }
data Identity'verificationSessionVerifiedOutputs'Address' = Identity'verificationSessionVerifiedOutputs'Address'
  { 
    
    
    
    
    Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'City :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Country :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'PostalCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'State :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> Identity'verificationSessionVerifiedOutputs'Address' -> ShowS
[Identity'verificationSessionVerifiedOutputs'Address'] -> ShowS
Identity'verificationSessionVerifiedOutputs'Address' -> String
(Int
 -> Identity'verificationSessionVerifiedOutputs'Address' -> ShowS)
-> (Identity'verificationSessionVerifiedOutputs'Address' -> String)
-> ([Identity'verificationSessionVerifiedOutputs'Address']
    -> ShowS)
-> Show Identity'verificationSessionVerifiedOutputs'Address'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionVerifiedOutputs'Address'] -> ShowS
$cshowList :: [Identity'verificationSessionVerifiedOutputs'Address'] -> ShowS
show :: Identity'verificationSessionVerifiedOutputs'Address' -> String
$cshow :: Identity'verificationSessionVerifiedOutputs'Address' -> String
showsPrec :: Int
-> Identity'verificationSessionVerifiedOutputs'Address' -> ShowS
$cshowsPrec :: Int
-> Identity'verificationSessionVerifiedOutputs'Address' -> ShowS
GHC.Show.Show,
      Identity'verificationSessionVerifiedOutputs'Address'
-> Identity'verificationSessionVerifiedOutputs'Address' -> Bool
(Identity'verificationSessionVerifiedOutputs'Address'
 -> Identity'verificationSessionVerifiedOutputs'Address' -> Bool)
-> (Identity'verificationSessionVerifiedOutputs'Address'
    -> Identity'verificationSessionVerifiedOutputs'Address' -> Bool)
-> Eq Identity'verificationSessionVerifiedOutputs'Address'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionVerifiedOutputs'Address'
-> Identity'verificationSessionVerifiedOutputs'Address' -> Bool
$c/= :: Identity'verificationSessionVerifiedOutputs'Address'
-> Identity'verificationSessionVerifiedOutputs'Address' -> Bool
== :: Identity'verificationSessionVerifiedOutputs'Address'
-> Identity'verificationSessionVerifiedOutputs'Address' -> Bool
$c== :: Identity'verificationSessionVerifiedOutputs'Address'
-> Identity'verificationSessionVerifiedOutputs'Address' -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionVerifiedOutputs'Address' where
  toJSON :: Identity'verificationSessionVerifiedOutputs'Address' -> Value
toJSON Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'City Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Country Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line1 Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line2 Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'PostalCode Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'State Identity'verificationSessionVerifiedOutputs'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Identity'verificationSessionVerifiedOutputs'Address' -> Encoding
toEncoding Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'City Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Country Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line1 Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line2 Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'PostalCode Identity'verificationSessionVerifiedOutputs'Address'
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..= Identity'verificationSessionVerifiedOutputs'Address' -> Maybe Text
identity'verificationSessionVerifiedOutputs'Address'State Identity'verificationSessionVerifiedOutputs'Address'
obj))))))
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionVerifiedOutputs'Address' where
  parseJSON :: Value
-> Parser Identity'verificationSessionVerifiedOutputs'Address'
parseJSON = String
-> (Object
    -> Parser Identity'verificationSessionVerifiedOutputs'Address')
-> Value
-> Parser Identity'verificationSessionVerifiedOutputs'Address'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Identity'verificationSessionVerifiedOutputs'Address'" (\Object
obj -> ((((((Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Identity'verificationSessionVerifiedOutputs'Address')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs'Address')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Identity'verificationSessionVerifiedOutputs'Address'
Identity'verificationSessionVerifiedOutputs'Address' Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Identity'verificationSessionVerifiedOutputs'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs'Address')
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
   -> Identity'verificationSessionVerifiedOutputs'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs'Address')
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
   -> Identity'verificationSessionVerifiedOutputs'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs'Address')
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
   -> Identity'verificationSessionVerifiedOutputs'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Identity'verificationSessionVerifiedOutputs'Address')
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
   -> Identity'verificationSessionVerifiedOutputs'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Identity'verificationSessionVerifiedOutputs'Address')
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
   -> Identity'verificationSessionVerifiedOutputs'Address')
-> Parser (Maybe Text)
-> Parser Identity'verificationSessionVerifiedOutputs'Address'
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"))
mkIdentity'verificationSessionVerifiedOutputs'Address' :: Identity'verificationSessionVerifiedOutputs'Address'
mkIdentity'verificationSessionVerifiedOutputs'Address' :: Identity'verificationSessionVerifiedOutputs'Address'
mkIdentity'verificationSessionVerifiedOutputs'Address' =
  Identity'verificationSessionVerifiedOutputs'Address' :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Identity'verificationSessionVerifiedOutputs'Address'
Identity'verificationSessionVerifiedOutputs'Address'
    { identity'verificationSessionVerifiedOutputs'Address'City :: Maybe Text
identity'verificationSessionVerifiedOutputs'Address'City = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Address'Country :: Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Country = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Address'Line1 :: Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Address'Line2 :: Maybe Text
identity'verificationSessionVerifiedOutputs'Address'Line2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Address'PostalCode :: Maybe Text
identity'verificationSessionVerifiedOutputs'Address'PostalCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Address'State :: Maybe Text
identity'verificationSessionVerifiedOutputs'Address'State = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }
data Identity'verificationSessionVerifiedOutputs'Dob' = Identity'verificationSessionVerifiedOutputs'Dob'
  { 
    Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Day :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Month :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Year :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int -> Identity'verificationSessionVerifiedOutputs'Dob' -> ShowS
[Identity'verificationSessionVerifiedOutputs'Dob'] -> ShowS
Identity'verificationSessionVerifiedOutputs'Dob' -> String
(Int -> Identity'verificationSessionVerifiedOutputs'Dob' -> ShowS)
-> (Identity'verificationSessionVerifiedOutputs'Dob' -> String)
-> ([Identity'verificationSessionVerifiedOutputs'Dob'] -> ShowS)
-> Show Identity'verificationSessionVerifiedOutputs'Dob'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionVerifiedOutputs'Dob'] -> ShowS
$cshowList :: [Identity'verificationSessionVerifiedOutputs'Dob'] -> ShowS
show :: Identity'verificationSessionVerifiedOutputs'Dob' -> String
$cshow :: Identity'verificationSessionVerifiedOutputs'Dob' -> String
showsPrec :: Int -> Identity'verificationSessionVerifiedOutputs'Dob' -> ShowS
$cshowsPrec :: Int -> Identity'verificationSessionVerifiedOutputs'Dob' -> ShowS
GHC.Show.Show,
      Identity'verificationSessionVerifiedOutputs'Dob'
-> Identity'verificationSessionVerifiedOutputs'Dob' -> Bool
(Identity'verificationSessionVerifiedOutputs'Dob'
 -> Identity'verificationSessionVerifiedOutputs'Dob' -> Bool)
-> (Identity'verificationSessionVerifiedOutputs'Dob'
    -> Identity'verificationSessionVerifiedOutputs'Dob' -> Bool)
-> Eq Identity'verificationSessionVerifiedOutputs'Dob'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionVerifiedOutputs'Dob'
-> Identity'verificationSessionVerifiedOutputs'Dob' -> Bool
$c/= :: Identity'verificationSessionVerifiedOutputs'Dob'
-> Identity'verificationSessionVerifiedOutputs'Dob' -> Bool
== :: Identity'verificationSessionVerifiedOutputs'Dob'
-> Identity'verificationSessionVerifiedOutputs'Dob' -> Bool
$c== :: Identity'verificationSessionVerifiedOutputs'Dob'
-> Identity'verificationSessionVerifiedOutputs'Dob' -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionVerifiedOutputs'Dob' where
  toJSON :: Identity'verificationSessionVerifiedOutputs'Dob' -> Value
toJSON Identity'verificationSessionVerifiedOutputs'Dob'
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..= Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Day Identity'verificationSessionVerifiedOutputs'Dob'
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..= Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Month Identity'verificationSessionVerifiedOutputs'Dob'
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..= Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Year Identity'verificationSessionVerifiedOutputs'Dob'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Identity'verificationSessionVerifiedOutputs'Dob' -> Encoding
toEncoding Identity'verificationSessionVerifiedOutputs'Dob'
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..= Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Day Identity'verificationSessionVerifiedOutputs'Dob'
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..= Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Month Identity'verificationSessionVerifiedOutputs'Dob'
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..= Identity'verificationSessionVerifiedOutputs'Dob' -> Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Year Identity'verificationSessionVerifiedOutputs'Dob'
obj)))
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionVerifiedOutputs'Dob' where
  parseJSON :: Value -> Parser Identity'verificationSessionVerifiedOutputs'Dob'
parseJSON = String
-> (Object
    -> Parser Identity'verificationSessionVerifiedOutputs'Dob')
-> Value
-> Parser Identity'verificationSessionVerifiedOutputs'Dob'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Identity'verificationSessionVerifiedOutputs'Dob'" (\Object
obj -> (((Maybe Int
 -> Maybe Int
 -> Maybe Int
 -> Identity'verificationSessionVerifiedOutputs'Dob')
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Int
      -> Identity'verificationSessionVerifiedOutputs'Dob')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe Int
-> Maybe Int
-> Identity'verificationSessionVerifiedOutputs'Dob'
Identity'verificationSessionVerifiedOutputs'Dob' Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Int
   -> Identity'verificationSessionVerifiedOutputs'Dob')
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Int -> Identity'verificationSessionVerifiedOutputs'Dob')
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 -> Identity'verificationSessionVerifiedOutputs'Dob')
-> Parser (Maybe Int)
-> Parser
     (Maybe Int -> Identity'verificationSessionVerifiedOutputs'Dob')
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 -> Identity'verificationSessionVerifiedOutputs'Dob')
-> Parser (Maybe Int)
-> Parser Identity'verificationSessionVerifiedOutputs'Dob'
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"))
mkIdentity'verificationSessionVerifiedOutputs'Dob' :: Identity'verificationSessionVerifiedOutputs'Dob'
mkIdentity'verificationSessionVerifiedOutputs'Dob' :: Identity'verificationSessionVerifiedOutputs'Dob'
mkIdentity'verificationSessionVerifiedOutputs'Dob' =
  Identity'verificationSessionVerifiedOutputs'Dob' :: Maybe Int
-> Maybe Int
-> Maybe Int
-> Identity'verificationSessionVerifiedOutputs'Dob'
Identity'verificationSessionVerifiedOutputs'Dob'
    { identity'verificationSessionVerifiedOutputs'Dob'Day :: Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Day = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Dob'Month :: Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Month = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      identity'verificationSessionVerifiedOutputs'Dob'Year :: Maybe Int
identity'verificationSessionVerifiedOutputs'Dob'Year = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }
data Identity'verificationSessionVerifiedOutputs'IdNumberType'
  = 
    Identity'verificationSessionVerifiedOutputs'IdNumberType'Other Data.Aeson.Types.Internal.Value
  | 
    Identity'verificationSessionVerifiedOutputs'IdNumberType'Typed Data.Text.Internal.Text
  | 
    Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumBrCpf
  | 
    Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumSgNric
  | 
    Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumUsSsn
  deriving (Int
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> ShowS
[Identity'verificationSessionVerifiedOutputs'IdNumberType']
-> ShowS
Identity'verificationSessionVerifiedOutputs'IdNumberType' -> String
(Int
 -> Identity'verificationSessionVerifiedOutputs'IdNumberType'
 -> ShowS)
-> (Identity'verificationSessionVerifiedOutputs'IdNumberType'
    -> String)
-> ([Identity'verificationSessionVerifiedOutputs'IdNumberType']
    -> ShowS)
-> Show Identity'verificationSessionVerifiedOutputs'IdNumberType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity'verificationSessionVerifiedOutputs'IdNumberType']
-> ShowS
$cshowList :: [Identity'verificationSessionVerifiedOutputs'IdNumberType']
-> ShowS
show :: Identity'verificationSessionVerifiedOutputs'IdNumberType' -> String
$cshow :: Identity'verificationSessionVerifiedOutputs'IdNumberType' -> String
showsPrec :: Int
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> ShowS
$cshowsPrec :: Int
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> ShowS
GHC.Show.Show, Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Bool
(Identity'verificationSessionVerifiedOutputs'IdNumberType'
 -> Identity'verificationSessionVerifiedOutputs'IdNumberType'
 -> Bool)
-> (Identity'verificationSessionVerifiedOutputs'IdNumberType'
    -> Identity'verificationSessionVerifiedOutputs'IdNumberType'
    -> Bool)
-> Eq Identity'verificationSessionVerifiedOutputs'IdNumberType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Bool
$c/= :: Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Bool
== :: Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Bool
$c== :: Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON Identity'verificationSessionVerifiedOutputs'IdNumberType' where
  toJSON :: Identity'verificationSessionVerifiedOutputs'IdNumberType' -> Value
toJSON (Identity'verificationSessionVerifiedOutputs'IdNumberType'Other Value
val) = Value
val
  toJSON (Identity'verificationSessionVerifiedOutputs'IdNumberType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (Identity'verificationSessionVerifiedOutputs'IdNumberType'
Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumBrCpf) = Value
"br_cpf"
  toJSON (Identity'verificationSessionVerifiedOutputs'IdNumberType'
Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumSgNric) = Value
"sg_nric"
  toJSON (Identity'verificationSessionVerifiedOutputs'IdNumberType'
Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumUsSsn) = Value
"us_ssn"
instance Data.Aeson.Types.FromJSON.FromJSON Identity'verificationSessionVerifiedOutputs'IdNumberType' where
  parseJSON :: Value
-> Parser Identity'verificationSessionVerifiedOutputs'IdNumberType'
parseJSON Value
val =
    Identity'verificationSessionVerifiedOutputs'IdNumberType'
-> Parser Identity'verificationSessionVerifiedOutputs'IdNumberType'
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" -> Identity'verificationSessionVerifiedOutputs'IdNumberType'
Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumBrCpf
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sg_nric" -> Identity'verificationSessionVerifiedOutputs'IdNumberType'
Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumSgNric
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"us_ssn" -> Identity'verificationSessionVerifiedOutputs'IdNumberType'
Identity'verificationSessionVerifiedOutputs'IdNumberType'EnumUsSsn
            | Bool
GHC.Base.otherwise -> Value -> Identity'verificationSessionVerifiedOutputs'IdNumberType'
Identity'verificationSessionVerifiedOutputs'IdNumberType'Other Value
val
      )