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

-- | Defines the object schema located at @components.schemas.subscriptions_resource_pending_update@ in the specification.
--
-- Pending Updates store the changes pending from a previous update that will be applied
-- to the Subscription upon successful payment.
data SubscriptionsResourcePendingUpdate = SubscriptionsResourcePendingUpdate
  { -- | billing_cycle_anchor: If the update is applied, determines the date of the first full invoice, and, for plans with \`month\` or \`year\` intervals, the day of the month for subsequent invoices.
    SubscriptionsResourcePendingUpdate -> Maybe Int
subscriptionsResourcePendingUpdateBillingCycleAnchor :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | expires_at: The point after which the changes reflected by this update will be discarded and no longer applied.
    SubscriptionsResourcePendingUpdate -> Int
subscriptionsResourcePendingUpdateExpiresAt :: GHC.Types.Int,
    -- | subscription_items: List of subscription items, each with an attached plan, that will be set if the update is applied.
    SubscriptionsResourcePendingUpdate -> Maybe [SubscriptionItem]
subscriptionsResourcePendingUpdateSubscriptionItems :: (GHC.Maybe.Maybe ([SubscriptionItem])),
    -- | trial_end: Unix timestamp representing the end of the trial period the customer will get before being charged for the first time, if the update is applied.
    SubscriptionsResourcePendingUpdate -> Maybe Int
subscriptionsResourcePendingUpdateTrialEnd :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | trial_from_plan: Indicates if a plan\'s \`trial_period_days\` should be applied to the subscription. Setting \`trial_end\` per subscription is preferred, and this defaults to \`false\`. Setting this flag to \`true\` together with \`trial_end\` is not allowed.
    SubscriptionsResourcePendingUpdate -> Maybe Bool
subscriptionsResourcePendingUpdateTrialFromPlan :: (GHC.Maybe.Maybe GHC.Types.Bool)
  }
  deriving
    ( Int -> SubscriptionsResourcePendingUpdate -> ShowS
[SubscriptionsResourcePendingUpdate] -> ShowS
SubscriptionsResourcePendingUpdate -> String
(Int -> SubscriptionsResourcePendingUpdate -> ShowS)
-> (SubscriptionsResourcePendingUpdate -> String)
-> ([SubscriptionsResourcePendingUpdate] -> ShowS)
-> Show SubscriptionsResourcePendingUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionsResourcePendingUpdate] -> ShowS
$cshowList :: [SubscriptionsResourcePendingUpdate] -> ShowS
show :: SubscriptionsResourcePendingUpdate -> String
$cshow :: SubscriptionsResourcePendingUpdate -> String
showsPrec :: Int -> SubscriptionsResourcePendingUpdate -> ShowS
$cshowsPrec :: Int -> SubscriptionsResourcePendingUpdate -> ShowS
GHC.Show.Show,
      SubscriptionsResourcePendingUpdate
-> SubscriptionsResourcePendingUpdate -> Bool
(SubscriptionsResourcePendingUpdate
 -> SubscriptionsResourcePendingUpdate -> Bool)
-> (SubscriptionsResourcePendingUpdate
    -> SubscriptionsResourcePendingUpdate -> Bool)
-> Eq SubscriptionsResourcePendingUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionsResourcePendingUpdate
-> SubscriptionsResourcePendingUpdate -> Bool
$c/= :: SubscriptionsResourcePendingUpdate
-> SubscriptionsResourcePendingUpdate -> Bool
== :: SubscriptionsResourcePendingUpdate
-> SubscriptionsResourcePendingUpdate -> Bool
$c== :: SubscriptionsResourcePendingUpdate
-> SubscriptionsResourcePendingUpdate -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionsResourcePendingUpdate where
  toJSON :: SubscriptionsResourcePendingUpdate -> Value
toJSON SubscriptionsResourcePendingUpdate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"billing_cycle_anchor" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe Int
subscriptionsResourcePendingUpdateBillingCycleAnchor SubscriptionsResourcePendingUpdate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"expires_at" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Int
subscriptionsResourcePendingUpdateExpiresAt SubscriptionsResourcePendingUpdate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"subscription_items" Text -> Maybe [SubscriptionItem] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe [SubscriptionItem]
subscriptionsResourcePendingUpdateSubscriptionItems SubscriptionsResourcePendingUpdate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"trial_end" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe Int
subscriptionsResourcePendingUpdateTrialEnd SubscriptionsResourcePendingUpdate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"trial_from_plan" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe Bool
subscriptionsResourcePendingUpdateTrialFromPlan SubscriptionsResourcePendingUpdate
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: SubscriptionsResourcePendingUpdate -> Encoding
toEncoding SubscriptionsResourcePendingUpdate
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"billing_cycle_anchor" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe Int
subscriptionsResourcePendingUpdateBillingCycleAnchor SubscriptionsResourcePendingUpdate
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"expires_at" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Int
subscriptionsResourcePendingUpdateExpiresAt SubscriptionsResourcePendingUpdate
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"subscription_items" Text -> Maybe [SubscriptionItem] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe [SubscriptionItem]
subscriptionsResourcePendingUpdateSubscriptionItems SubscriptionsResourcePendingUpdate
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"trial_end" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe Int
subscriptionsResourcePendingUpdateTrialEnd SubscriptionsResourcePendingUpdate
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"trial_from_plan" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionsResourcePendingUpdate -> Maybe Bool
subscriptionsResourcePendingUpdateTrialFromPlan SubscriptionsResourcePendingUpdate
obj)))))

instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionsResourcePendingUpdate where
  parseJSON :: Value -> Parser SubscriptionsResourcePendingUpdate
parseJSON = String
-> (Object -> Parser SubscriptionsResourcePendingUpdate)
-> Value
-> Parser SubscriptionsResourcePendingUpdate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionsResourcePendingUpdate" (\Object
obj -> (((((Maybe Int
 -> Int
 -> Maybe [SubscriptionItem]
 -> Maybe Int
 -> Maybe Bool
 -> SubscriptionsResourcePendingUpdate)
-> Parser
     (Maybe Int
      -> Int
      -> Maybe [SubscriptionItem]
      -> Maybe Int
      -> Maybe Bool
      -> SubscriptionsResourcePendingUpdate)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Int
-> Maybe [SubscriptionItem]
-> Maybe Int
-> Maybe Bool
-> SubscriptionsResourcePendingUpdate
SubscriptionsResourcePendingUpdate Parser
  (Maybe Int
   -> Int
   -> Maybe [SubscriptionItem]
   -> Maybe Int
   -> Maybe Bool
   -> SubscriptionsResourcePendingUpdate)
-> Parser (Maybe Int)
-> Parser
     (Int
      -> Maybe [SubscriptionItem]
      -> Maybe Int
      -> Maybe Bool
      -> SubscriptionsResourcePendingUpdate)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"billing_cycle_anchor")) Parser
  (Int
   -> Maybe [SubscriptionItem]
   -> Maybe Int
   -> Maybe Bool
   -> SubscriptionsResourcePendingUpdate)
-> Parser Int
-> Parser
     (Maybe [SubscriptionItem]
      -> Maybe Int -> Maybe Bool -> SubscriptionsResourcePendingUpdate)
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
"expires_at")) Parser
  (Maybe [SubscriptionItem]
   -> Maybe Int -> Maybe Bool -> SubscriptionsResourcePendingUpdate)
-> Parser (Maybe [SubscriptionItem])
-> Parser
     (Maybe Int -> Maybe Bool -> SubscriptionsResourcePendingUpdate)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [SubscriptionItem])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"subscription_items")) Parser
  (Maybe Int -> Maybe Bool -> SubscriptionsResourcePendingUpdate)
-> Parser (Maybe Int)
-> Parser (Maybe Bool -> SubscriptionsResourcePendingUpdate)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"trial_end")) Parser (Maybe Bool -> SubscriptionsResourcePendingUpdate)
-> Parser (Maybe Bool) -> Parser SubscriptionsResourcePendingUpdate
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"trial_from_plan"))

-- | Create a new 'SubscriptionsResourcePendingUpdate' with all required fields.
mkSubscriptionsResourcePendingUpdate ::
  -- | 'subscriptionsResourcePendingUpdateExpiresAt'
  GHC.Types.Int ->
  SubscriptionsResourcePendingUpdate
mkSubscriptionsResourcePendingUpdate :: Int -> SubscriptionsResourcePendingUpdate
mkSubscriptionsResourcePendingUpdate Int
subscriptionsResourcePendingUpdateExpiresAt =
  SubscriptionsResourcePendingUpdate :: Maybe Int
-> Int
-> Maybe [SubscriptionItem]
-> Maybe Int
-> Maybe Bool
-> SubscriptionsResourcePendingUpdate
SubscriptionsResourcePendingUpdate
    { subscriptionsResourcePendingUpdateBillingCycleAnchor :: Maybe Int
subscriptionsResourcePendingUpdateBillingCycleAnchor = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      subscriptionsResourcePendingUpdateExpiresAt :: Int
subscriptionsResourcePendingUpdateExpiresAt = Int
subscriptionsResourcePendingUpdateExpiresAt,
      subscriptionsResourcePendingUpdateSubscriptionItems :: Maybe [SubscriptionItem]
subscriptionsResourcePendingUpdateSubscriptionItems = Maybe [SubscriptionItem]
forall a. Maybe a
GHC.Maybe.Nothing,
      subscriptionsResourcePendingUpdateTrialEnd :: Maybe Int
subscriptionsResourcePendingUpdateTrialEnd = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      subscriptionsResourcePendingUpdateTrialFromPlan :: Maybe Bool
subscriptionsResourcePendingUpdateTrialFromPlan = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
    }