{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.BillingInfo 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
import qualified Data.ByteString as Data.ByteString.Internal
import qualified Data.Foldable
import qualified Data.Functor
import qualified Data.Maybe
import qualified Data.Scientific
import qualified Data.Text
import qualified Data.Text as 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 RecurlyClient.Common
import RecurlyClient.TypeAlias
import {-# SOURCE #-} RecurlyClient.Types.Address
import {-# SOURCE #-} RecurlyClient.Types.PaymentGatewayReferences
import {-# SOURCE #-} RecurlyClient.Types.PaymentMethod
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data BillingInfo = BillingInfo
{ BillingInfo -> Maybe Text
billingInfoAccount_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, BillingInfo -> Maybe Address
billingInfoAddress :: (GHC.Maybe.Maybe Address)
, BillingInfo -> Maybe Bool
billingInfoBackup_payment_method :: (GHC.Maybe.Maybe GHC.Types.Bool)
, BillingInfo -> Maybe Text
billingInfoCompany :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, BillingInfo -> Maybe JsonDateTime
billingInfoCreated_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, BillingInfo -> Maybe Text
billingInfoFirst_name :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, BillingInfo -> Maybe BillingInfoFraud
billingInfoFraud :: (GHC.Maybe.Maybe BillingInfoFraud)
, BillingInfo -> Maybe Text
billingInfoId :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, BillingInfo -> Maybe Text
billingInfoLast_name :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, BillingInfo -> Maybe Text
billingInfoObject :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, BillingInfo -> Maybe [PaymentGatewayReferences]
billingInfoPayment_gateway_references :: (GHC.Maybe.Maybe [PaymentGatewayReferences])
, BillingInfo -> Maybe PaymentMethod
billingInfoPayment_method :: (GHC.Maybe.Maybe PaymentMethod)
, BillingInfo -> Maybe Bool
billingInfoPrimary_payment_method :: (GHC.Maybe.Maybe GHC.Types.Bool)
, BillingInfo -> Maybe JsonDateTime
billingInfoUpdated_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, BillingInfo -> Maybe BillingInfoUpdated_by
billingInfoUpdated_by :: (GHC.Maybe.Maybe BillingInfoUpdated_by)
, BillingInfo -> Maybe Bool
billingInfoValid :: (GHC.Maybe.Maybe GHC.Types.Bool)
, BillingInfo -> Maybe Text
billingInfoVat_number :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> BillingInfo -> ShowS
[BillingInfo] -> ShowS
BillingInfo -> String
(Int -> BillingInfo -> ShowS)
-> (BillingInfo -> String)
-> ([BillingInfo] -> ShowS)
-> Show BillingInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BillingInfo -> ShowS
showsPrec :: Int -> BillingInfo -> ShowS
$cshow :: BillingInfo -> String
show :: BillingInfo -> String
$cshowList :: [BillingInfo] -> ShowS
showList :: [BillingInfo] -> ShowS
GHC.Show.Show
, BillingInfo -> BillingInfo -> Bool
(BillingInfo -> BillingInfo -> Bool)
-> (BillingInfo -> BillingInfo -> Bool) -> Eq BillingInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BillingInfo -> BillingInfo -> Bool
== :: BillingInfo -> BillingInfo -> Bool
$c/= :: BillingInfo -> BillingInfo -> Bool
/= :: BillingInfo -> BillingInfo -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON BillingInfo where
toJSON :: BillingInfo -> Value
toJSON BillingInfo
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"account_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoAccount_id BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Address -> [Pair]) -> Maybe Address -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Address -> Pair) -> Address -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"address" Key -> Address -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Address
billingInfoAddress BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"backup_payment_method" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Bool
billingInfoBackup_payment_method BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"company" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoCompany BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"created_at" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe JsonDateTime
billingInfoCreated_at BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"first_name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoFirst_name BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (BillingInfoFraud -> [Pair]) -> Maybe BillingInfoFraud -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (BillingInfoFraud -> Pair) -> BillingInfoFraud -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"fraud" Key -> BillingInfoFraud -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe BillingInfoFraud
billingInfoFraud BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoId BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"last_name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoLast_name BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"object" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoObject BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([PaymentGatewayReferences] -> [Pair])
-> Maybe [PaymentGatewayReferences]
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> ([PaymentGatewayReferences] -> Pair)
-> [PaymentGatewayReferences]
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"payment_gateway_references" Key -> [PaymentGatewayReferences] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe [PaymentGatewayReferences]
billingInfoPayment_gateway_references BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (PaymentMethod -> [Pair]) -> Maybe PaymentMethod -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (PaymentMethod -> Pair) -> PaymentMethod -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"payment_method" Key -> PaymentMethod -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe PaymentMethod
billingInfoPayment_method BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"primary_payment_method" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Bool
billingInfoPrimary_payment_method BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"updated_at" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe JsonDateTime
billingInfoUpdated_at BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (BillingInfoUpdated_by -> [Pair])
-> Maybe BillingInfoUpdated_by
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (BillingInfoUpdated_by -> Pair)
-> BillingInfoUpdated_by
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"updated_by" Key -> BillingInfoUpdated_by -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe BillingInfoUpdated_by
billingInfoUpdated_by BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"valid" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Bool
billingInfoValid BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"vat_number" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoVat_number BillingInfo
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: BillingInfo -> Encoding
toEncoding BillingInfo
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ([Series] -> Series
forall a. Monoid a => [a] -> a
GHC.Base.mconcat ([[Series]] -> [Series]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"account_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoAccount_id BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Address -> [Series]) -> Maybe Address -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Address -> Series) -> Address -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"address" Key -> Address -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Address
billingInfoAddress BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"backup_payment_method" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Bool
billingInfoBackup_payment_method BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"company" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoCompany BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"created_at" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe JsonDateTime
billingInfoCreated_at BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"first_name" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoFirst_name BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (BillingInfoFraud -> [Series])
-> Maybe BillingInfoFraud
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (BillingInfoFraud -> Series) -> BillingInfoFraud -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"fraud" Key -> BillingInfoFraud -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe BillingInfoFraud
billingInfoFraud BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoId BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"last_name" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoLast_name BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"object" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoObject BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([PaymentGatewayReferences] -> [Series])
-> Maybe [PaymentGatewayReferences]
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> ([PaymentGatewayReferences] -> Series)
-> [PaymentGatewayReferences]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"payment_gateway_references" Key -> [PaymentGatewayReferences] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe [PaymentGatewayReferences]
billingInfoPayment_gateway_references BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (PaymentMethod -> [Series]) -> Maybe PaymentMethod -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (PaymentMethod -> Series) -> PaymentMethod -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"payment_method" Key -> PaymentMethod -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe PaymentMethod
billingInfoPayment_method BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"primary_payment_method" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Bool
billingInfoPrimary_payment_method BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"updated_at" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe JsonDateTime
billingInfoUpdated_at BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (BillingInfoUpdated_by -> [Series])
-> Maybe BillingInfoUpdated_by
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (BillingInfoUpdated_by -> Series)
-> BillingInfoUpdated_by
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"updated_by" Key -> BillingInfoUpdated_by -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe BillingInfoUpdated_by
billingInfoUpdated_by BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"valid" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Bool
billingInfoValid BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"vat_number" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfo -> Maybe Text
billingInfoVat_number BillingInfo
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON BillingInfo where
parseJSON :: Value -> Parser BillingInfo
parseJSON = String
-> (Object -> Parser BillingInfo) -> Value -> Parser BillingInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"BillingInfo" (\Object
obj -> (((((((((((((((((Maybe Text
-> Maybe Address
-> Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser
(Maybe Text
-> Maybe Address
-> Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Address
-> Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo
BillingInfo Parser
(Maybe Text
-> Maybe Address
-> Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe Address
-> Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"account_id")) Parser
(Maybe Address
-> Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Address)
-> Parser
(Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Address)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"address")) Parser
(Maybe Bool
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Bool)
-> Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"backup_payment_method")) Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"company")) Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"created_at")) Parser
(Maybe Text
-> Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"first_name")) Parser
(Maybe BillingInfoFraud
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe BillingInfoFraud)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe BillingInfoFraud)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"fraud")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"id")) Parser
(Maybe Text
-> Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"last_name")) Parser
(Maybe Text
-> Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"object")) Parser
(Maybe [PaymentGatewayReferences]
-> Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe [PaymentGatewayReferences])
-> Parser
(Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe [PaymentGatewayReferences])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"payment_gateway_references")) Parser
(Maybe PaymentMethod
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe PaymentMethod)
-> Parser
(Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe PaymentMethod)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"payment_method")) Parser
(Maybe Bool
-> Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe Bool)
-> Parser
(Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"primary_payment_method")) Parser
(Maybe JsonDateTime
-> Maybe BillingInfoUpdated_by
-> Maybe Bool
-> Maybe Text
-> BillingInfo)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe BillingInfoUpdated_by
-> Maybe Bool -> Maybe Text -> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"updated_at")) Parser
(Maybe BillingInfoUpdated_by
-> Maybe Bool -> Maybe Text -> BillingInfo)
-> Parser (Maybe BillingInfoUpdated_by)
-> Parser (Maybe Bool -> Maybe Text -> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe BillingInfoUpdated_by)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"updated_by")) Parser (Maybe Bool -> Maybe Text -> BillingInfo)
-> Parser (Maybe Bool) -> Parser (Maybe Text -> BillingInfo)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"valid")) Parser (Maybe Text -> BillingInfo)
-> Parser (Maybe Text) -> Parser BillingInfo
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"vat_number"))
mkBillingInfo :: BillingInfo
mkBillingInfo :: BillingInfo
mkBillingInfo =
BillingInfo
{ billingInfoAccount_id :: Maybe Text
billingInfoAccount_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoAddress :: Maybe Address
billingInfoAddress = Maybe Address
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoBackup_payment_method :: Maybe Bool
billingInfoBackup_payment_method = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoCompany :: Maybe Text
billingInfoCompany = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoCreated_at :: Maybe JsonDateTime
billingInfoCreated_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoFirst_name :: Maybe Text
billingInfoFirst_name = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoFraud :: Maybe BillingInfoFraud
billingInfoFraud = Maybe BillingInfoFraud
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoId :: Maybe Text
billingInfoId = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoLast_name :: Maybe Text
billingInfoLast_name = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoObject :: Maybe Text
billingInfoObject = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoPayment_gateway_references :: Maybe [PaymentGatewayReferences]
billingInfoPayment_gateway_references = Maybe [PaymentGatewayReferences]
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoPayment_method :: Maybe PaymentMethod
billingInfoPayment_method = Maybe PaymentMethod
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoPrimary_payment_method :: Maybe Bool
billingInfoPrimary_payment_method = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoUpdated_at :: Maybe JsonDateTime
billingInfoUpdated_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoUpdated_by :: Maybe BillingInfoUpdated_by
billingInfoUpdated_by = Maybe BillingInfoUpdated_by
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoValid :: Maybe Bool
billingInfoValid = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoVat_number :: Maybe Text
billingInfoVat_number = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}
data BillingInfoFraud = BillingInfoFraud
{ BillingInfoFraud -> Maybe BillingInfoFraudDecision
billingInfoFraudDecision :: (GHC.Maybe.Maybe BillingInfoFraudDecision)
, BillingInfoFraud -> Maybe Object
billingInfoFraudRisk_rules_triggered :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object)
, BillingInfoFraud -> Maybe Int
billingInfoFraudScore :: (GHC.Maybe.Maybe GHC.Types.Int)
}
deriving
( Int -> BillingInfoFraud -> ShowS
[BillingInfoFraud] -> ShowS
BillingInfoFraud -> String
(Int -> BillingInfoFraud -> ShowS)
-> (BillingInfoFraud -> String)
-> ([BillingInfoFraud] -> ShowS)
-> Show BillingInfoFraud
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BillingInfoFraud -> ShowS
showsPrec :: Int -> BillingInfoFraud -> ShowS
$cshow :: BillingInfoFraud -> String
show :: BillingInfoFraud -> String
$cshowList :: [BillingInfoFraud] -> ShowS
showList :: [BillingInfoFraud] -> ShowS
GHC.Show.Show
, BillingInfoFraud -> BillingInfoFraud -> Bool
(BillingInfoFraud -> BillingInfoFraud -> Bool)
-> (BillingInfoFraud -> BillingInfoFraud -> Bool)
-> Eq BillingInfoFraud
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BillingInfoFraud -> BillingInfoFraud -> Bool
== :: BillingInfoFraud -> BillingInfoFraud -> Bool
$c/= :: BillingInfoFraud -> BillingInfoFraud -> Bool
/= :: BillingInfoFraud -> BillingInfoFraud -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON BillingInfoFraud where
toJSON :: BillingInfoFraud -> Value
toJSON BillingInfoFraud
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair]
-> (BillingInfoFraudDecision -> [Pair])
-> Maybe BillingInfoFraudDecision
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (BillingInfoFraudDecision -> Pair)
-> BillingInfoFraudDecision
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"decision" Key -> BillingInfoFraudDecision -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfoFraud -> Maybe BillingInfoFraudDecision
billingInfoFraudDecision BillingInfoFraud
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Object -> [Pair]) -> Maybe Object -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Object -> Pair) -> Object -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"risk_rules_triggered" Key -> Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfoFraud -> Maybe Object
billingInfoFraudRisk_rules_triggered BillingInfoFraud
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"score" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfoFraud -> Maybe Int
billingInfoFraudScore BillingInfoFraud
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: BillingInfoFraud -> Encoding
toEncoding BillingInfoFraud
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ([Series] -> Series
forall a. Monoid a => [a] -> a
GHC.Base.mconcat ([[Series]] -> [Series]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Series]
-> (BillingInfoFraudDecision -> [Series])
-> Maybe BillingInfoFraudDecision
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (BillingInfoFraudDecision -> Series)
-> BillingInfoFraudDecision
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"decision" Key -> BillingInfoFraudDecision -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfoFraud -> Maybe BillingInfoFraudDecision
billingInfoFraudDecision BillingInfoFraud
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Object -> [Series]) -> Maybe Object -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Object -> Series) -> Object -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"risk_rules_triggered" Key -> Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfoFraud -> Maybe Object
billingInfoFraudRisk_rules_triggered BillingInfoFraud
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Int -> [Series]) -> Maybe Int -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Int -> Series) -> Int -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"score" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfoFraud -> Maybe Int
billingInfoFraudScore BillingInfoFraud
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON BillingInfoFraud where
parseJSON :: Value -> Parser BillingInfoFraud
parseJSON = String
-> (Object -> Parser BillingInfoFraud)
-> Value
-> Parser BillingInfoFraud
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"BillingInfoFraud" (\Object
obj -> (((Maybe BillingInfoFraudDecision
-> Maybe Object -> Maybe Int -> BillingInfoFraud)
-> Parser
(Maybe BillingInfoFraudDecision
-> Maybe Object -> Maybe Int -> BillingInfoFraud)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe BillingInfoFraudDecision
-> Maybe Object -> Maybe Int -> BillingInfoFraud
BillingInfoFraud Parser
(Maybe BillingInfoFraudDecision
-> Maybe Object -> Maybe Int -> BillingInfoFraud)
-> Parser (Maybe BillingInfoFraudDecision)
-> Parser (Maybe Object -> Maybe Int -> BillingInfoFraud)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe BillingInfoFraudDecision)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"decision")) Parser (Maybe Object -> Maybe Int -> BillingInfoFraud)
-> Parser (Maybe Object) -> Parser (Maybe Int -> BillingInfoFraud)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"risk_rules_triggered")) Parser (Maybe Int -> BillingInfoFraud)
-> Parser (Maybe Int) -> Parser BillingInfoFraud
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"score"))
mkBillingInfoFraud :: BillingInfoFraud
mkBillingInfoFraud :: BillingInfoFraud
mkBillingInfoFraud =
BillingInfoFraud
{ billingInfoFraudDecision :: Maybe BillingInfoFraudDecision
billingInfoFraudDecision = Maybe BillingInfoFraudDecision
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoFraudRisk_rules_triggered :: Maybe Object
billingInfoFraudRisk_rules_triggered = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoFraudScore :: Maybe Int
billingInfoFraudScore = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
}
data BillingInfoFraudDecision
=
BillingInfoFraudDecisionOther Data.Aeson.Types.Internal.Value
|
BillingInfoFraudDecisionTyped Data.Text.Internal.Text
|
BillingInfoFraudDecisionEnumApprove
|
BillingInfoFraudDecisionEnumDecline
|
BillingInfoFraudDecisionEnumEscalate
|
BillingInfoFraudDecisionEnumReview
deriving (Int -> BillingInfoFraudDecision -> ShowS
[BillingInfoFraudDecision] -> ShowS
BillingInfoFraudDecision -> String
(Int -> BillingInfoFraudDecision -> ShowS)
-> (BillingInfoFraudDecision -> String)
-> ([BillingInfoFraudDecision] -> ShowS)
-> Show BillingInfoFraudDecision
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BillingInfoFraudDecision -> ShowS
showsPrec :: Int -> BillingInfoFraudDecision -> ShowS
$cshow :: BillingInfoFraudDecision -> String
show :: BillingInfoFraudDecision -> String
$cshowList :: [BillingInfoFraudDecision] -> ShowS
showList :: [BillingInfoFraudDecision] -> ShowS
GHC.Show.Show, BillingInfoFraudDecision -> BillingInfoFraudDecision -> Bool
(BillingInfoFraudDecision -> BillingInfoFraudDecision -> Bool)
-> (BillingInfoFraudDecision -> BillingInfoFraudDecision -> Bool)
-> Eq BillingInfoFraudDecision
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BillingInfoFraudDecision -> BillingInfoFraudDecision -> Bool
== :: BillingInfoFraudDecision -> BillingInfoFraudDecision -> Bool
$c/= :: BillingInfoFraudDecision -> BillingInfoFraudDecision -> Bool
/= :: BillingInfoFraudDecision -> BillingInfoFraudDecision -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON BillingInfoFraudDecision where
toJSON :: BillingInfoFraudDecision -> Value
toJSON (BillingInfoFraudDecisionOther Value
val) = Value
val
toJSON (BillingInfoFraudDecisionTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (BillingInfoFraudDecision
BillingInfoFraudDecisionEnumApprove) = Value
"approve"
toJSON (BillingInfoFraudDecision
BillingInfoFraudDecisionEnumDecline) = Value
"decline"
toJSON (BillingInfoFraudDecision
BillingInfoFraudDecisionEnumEscalate) = Value
"escalate"
toJSON (BillingInfoFraudDecision
BillingInfoFraudDecisionEnumReview) = Value
"review"
instance Data.Aeson.Types.FromJSON.FromJSON BillingInfoFraudDecision where
parseJSON :: Value -> Parser BillingInfoFraudDecision
parseJSON Value
val =
BillingInfoFraudDecision -> Parser BillingInfoFraudDecision
forall a. a -> Parser a
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
"approve" -> BillingInfoFraudDecision
BillingInfoFraudDecisionEnumApprove
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"decline" -> BillingInfoFraudDecision
BillingInfoFraudDecisionEnumDecline
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"escalate" -> BillingInfoFraudDecision
BillingInfoFraudDecisionEnumEscalate
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"review" -> BillingInfoFraudDecision
BillingInfoFraudDecisionEnumReview
| Bool
GHC.Base.otherwise -> Value -> BillingInfoFraudDecision
BillingInfoFraudDecisionOther Value
val
)
data BillingInfoUpdated_by = BillingInfoUpdated_by
{ BillingInfoUpdated_by -> Maybe Text
billingInfoUpdated_byCountry :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, BillingInfoUpdated_by -> Maybe Text
billingInfoUpdated_byIp :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> BillingInfoUpdated_by -> ShowS
[BillingInfoUpdated_by] -> ShowS
BillingInfoUpdated_by -> String
(Int -> BillingInfoUpdated_by -> ShowS)
-> (BillingInfoUpdated_by -> String)
-> ([BillingInfoUpdated_by] -> ShowS)
-> Show BillingInfoUpdated_by
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BillingInfoUpdated_by -> ShowS
showsPrec :: Int -> BillingInfoUpdated_by -> ShowS
$cshow :: BillingInfoUpdated_by -> String
show :: BillingInfoUpdated_by -> String
$cshowList :: [BillingInfoUpdated_by] -> ShowS
showList :: [BillingInfoUpdated_by] -> ShowS
GHC.Show.Show
, BillingInfoUpdated_by -> BillingInfoUpdated_by -> Bool
(BillingInfoUpdated_by -> BillingInfoUpdated_by -> Bool)
-> (BillingInfoUpdated_by -> BillingInfoUpdated_by -> Bool)
-> Eq BillingInfoUpdated_by
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BillingInfoUpdated_by -> BillingInfoUpdated_by -> Bool
== :: BillingInfoUpdated_by -> BillingInfoUpdated_by -> Bool
$c/= :: BillingInfoUpdated_by -> BillingInfoUpdated_by -> Bool
/= :: BillingInfoUpdated_by -> BillingInfoUpdated_by -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON BillingInfoUpdated_by where
toJSON :: BillingInfoUpdated_by -> Value
toJSON BillingInfoUpdated_by
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"country" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfoUpdated_by -> Maybe Text
billingInfoUpdated_byCountry BillingInfoUpdated_by
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ip" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (BillingInfoUpdated_by -> Maybe Text
billingInfoUpdated_byIp BillingInfoUpdated_by
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: BillingInfoUpdated_by -> Encoding
toEncoding BillingInfoUpdated_by
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ([Series] -> Series
forall a. Monoid a => [a] -> a
GHC.Base.mconcat ([[Series]] -> [Series]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"country" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfoUpdated_by -> Maybe Text
billingInfoUpdated_byCountry BillingInfoUpdated_by
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ip" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (BillingInfoUpdated_by -> Maybe Text
billingInfoUpdated_byIp BillingInfoUpdated_by
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON BillingInfoUpdated_by where
parseJSON :: Value -> Parser BillingInfoUpdated_by
parseJSON = String
-> (Object -> Parser BillingInfoUpdated_by)
-> Value
-> Parser BillingInfoUpdated_by
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"BillingInfoUpdated_by" (\Object
obj -> ((Maybe Text -> Maybe Text -> BillingInfoUpdated_by)
-> Parser (Maybe Text -> Maybe Text -> BillingInfoUpdated_by)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text -> Maybe Text -> BillingInfoUpdated_by
BillingInfoUpdated_by Parser (Maybe Text -> Maybe Text -> BillingInfoUpdated_by)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> BillingInfoUpdated_by)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"country")) Parser (Maybe Text -> BillingInfoUpdated_by)
-> Parser (Maybe Text) -> Parser BillingInfoUpdated_by
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"ip"))
mkBillingInfoUpdated_by :: BillingInfoUpdated_by
mkBillingInfoUpdated_by :: BillingInfoUpdated_by
mkBillingInfoUpdated_by =
BillingInfoUpdated_by
{ billingInfoUpdated_byCountry :: Maybe Text
billingInfoUpdated_byCountry = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, billingInfoUpdated_byIp :: Maybe Text
billingInfoUpdated_byIp = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}