{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Types.CreditNoteTaxAmount 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.TaxRate
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data CreditNoteTaxAmount = CreditNoteTaxAmount
{
CreditNoteTaxAmount -> Int
creditNoteTaxAmountAmount :: GHC.Types.Int,
CreditNoteTaxAmount -> Bool
creditNoteTaxAmountInclusive :: GHC.Types.Bool,
CreditNoteTaxAmount -> CreditNoteTaxAmountTaxRate'Variants
creditNoteTaxAmountTaxRate :: CreditNoteTaxAmountTaxRate'Variants
}
deriving
( Int -> CreditNoteTaxAmount -> ShowS
[CreditNoteTaxAmount] -> ShowS
CreditNoteTaxAmount -> String
(Int -> CreditNoteTaxAmount -> ShowS)
-> (CreditNoteTaxAmount -> String)
-> ([CreditNoteTaxAmount] -> ShowS)
-> Show CreditNoteTaxAmount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreditNoteTaxAmount] -> ShowS
$cshowList :: [CreditNoteTaxAmount] -> ShowS
show :: CreditNoteTaxAmount -> String
$cshow :: CreditNoteTaxAmount -> String
showsPrec :: Int -> CreditNoteTaxAmount -> ShowS
$cshowsPrec :: Int -> CreditNoteTaxAmount -> ShowS
GHC.Show.Show,
CreditNoteTaxAmount -> CreditNoteTaxAmount -> Bool
(CreditNoteTaxAmount -> CreditNoteTaxAmount -> Bool)
-> (CreditNoteTaxAmount -> CreditNoteTaxAmount -> Bool)
-> Eq CreditNoteTaxAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreditNoteTaxAmount -> CreditNoteTaxAmount -> Bool
$c/= :: CreditNoteTaxAmount -> CreditNoteTaxAmount -> Bool
== :: CreditNoteTaxAmount -> CreditNoteTaxAmount -> Bool
$c== :: CreditNoteTaxAmount -> CreditNoteTaxAmount -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON CreditNoteTaxAmount where
toJSON :: CreditNoteTaxAmount -> Value
toJSON CreditNoteTaxAmount
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CreditNoteTaxAmount -> Int
creditNoteTaxAmountAmount CreditNoteTaxAmount
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"inclusive" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CreditNoteTaxAmount -> Bool
creditNoteTaxAmountInclusive CreditNoteTaxAmount
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_rate" Text -> CreditNoteTaxAmountTaxRate'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CreditNoteTaxAmount -> CreditNoteTaxAmountTaxRate'Variants
creditNoteTaxAmountTaxRate CreditNoteTaxAmount
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: CreditNoteTaxAmount -> Encoding
toEncoding CreditNoteTaxAmount
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CreditNoteTaxAmount -> Int
creditNoteTaxAmountAmount CreditNoteTaxAmount
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"inclusive" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CreditNoteTaxAmount -> Bool
creditNoteTaxAmountInclusive CreditNoteTaxAmount
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_rate" Text -> CreditNoteTaxAmountTaxRate'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CreditNoteTaxAmount -> CreditNoteTaxAmountTaxRate'Variants
creditNoteTaxAmountTaxRate CreditNoteTaxAmount
obj)))
instance Data.Aeson.Types.FromJSON.FromJSON CreditNoteTaxAmount where
parseJSON :: Value -> Parser CreditNoteTaxAmount
parseJSON = String
-> (Object -> Parser CreditNoteTaxAmount)
-> Value
-> Parser CreditNoteTaxAmount
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"CreditNoteTaxAmount" (\Object
obj -> (((Int
-> Bool
-> CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmount)
-> Parser
(Int
-> Bool
-> CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmount)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Int
-> Bool
-> CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmount
CreditNoteTaxAmount Parser
(Int
-> Bool
-> CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmount)
-> Parser Int
-> Parser
(Bool
-> CreditNoteTaxAmountTaxRate'Variants -> CreditNoteTaxAmount)
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
"amount")) Parser
(Bool
-> CreditNoteTaxAmountTaxRate'Variants -> CreditNoteTaxAmount)
-> Parser Bool
-> Parser
(CreditNoteTaxAmountTaxRate'Variants -> CreditNoteTaxAmount)
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
"inclusive")) Parser (CreditNoteTaxAmountTaxRate'Variants -> CreditNoteTaxAmount)
-> Parser CreditNoteTaxAmountTaxRate'Variants
-> Parser CreditNoteTaxAmount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser CreditNoteTaxAmountTaxRate'Variants
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"tax_rate"))
mkCreditNoteTaxAmount ::
GHC.Types.Int ->
GHC.Types.Bool ->
CreditNoteTaxAmountTaxRate'Variants ->
CreditNoteTaxAmount
mkCreditNoteTaxAmount :: Int
-> Bool
-> CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmount
mkCreditNoteTaxAmount Int
creditNoteTaxAmountAmount Bool
creditNoteTaxAmountInclusive CreditNoteTaxAmountTaxRate'Variants
creditNoteTaxAmountTaxRate =
CreditNoteTaxAmount :: Int
-> Bool
-> CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmount
CreditNoteTaxAmount
{ creditNoteTaxAmountAmount :: Int
creditNoteTaxAmountAmount = Int
creditNoteTaxAmountAmount,
creditNoteTaxAmountInclusive :: Bool
creditNoteTaxAmountInclusive = Bool
creditNoteTaxAmountInclusive,
creditNoteTaxAmountTaxRate :: CreditNoteTaxAmountTaxRate'Variants
creditNoteTaxAmountTaxRate = CreditNoteTaxAmountTaxRate'Variants
creditNoteTaxAmountTaxRate
}
data CreditNoteTaxAmountTaxRate'Variants
= CreditNoteTaxAmountTaxRate'Text Data.Text.Internal.Text
| CreditNoteTaxAmountTaxRate'TaxRate TaxRate
deriving (Int -> CreditNoteTaxAmountTaxRate'Variants -> ShowS
[CreditNoteTaxAmountTaxRate'Variants] -> ShowS
CreditNoteTaxAmountTaxRate'Variants -> String
(Int -> CreditNoteTaxAmountTaxRate'Variants -> ShowS)
-> (CreditNoteTaxAmountTaxRate'Variants -> String)
-> ([CreditNoteTaxAmountTaxRate'Variants] -> ShowS)
-> Show CreditNoteTaxAmountTaxRate'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreditNoteTaxAmountTaxRate'Variants] -> ShowS
$cshowList :: [CreditNoteTaxAmountTaxRate'Variants] -> ShowS
show :: CreditNoteTaxAmountTaxRate'Variants -> String
$cshow :: CreditNoteTaxAmountTaxRate'Variants -> String
showsPrec :: Int -> CreditNoteTaxAmountTaxRate'Variants -> ShowS
$cshowsPrec :: Int -> CreditNoteTaxAmountTaxRate'Variants -> ShowS
GHC.Show.Show, CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmountTaxRate'Variants -> Bool
(CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmountTaxRate'Variants -> Bool)
-> (CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmountTaxRate'Variants -> Bool)
-> Eq CreditNoteTaxAmountTaxRate'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmountTaxRate'Variants -> Bool
$c/= :: CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmountTaxRate'Variants -> Bool
== :: CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmountTaxRate'Variants -> Bool
$c== :: CreditNoteTaxAmountTaxRate'Variants
-> CreditNoteTaxAmountTaxRate'Variants -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CreditNoteTaxAmountTaxRate'Variants where
toJSON :: CreditNoteTaxAmountTaxRate'Variants -> Value
toJSON (CreditNoteTaxAmountTaxRate'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
toJSON (CreditNoteTaxAmountTaxRate'TaxRate TaxRate
a) = TaxRate -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON TaxRate
a
instance Data.Aeson.Types.FromJSON.FromJSON CreditNoteTaxAmountTaxRate'Variants where
parseJSON :: Value -> Parser CreditNoteTaxAmountTaxRate'Variants
parseJSON Value
val = case (Text -> CreditNoteTaxAmountTaxRate'Variants
CreditNoteTaxAmountTaxRate'Text (Text -> CreditNoteTaxAmountTaxRate'Variants)
-> Result Text -> Result CreditNoteTaxAmountTaxRate'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 CreditNoteTaxAmountTaxRate'Variants
-> Result CreditNoteTaxAmountTaxRate'Variants
-> Result CreditNoteTaxAmountTaxRate'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((TaxRate -> CreditNoteTaxAmountTaxRate'Variants
CreditNoteTaxAmountTaxRate'TaxRate (TaxRate -> CreditNoteTaxAmountTaxRate'Variants)
-> Result TaxRate -> Result CreditNoteTaxAmountTaxRate'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result TaxRate
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CreditNoteTaxAmountTaxRate'Variants
-> Result CreditNoteTaxAmountTaxRate'Variants
-> Result CreditNoteTaxAmountTaxRate'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result CreditNoteTaxAmountTaxRate'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
Data.Aeson.Types.Internal.Success CreditNoteTaxAmountTaxRate'Variants
a -> CreditNoteTaxAmountTaxRate'Variants
-> Parser CreditNoteTaxAmountTaxRate'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure CreditNoteTaxAmountTaxRate'Variants
a
Data.Aeson.Types.Internal.Error String
a -> String -> Parser CreditNoteTaxAmountTaxRate'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a