{-# 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 CustomerAcceptance
module StripeAPI.Types.CustomerAcceptance 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.OnlineAcceptance
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | Defines the object schema located at @components.schemas.customer_acceptance@ in the specification.
data CustomerAcceptance = CustomerAcceptance
  { -- | accepted_at: The time at which the customer accepted the Mandate.
    CustomerAcceptance -> Maybe Int
customerAcceptanceAcceptedAt :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | offline:
    CustomerAcceptance -> Maybe OfflineAcceptance
customerAcceptanceOffline :: (GHC.Maybe.Maybe OfflineAcceptance),
    -- | online:
    CustomerAcceptance -> Maybe OnlineAcceptance
customerAcceptanceOnline :: (GHC.Maybe.Maybe OnlineAcceptance),
    -- | type: The type of customer acceptance information included with the Mandate. One of \`online\` or \`offline\`.
    CustomerAcceptance -> CustomerAcceptanceType'
customerAcceptanceType :: CustomerAcceptanceType'
  }
  deriving
    ( Int -> CustomerAcceptance -> ShowS
[CustomerAcceptance] -> ShowS
CustomerAcceptance -> String
(Int -> CustomerAcceptance -> ShowS)
-> (CustomerAcceptance -> String)
-> ([CustomerAcceptance] -> ShowS)
-> Show CustomerAcceptance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomerAcceptance] -> ShowS
$cshowList :: [CustomerAcceptance] -> ShowS
show :: CustomerAcceptance -> String
$cshow :: CustomerAcceptance -> String
showsPrec :: Int -> CustomerAcceptance -> ShowS
$cshowsPrec :: Int -> CustomerAcceptance -> ShowS
GHC.Show.Show,
      CustomerAcceptance -> CustomerAcceptance -> Bool
(CustomerAcceptance -> CustomerAcceptance -> Bool)
-> (CustomerAcceptance -> CustomerAcceptance -> Bool)
-> Eq CustomerAcceptance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerAcceptance -> CustomerAcceptance -> Bool
$c/= :: CustomerAcceptance -> CustomerAcceptance -> Bool
== :: CustomerAcceptance -> CustomerAcceptance -> Bool
$c== :: CustomerAcceptance -> CustomerAcceptance -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON CustomerAcceptance where
  toJSON :: CustomerAcceptance -> Value
toJSON CustomerAcceptance
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"accepted_at" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> Maybe Int
customerAcceptanceAcceptedAt CustomerAcceptance
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"offline" Text -> Maybe OfflineAcceptance -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> Maybe OfflineAcceptance
customerAcceptanceOffline CustomerAcceptance
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"online" Text -> Maybe OnlineAcceptance -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> Maybe OnlineAcceptance
customerAcceptanceOnline CustomerAcceptance
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"type" Text -> CustomerAcceptanceType' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> CustomerAcceptanceType'
customerAcceptanceType CustomerAcceptance
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: CustomerAcceptance -> Encoding
toEncoding CustomerAcceptance
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"accepted_at" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> Maybe Int
customerAcceptanceAcceptedAt CustomerAcceptance
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"offline" Text -> Maybe OfflineAcceptance -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> Maybe OfflineAcceptance
customerAcceptanceOffline CustomerAcceptance
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"online" Text -> Maybe OnlineAcceptance -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> Maybe OnlineAcceptance
customerAcceptanceOnline CustomerAcceptance
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"type" Text -> CustomerAcceptanceType' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= CustomerAcceptance -> CustomerAcceptanceType'
customerAcceptanceType CustomerAcceptance
obj))))

instance Data.Aeson.Types.FromJSON.FromJSON CustomerAcceptance where
  parseJSON :: Value -> Parser CustomerAcceptance
parseJSON = String
-> (OfflineAcceptance -> Parser CustomerAcceptance)
-> Value
-> Parser CustomerAcceptance
forall a.
String -> (OfflineAcceptance -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"CustomerAcceptance" (\OfflineAcceptance
obj -> ((((Maybe Int
 -> Maybe OfflineAcceptance
 -> Maybe OnlineAcceptance
 -> CustomerAcceptanceType'
 -> CustomerAcceptance)
-> Parser
     (Maybe Int
      -> Maybe OfflineAcceptance
      -> Maybe OnlineAcceptance
      -> CustomerAcceptanceType'
      -> CustomerAcceptance)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe OfflineAcceptance
-> Maybe OnlineAcceptance
-> CustomerAcceptanceType'
-> CustomerAcceptance
CustomerAcceptance Parser
  (Maybe Int
   -> Maybe OfflineAcceptance
   -> Maybe OnlineAcceptance
   -> CustomerAcceptanceType'
   -> CustomerAcceptance)
-> Parser (Maybe Int)
-> Parser
     (Maybe OfflineAcceptance
      -> Maybe OnlineAcceptance
      -> CustomerAcceptanceType'
      -> CustomerAcceptance)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (OfflineAcceptance
obj OfflineAcceptance -> Text -> Parser (Maybe Int)
forall a.
FromJSON a =>
OfflineAcceptance -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"accepted_at")) Parser
  (Maybe OfflineAcceptance
   -> Maybe OnlineAcceptance
   -> CustomerAcceptanceType'
   -> CustomerAcceptance)
-> Parser (Maybe OfflineAcceptance)
-> Parser
     (Maybe OnlineAcceptance
      -> CustomerAcceptanceType' -> CustomerAcceptance)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (OfflineAcceptance
obj OfflineAcceptance -> Text -> Parser (Maybe OfflineAcceptance)
forall a.
FromJSON a =>
OfflineAcceptance -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"offline")) Parser
  (Maybe OnlineAcceptance
   -> CustomerAcceptanceType' -> CustomerAcceptance)
-> Parser (Maybe OnlineAcceptance)
-> Parser (CustomerAcceptanceType' -> CustomerAcceptance)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (OfflineAcceptance
obj OfflineAcceptance -> Text -> Parser (Maybe OnlineAcceptance)
forall a.
FromJSON a =>
OfflineAcceptance -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"online")) Parser (CustomerAcceptanceType' -> CustomerAcceptance)
-> Parser CustomerAcceptanceType' -> Parser CustomerAcceptance
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (OfflineAcceptance
obj OfflineAcceptance -> Text -> Parser CustomerAcceptanceType'
forall a. FromJSON a => OfflineAcceptance -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"type"))

-- | Create a new 'CustomerAcceptance' with all required fields.
mkCustomerAcceptance ::
  -- | 'customerAcceptanceType'
  CustomerAcceptanceType' ->
  CustomerAcceptance
mkCustomerAcceptance :: CustomerAcceptanceType' -> CustomerAcceptance
mkCustomerAcceptance CustomerAcceptanceType'
customerAcceptanceType =
  CustomerAcceptance :: Maybe Int
-> Maybe OfflineAcceptance
-> Maybe OnlineAcceptance
-> CustomerAcceptanceType'
-> CustomerAcceptance
CustomerAcceptance
    { customerAcceptanceAcceptedAt :: Maybe Int
customerAcceptanceAcceptedAt = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      customerAcceptanceOffline :: Maybe OfflineAcceptance
customerAcceptanceOffline = Maybe OfflineAcceptance
forall a. Maybe a
GHC.Maybe.Nothing,
      customerAcceptanceOnline :: Maybe OnlineAcceptance
customerAcceptanceOnline = Maybe OnlineAcceptance
forall a. Maybe a
GHC.Maybe.Nothing,
      customerAcceptanceType :: CustomerAcceptanceType'
customerAcceptanceType = CustomerAcceptanceType'
customerAcceptanceType
    }

-- | Defines the enum schema located at @components.schemas.customer_acceptance.properties.type@ in the specification.
--
-- The type of customer acceptance information included with the Mandate. One of \`online\` or \`offline\`.
data CustomerAcceptanceType'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    CustomerAcceptanceType'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    CustomerAcceptanceType'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"offline"@
    CustomerAcceptanceType'EnumOffline
  | -- | Represents the JSON value @"online"@
    CustomerAcceptanceType'EnumOnline
  deriving (Int -> CustomerAcceptanceType' -> ShowS
[CustomerAcceptanceType'] -> ShowS
CustomerAcceptanceType' -> String
(Int -> CustomerAcceptanceType' -> ShowS)
-> (CustomerAcceptanceType' -> String)
-> ([CustomerAcceptanceType'] -> ShowS)
-> Show CustomerAcceptanceType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomerAcceptanceType'] -> ShowS
$cshowList :: [CustomerAcceptanceType'] -> ShowS
show :: CustomerAcceptanceType' -> String
$cshow :: CustomerAcceptanceType' -> String
showsPrec :: Int -> CustomerAcceptanceType' -> ShowS
$cshowsPrec :: Int -> CustomerAcceptanceType' -> ShowS
GHC.Show.Show, CustomerAcceptanceType' -> CustomerAcceptanceType' -> Bool
(CustomerAcceptanceType' -> CustomerAcceptanceType' -> Bool)
-> (CustomerAcceptanceType' -> CustomerAcceptanceType' -> Bool)
-> Eq CustomerAcceptanceType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerAcceptanceType' -> CustomerAcceptanceType' -> Bool
$c/= :: CustomerAcceptanceType' -> CustomerAcceptanceType' -> Bool
== :: CustomerAcceptanceType' -> CustomerAcceptanceType' -> Bool
$c== :: CustomerAcceptanceType' -> CustomerAcceptanceType' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON CustomerAcceptanceType' where
  toJSON :: CustomerAcceptanceType' -> Value
toJSON (CustomerAcceptanceType'Other Value
val) = Value
val
  toJSON (CustomerAcceptanceType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (CustomerAcceptanceType'
CustomerAcceptanceType'EnumOffline) = Value
"offline"
  toJSON (CustomerAcceptanceType'
CustomerAcceptanceType'EnumOnline) = Value
"online"

instance Data.Aeson.Types.FromJSON.FromJSON CustomerAcceptanceType' where
  parseJSON :: Value -> Parser CustomerAcceptanceType'
parseJSON Value
val =
    CustomerAcceptanceType' -> Parser CustomerAcceptanceType'
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
"offline" -> CustomerAcceptanceType'
CustomerAcceptanceType'EnumOffline
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"online" -> CustomerAcceptanceType'
CustomerAcceptanceType'EnumOnline
            | Bool
GHC.Base.otherwise -> Value -> CustomerAcceptanceType'
CustomerAcceptanceType'Other Value
val
      )