-- https://developer.paddle.com/api-reference/subscription-api/subscription-users/updateuser
module Paddle.Client.SubscriptionUsersUpdate where

import Data.Aeson (ToJSON, toJSON, genericToJSON)
import Protolude
import Prelude ()
import Paddle.FieldModifier (customJSONOptions)


data SubscriptionUsersUpdate = SubscriptionUsersUpdate 
  { SubscriptionUsersUpdate -> Int
vendorId :: Int
  , SubscriptionUsersUpdate -> Text
vendorAuthCode :: Text
  , SubscriptionUsersUpdate -> Integer
subscriptionId :: Integer
  , SubscriptionUsersUpdate -> Maybe Integer
planId :: Maybe Integer
  , SubscriptionUsersUpdate -> Maybe Bool
prorate :: Maybe Bool
  , SubscriptionUsersUpdate -> Maybe Bool
pause :: Maybe Bool
  , SubscriptionUsersUpdate -> Maybe Bool
billImmediately :: Maybe Bool
  } deriving (Int -> SubscriptionUsersUpdate -> ShowS
[SubscriptionUsersUpdate] -> ShowS
SubscriptionUsersUpdate -> String
(Int -> SubscriptionUsersUpdate -> ShowS)
-> (SubscriptionUsersUpdate -> String)
-> ([SubscriptionUsersUpdate] -> ShowS)
-> Show SubscriptionUsersUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionUsersUpdate] -> ShowS
$cshowList :: [SubscriptionUsersUpdate] -> ShowS
show :: SubscriptionUsersUpdate -> String
$cshow :: SubscriptionUsersUpdate -> String
showsPrec :: Int -> SubscriptionUsersUpdate -> ShowS
$cshowsPrec :: Int -> SubscriptionUsersUpdate -> ShowS
Show, (forall x.
 SubscriptionUsersUpdate -> Rep SubscriptionUsersUpdate x)
-> (forall x.
    Rep SubscriptionUsersUpdate x -> SubscriptionUsersUpdate)
-> Generic SubscriptionUsersUpdate
forall x. Rep SubscriptionUsersUpdate x -> SubscriptionUsersUpdate
forall x. SubscriptionUsersUpdate -> Rep SubscriptionUsersUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubscriptionUsersUpdate x -> SubscriptionUsersUpdate
$cfrom :: forall x. SubscriptionUsersUpdate -> Rep SubscriptionUsersUpdate x
Generic)

instance ToJSON SubscriptionUsersUpdate where
    toJSON :: SubscriptionUsersUpdate -> Value
toJSON = Options -> SubscriptionUsersUpdate -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
customJSONOptions