{-# LANGUAGE MultiWayIf #-}
-- CHANGE WITH CAUTION: This is a generated code file generated by https://github.com/Haskell-OpenAPI-Code-Generator/Haskell-OpenAPI-Client-Code-Generator.
{-# LANGUAGE OverloadedStrings #-}

-- | Contains the types generated from the schema InvoiceTaxAmount
module StripeAPI.Types.InvoiceTaxAmount 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

-- | Defines the object schema located at @components.schemas.invoice_tax_amount@ in the specification.
data InvoiceTaxAmount = InvoiceTaxAmount
  { -- | amount: The amount, in %s, of the tax.
    InvoiceTaxAmount -> Int
invoiceTaxAmountAmount :: GHC.Types.Int,
    -- | inclusive: Whether this tax amount is inclusive or exclusive.
    InvoiceTaxAmount -> Bool
invoiceTaxAmountInclusive :: GHC.Types.Bool,
    -- | tax_rate: The tax rate that was applied to get this tax amount.
    InvoiceTaxAmount -> InvoiceTaxAmountTaxRate'Variants
invoiceTaxAmountTaxRate :: InvoiceTaxAmountTaxRate'Variants
  }
  deriving
    ( Int -> InvoiceTaxAmount -> ShowS
[InvoiceTaxAmount] -> ShowS
InvoiceTaxAmount -> String
(Int -> InvoiceTaxAmount -> ShowS)
-> (InvoiceTaxAmount -> String)
-> ([InvoiceTaxAmount] -> ShowS)
-> Show InvoiceTaxAmount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InvoiceTaxAmount] -> ShowS
$cshowList :: [InvoiceTaxAmount] -> ShowS
show :: InvoiceTaxAmount -> String
$cshow :: InvoiceTaxAmount -> String
showsPrec :: Int -> InvoiceTaxAmount -> ShowS
$cshowsPrec :: Int -> InvoiceTaxAmount -> ShowS
GHC.Show.Show,
      InvoiceTaxAmount -> InvoiceTaxAmount -> Bool
(InvoiceTaxAmount -> InvoiceTaxAmount -> Bool)
-> (InvoiceTaxAmount -> InvoiceTaxAmount -> Bool)
-> Eq InvoiceTaxAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InvoiceTaxAmount -> InvoiceTaxAmount -> Bool
$c/= :: InvoiceTaxAmount -> InvoiceTaxAmount -> Bool
== :: InvoiceTaxAmount -> InvoiceTaxAmount -> Bool
$c== :: InvoiceTaxAmount -> InvoiceTaxAmount -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON InvoiceTaxAmount where
  toJSON :: InvoiceTaxAmount -> Value
toJSON InvoiceTaxAmount
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..= InvoiceTaxAmount -> Int
invoiceTaxAmountAmount InvoiceTaxAmount
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..= InvoiceTaxAmount -> Bool
invoiceTaxAmountInclusive InvoiceTaxAmount
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_rate" Text -> InvoiceTaxAmountTaxRate'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= InvoiceTaxAmount -> InvoiceTaxAmountTaxRate'Variants
invoiceTaxAmountTaxRate InvoiceTaxAmount
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: InvoiceTaxAmount -> Encoding
toEncoding InvoiceTaxAmount
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..= InvoiceTaxAmount -> Int
invoiceTaxAmountAmount InvoiceTaxAmount
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..= InvoiceTaxAmount -> Bool
invoiceTaxAmountInclusive InvoiceTaxAmount
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_rate" Text -> InvoiceTaxAmountTaxRate'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= InvoiceTaxAmount -> InvoiceTaxAmountTaxRate'Variants
invoiceTaxAmountTaxRate InvoiceTaxAmount
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON InvoiceTaxAmount where
  parseJSON :: Value -> Parser InvoiceTaxAmount
parseJSON = String
-> (Object -> Parser InvoiceTaxAmount)
-> Value
-> Parser InvoiceTaxAmount
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"InvoiceTaxAmount" (\Object
obj -> (((Int
 -> Bool -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount)
-> Parser
     (Int
      -> Bool -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Int -> Bool -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount
InvoiceTaxAmount Parser
  (Int
   -> Bool -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount)
-> Parser Int
-> Parser
     (Bool -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount)
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 -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount)
-> Parser Bool
-> Parser (InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount)
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 (InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount)
-> Parser InvoiceTaxAmountTaxRate'Variants
-> Parser InvoiceTaxAmount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser InvoiceTaxAmountTaxRate'Variants
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"tax_rate"))

-- | Create a new 'InvoiceTaxAmount' with all required fields.
mkInvoiceTaxAmount ::
  -- | 'invoiceTaxAmountAmount'
  GHC.Types.Int ->
  -- | 'invoiceTaxAmountInclusive'
  GHC.Types.Bool ->
  -- | 'invoiceTaxAmountTaxRate'
  InvoiceTaxAmountTaxRate'Variants ->
  InvoiceTaxAmount
mkInvoiceTaxAmount :: Int -> Bool -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount
mkInvoiceTaxAmount Int
invoiceTaxAmountAmount Bool
invoiceTaxAmountInclusive InvoiceTaxAmountTaxRate'Variants
invoiceTaxAmountTaxRate =
  InvoiceTaxAmount :: Int -> Bool -> InvoiceTaxAmountTaxRate'Variants -> InvoiceTaxAmount
InvoiceTaxAmount
    { invoiceTaxAmountAmount :: Int
invoiceTaxAmountAmount = Int
invoiceTaxAmountAmount,
      invoiceTaxAmountInclusive :: Bool
invoiceTaxAmountInclusive = Bool
invoiceTaxAmountInclusive,
      invoiceTaxAmountTaxRate :: InvoiceTaxAmountTaxRate'Variants
invoiceTaxAmountTaxRate = InvoiceTaxAmountTaxRate'Variants
invoiceTaxAmountTaxRate
    }

-- | Defines the oneOf schema located at @components.schemas.invoice_tax_amount.properties.tax_rate.anyOf@ in the specification.
--
-- The tax rate that was applied to get this tax amount.
data InvoiceTaxAmountTaxRate'Variants
  = InvoiceTaxAmountTaxRate'Text Data.Text.Internal.Text
  | InvoiceTaxAmountTaxRate'TaxRate TaxRate
  deriving (Int -> InvoiceTaxAmountTaxRate'Variants -> ShowS
[InvoiceTaxAmountTaxRate'Variants] -> ShowS
InvoiceTaxAmountTaxRate'Variants -> String
(Int -> InvoiceTaxAmountTaxRate'Variants -> ShowS)
-> (InvoiceTaxAmountTaxRate'Variants -> String)
-> ([InvoiceTaxAmountTaxRate'Variants] -> ShowS)
-> Show InvoiceTaxAmountTaxRate'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InvoiceTaxAmountTaxRate'Variants] -> ShowS
$cshowList :: [InvoiceTaxAmountTaxRate'Variants] -> ShowS
show :: InvoiceTaxAmountTaxRate'Variants -> String
$cshow :: InvoiceTaxAmountTaxRate'Variants -> String
showsPrec :: Int -> InvoiceTaxAmountTaxRate'Variants -> ShowS
$cshowsPrec :: Int -> InvoiceTaxAmountTaxRate'Variants -> ShowS
GHC.Show.Show, InvoiceTaxAmountTaxRate'Variants
-> InvoiceTaxAmountTaxRate'Variants -> Bool
(InvoiceTaxAmountTaxRate'Variants
 -> InvoiceTaxAmountTaxRate'Variants -> Bool)
-> (InvoiceTaxAmountTaxRate'Variants
    -> InvoiceTaxAmountTaxRate'Variants -> Bool)
-> Eq InvoiceTaxAmountTaxRate'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InvoiceTaxAmountTaxRate'Variants
-> InvoiceTaxAmountTaxRate'Variants -> Bool
$c/= :: InvoiceTaxAmountTaxRate'Variants
-> InvoiceTaxAmountTaxRate'Variants -> Bool
== :: InvoiceTaxAmountTaxRate'Variants
-> InvoiceTaxAmountTaxRate'Variants -> Bool
$c== :: InvoiceTaxAmountTaxRate'Variants
-> InvoiceTaxAmountTaxRate'Variants -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON InvoiceTaxAmountTaxRate'Variants where
  toJSON :: InvoiceTaxAmountTaxRate'Variants -> Value
toJSON (InvoiceTaxAmountTaxRate'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
  toJSON (InvoiceTaxAmountTaxRate'TaxRate TaxRate
a) = TaxRate -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON TaxRate
a

instance Data.Aeson.Types.FromJSON.FromJSON InvoiceTaxAmountTaxRate'Variants where
  parseJSON :: Value -> Parser InvoiceTaxAmountTaxRate'Variants
parseJSON Value
val = case (Text -> InvoiceTaxAmountTaxRate'Variants
InvoiceTaxAmountTaxRate'Text (Text -> InvoiceTaxAmountTaxRate'Variants)
-> Result Text -> Result InvoiceTaxAmountTaxRate'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 InvoiceTaxAmountTaxRate'Variants
-> Result InvoiceTaxAmountTaxRate'Variants
-> Result InvoiceTaxAmountTaxRate'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((TaxRate -> InvoiceTaxAmountTaxRate'Variants
InvoiceTaxAmountTaxRate'TaxRate (TaxRate -> InvoiceTaxAmountTaxRate'Variants)
-> Result TaxRate -> Result InvoiceTaxAmountTaxRate'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 InvoiceTaxAmountTaxRate'Variants
-> Result InvoiceTaxAmountTaxRate'Variants
-> Result InvoiceTaxAmountTaxRate'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result InvoiceTaxAmountTaxRate'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
    Data.Aeson.Types.Internal.Success InvoiceTaxAmountTaxRate'Variants
a -> InvoiceTaxAmountTaxRate'Variants
-> Parser InvoiceTaxAmountTaxRate'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure InvoiceTaxAmountTaxRate'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String -> Parser InvoiceTaxAmountTaxRate'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a