{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Stripe.Resources
  ( 
    TimeStamp(..), StripeList(..)
    
  , CustomerId(..), Customer(..), CustomerCreate(..), CustomerUpdate(..)
    
  , ProductId(..), PriceId(..)
  , Product(..), ProductCreate(..)
  , Price(..), PriceRecurring(..), PriceCreate(..), PriceCreateRecurring(..)
    
  , SubscriptionId(..)
    
  , CustomerPortalId(..), CustomerPortal(..), CustomerPortalCreate(..)
    
  , CheckoutSessionId(..), CheckoutSession(..), CheckoutSessionCreate(..), CheckoutSessionCreateLineItem(..)
    
  , EventId(..), Event(..), EventData(..)
  )
where
import Stripe.Util.Aeson
import Data.Maybe
import Data.Time
import Data.Time.Clock.POSIX
import GHC.Generics
import Servant.API
import Text.Casing (quietSnake)
import Web.FormUrlEncoded
import qualified Data.Aeson as A
import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T
import qualified Data.Vector as V
formOptions :: Int -> FormOptions
formOptions :: Int -> FormOptions
formOptions Int
x =
  FormOptions :: (String -> String) -> FormOptions
FormOptions
  { fieldLabelModifier :: String -> String
fieldLabelModifier = String -> String
quietSnake (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
x }
newtype TimeStamp
  = TimeStamp { TimeStamp -> UTCTime
unTimeStamp :: UTCTime }
  deriving (Int -> TimeStamp -> String -> String
[TimeStamp] -> String -> String
TimeStamp -> String
(Int -> TimeStamp -> String -> String)
-> (TimeStamp -> String)
-> ([TimeStamp] -> String -> String)
-> Show TimeStamp
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TimeStamp] -> String -> String
$cshowList :: [TimeStamp] -> String -> String
show :: TimeStamp -> String
$cshow :: TimeStamp -> String
showsPrec :: Int -> TimeStamp -> String -> String
$cshowsPrec :: Int -> TimeStamp -> String -> String
Show, TimeStamp -> TimeStamp -> Bool
(TimeStamp -> TimeStamp -> Bool)
-> (TimeStamp -> TimeStamp -> Bool) -> Eq TimeStamp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeStamp -> TimeStamp -> Bool
$c/= :: TimeStamp -> TimeStamp -> Bool
== :: TimeStamp -> TimeStamp -> Bool
$c== :: TimeStamp -> TimeStamp -> Bool
Eq)
instance A.ToJSON TimeStamp where
  toJSON :: TimeStamp -> Value
toJSON = Scientific -> Value
A.Number (Scientific -> Value)
-> (TimeStamp -> Scientific) -> TimeStamp -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Scientific
forall a. Fractional a => Rational -> a
fromRational (Rational -> Scientific)
-> (TimeStamp -> Rational) -> TimeStamp -> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> Rational
forall a. Real a => a -> Rational
toRational (POSIXTime -> Rational)
-> (TimeStamp -> POSIXTime) -> TimeStamp -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> POSIXTime
utcTimeToPOSIXSeconds (UTCTime -> POSIXTime)
-> (TimeStamp -> UTCTime) -> TimeStamp -> POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeStamp -> UTCTime
unTimeStamp
instance A.FromJSON TimeStamp where
  parseJSON :: Value -> Parser TimeStamp
parseJSON =
    String
-> (Scientific -> Parser TimeStamp) -> Value -> Parser TimeStamp
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
A.withScientific String
"unix timestamp" ((Scientific -> Parser TimeStamp) -> Value -> Parser TimeStamp)
-> (Scientific -> Parser TimeStamp) -> Value -> Parser TimeStamp
forall a b. (a -> b) -> a -> b
$ \Scientific
sci ->
    TimeStamp -> Parser TimeStamp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TimeStamp -> Parser TimeStamp) -> TimeStamp -> Parser TimeStamp
forall a b. (a -> b) -> a -> b
$ UTCTime -> TimeStamp
TimeStamp (UTCTime -> TimeStamp) -> UTCTime -> TimeStamp
forall a b. (a -> b) -> a -> b
$ POSIXTime -> UTCTime
posixSecondsToUTCTime (Rational -> POSIXTime
forall a. Fractional a => Rational -> a
fromRational (Rational -> POSIXTime) -> Rational -> POSIXTime
forall a b. (a -> b) -> a -> b
$ Scientific -> Rational
forall a. Real a => a -> Rational
toRational Scientific
sci)
data StripeList a
  = StripeList
  { StripeList a -> Bool
slHasMore :: Bool
  , StripeList a -> Vector a
slData :: V.Vector a
  } deriving (Int -> StripeList a -> String -> String
[StripeList a] -> String -> String
StripeList a -> String
(Int -> StripeList a -> String -> String)
-> (StripeList a -> String)
-> ([StripeList a] -> String -> String)
-> Show (StripeList a)
forall a. Show a => Int -> StripeList a -> String -> String
forall a. Show a => [StripeList a] -> String -> String
forall a. Show a => StripeList a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StripeList a] -> String -> String
$cshowList :: forall a. Show a => [StripeList a] -> String -> String
show :: StripeList a -> String
$cshow :: forall a. Show a => StripeList a -> String
showsPrec :: Int -> StripeList a -> String -> String
$cshowsPrec :: forall a. Show a => Int -> StripeList a -> String -> String
Show, StripeList a -> StripeList a -> Bool
(StripeList a -> StripeList a -> Bool)
-> (StripeList a -> StripeList a -> Bool) -> Eq (StripeList a)
forall a. Eq a => StripeList a -> StripeList a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StripeList a -> StripeList a -> Bool
$c/= :: forall a. Eq a => StripeList a -> StripeList a -> Bool
== :: StripeList a -> StripeList a -> Bool
$c== :: forall a. Eq a => StripeList a -> StripeList a -> Bool
Eq)
newtype CustomerId
  = CustomerId { CustomerId -> Text
unCustomerId :: T.Text }
  deriving (Int -> CustomerId -> String -> String
[CustomerId] -> String -> String
CustomerId -> String
(Int -> CustomerId -> String -> String)
-> (CustomerId -> String)
-> ([CustomerId] -> String -> String)
-> Show CustomerId
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CustomerId] -> String -> String
$cshowList :: [CustomerId] -> String -> String
show :: CustomerId -> String
$cshow :: CustomerId -> String
showsPrec :: Int -> CustomerId -> String -> String
$cshowsPrec :: Int -> CustomerId -> String -> String
Show, CustomerId -> CustomerId -> Bool
(CustomerId -> CustomerId -> Bool)
-> (CustomerId -> CustomerId -> Bool) -> Eq CustomerId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerId -> CustomerId -> Bool
$c/= :: CustomerId -> CustomerId -> Bool
== :: CustomerId -> CustomerId -> Bool
$c== :: CustomerId -> CustomerId -> Bool
Eq, [CustomerId] -> Encoding
[CustomerId] -> Value
CustomerId -> Encoding
CustomerId -> Value
(CustomerId -> Value)
-> (CustomerId -> Encoding)
-> ([CustomerId] -> Value)
-> ([CustomerId] -> Encoding)
-> ToJSON CustomerId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CustomerId] -> Encoding
$ctoEncodingList :: [CustomerId] -> Encoding
toJSONList :: [CustomerId] -> Value
$ctoJSONList :: [CustomerId] -> Value
toEncoding :: CustomerId -> Encoding
$ctoEncoding :: CustomerId -> Encoding
toJSON :: CustomerId -> Value
$ctoJSON :: CustomerId -> Value
ToJSON, Value -> Parser [CustomerId]
Value -> Parser CustomerId
(Value -> Parser CustomerId)
-> (Value -> Parser [CustomerId]) -> FromJSON CustomerId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CustomerId]
$cparseJSONList :: Value -> Parser [CustomerId]
parseJSON :: Value -> Parser CustomerId
$cparseJSON :: Value -> Parser CustomerId
FromJSON, CustomerId -> ByteString
CustomerId -> Builder
CustomerId -> Text
(CustomerId -> Text)
-> (CustomerId -> Builder)
-> (CustomerId -> ByteString)
-> (CustomerId -> Text)
-> ToHttpApiData CustomerId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: CustomerId -> Text
$ctoQueryParam :: CustomerId -> Text
toHeader :: CustomerId -> ByteString
$ctoHeader :: CustomerId -> ByteString
toEncodedUrlPiece :: CustomerId -> Builder
$ctoEncodedUrlPiece :: CustomerId -> Builder
toUrlPiece :: CustomerId -> Text
$ctoUrlPiece :: CustomerId -> Text
ToHttpApiData)
data Customer
  = Customer
  { Customer -> CustomerId
cId :: CustomerId
  , Customer -> Bool
cLivemode :: Bool
  , Customer -> TimeStamp
cCreated :: TimeStamp
  , Customer -> Maybe Text
cName :: Maybe T.Text
  , Customer -> Maybe Text
cEmail :: Maybe T.Text
  } deriving (Int -> Customer -> String -> String
[Customer] -> String -> String
Customer -> String
(Int -> Customer -> String -> String)
-> (Customer -> String)
-> ([Customer] -> String -> String)
-> Show Customer
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Customer] -> String -> String
$cshowList :: [Customer] -> String -> String
show :: Customer -> String
$cshow :: Customer -> String
showsPrec :: Int -> Customer -> String -> String
$cshowsPrec :: Int -> Customer -> String -> String
Show, Customer -> Customer -> Bool
(Customer -> Customer -> Bool)
-> (Customer -> Customer -> Bool) -> Eq Customer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Customer -> Customer -> Bool
$c/= :: Customer -> Customer -> Bool
== :: Customer -> Customer -> Bool
$c== :: Customer -> Customer -> Bool
Eq)
data CustomerCreate
  = CustomerCreate
  { CustomerCreate -> Maybe Text
ccName :: Maybe T.Text
  , CustomerCreate -> Maybe Text
ccEmail :: Maybe T.Text
  } deriving (Int -> CustomerCreate -> String -> String
[CustomerCreate] -> String -> String
CustomerCreate -> String
(Int -> CustomerCreate -> String -> String)
-> (CustomerCreate -> String)
-> ([CustomerCreate] -> String -> String)
-> Show CustomerCreate
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CustomerCreate] -> String -> String
$cshowList :: [CustomerCreate] -> String -> String
show :: CustomerCreate -> String
$cshow :: CustomerCreate -> String
showsPrec :: Int -> CustomerCreate -> String -> String
$cshowsPrec :: Int -> CustomerCreate -> String -> String
Show, CustomerCreate -> CustomerCreate -> Bool
(CustomerCreate -> CustomerCreate -> Bool)
-> (CustomerCreate -> CustomerCreate -> Bool) -> Eq CustomerCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerCreate -> CustomerCreate -> Bool
$c/= :: CustomerCreate -> CustomerCreate -> Bool
== :: CustomerCreate -> CustomerCreate -> Bool
$c== :: CustomerCreate -> CustomerCreate -> Bool
Eq, (forall x. CustomerCreate -> Rep CustomerCreate x)
-> (forall x. Rep CustomerCreate x -> CustomerCreate)
-> Generic CustomerCreate
forall x. Rep CustomerCreate x -> CustomerCreate
forall x. CustomerCreate -> Rep CustomerCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomerCreate x -> CustomerCreate
$cfrom :: forall x. CustomerCreate -> Rep CustomerCreate x
Generic)
data CustomerUpdate
  = CustomerUpdate
  { CustomerUpdate -> Maybe Text
cuName :: Maybe T.Text
  , CustomerUpdate -> Maybe Text
cuEmail :: Maybe T.Text
  } deriving (Int -> CustomerUpdate -> String -> String
[CustomerUpdate] -> String -> String
CustomerUpdate -> String
(Int -> CustomerUpdate -> String -> String)
-> (CustomerUpdate -> String)
-> ([CustomerUpdate] -> String -> String)
-> Show CustomerUpdate
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CustomerUpdate] -> String -> String
$cshowList :: [CustomerUpdate] -> String -> String
show :: CustomerUpdate -> String
$cshow :: CustomerUpdate -> String
showsPrec :: Int -> CustomerUpdate -> String -> String
$cshowsPrec :: Int -> CustomerUpdate -> String -> String
Show, CustomerUpdate -> CustomerUpdate -> Bool
(CustomerUpdate -> CustomerUpdate -> Bool)
-> (CustomerUpdate -> CustomerUpdate -> Bool) -> Eq CustomerUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerUpdate -> CustomerUpdate -> Bool
$c/= :: CustomerUpdate -> CustomerUpdate -> Bool
== :: CustomerUpdate -> CustomerUpdate -> Bool
$c== :: CustomerUpdate -> CustomerUpdate -> Bool
Eq, (forall x. CustomerUpdate -> Rep CustomerUpdate x)
-> (forall x. Rep CustomerUpdate x -> CustomerUpdate)
-> Generic CustomerUpdate
forall x. Rep CustomerUpdate x -> CustomerUpdate
forall x. CustomerUpdate -> Rep CustomerUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomerUpdate x -> CustomerUpdate
$cfrom :: forall x. CustomerUpdate -> Rep CustomerUpdate x
Generic)
newtype EventId
  = EventId { EventId -> Text
unEventId :: T.Text }
  deriving (Int -> EventId -> String -> String
[EventId] -> String -> String
EventId -> String
(Int -> EventId -> String -> String)
-> (EventId -> String)
-> ([EventId] -> String -> String)
-> Show EventId
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EventId] -> String -> String
$cshowList :: [EventId] -> String -> String
show :: EventId -> String
$cshow :: EventId -> String
showsPrec :: Int -> EventId -> String -> String
$cshowsPrec :: Int -> EventId -> String -> String
Show, EventId -> EventId -> Bool
(EventId -> EventId -> Bool)
-> (EventId -> EventId -> Bool) -> Eq EventId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventId -> EventId -> Bool
$c/= :: EventId -> EventId -> Bool
== :: EventId -> EventId -> Bool
$c== :: EventId -> EventId -> Bool
Eq, [EventId] -> Encoding
[EventId] -> Value
EventId -> Encoding
EventId -> Value
(EventId -> Value)
-> (EventId -> Encoding)
-> ([EventId] -> Value)
-> ([EventId] -> Encoding)
-> ToJSON EventId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [EventId] -> Encoding
$ctoEncodingList :: [EventId] -> Encoding
toJSONList :: [EventId] -> Value
$ctoJSONList :: [EventId] -> Value
toEncoding :: EventId -> Encoding
$ctoEncoding :: EventId -> Encoding
toJSON :: EventId -> Value
$ctoJSON :: EventId -> Value
ToJSON, Value -> Parser [EventId]
Value -> Parser EventId
(Value -> Parser EventId)
-> (Value -> Parser [EventId]) -> FromJSON EventId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EventId]
$cparseJSONList :: Value -> Parser [EventId]
parseJSON :: Value -> Parser EventId
$cparseJSON :: Value -> Parser EventId
FromJSON, EventId -> ByteString
EventId -> Builder
EventId -> Text
(EventId -> Text)
-> (EventId -> Builder)
-> (EventId -> ByteString)
-> (EventId -> Text)
-> ToHttpApiData EventId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: EventId -> Text
$ctoQueryParam :: EventId -> Text
toHeader :: EventId -> ByteString
$ctoHeader :: EventId -> ByteString
toEncodedUrlPiece :: EventId -> Builder
$ctoEncodedUrlPiece :: EventId -> Builder
toUrlPiece :: EventId -> Text
$ctoUrlPiece :: EventId -> Text
ToHttpApiData)
data Event
  = Event
  { Event -> EventId
eId :: EventId
  , Event -> TimeStamp
eCreated :: TimeStamp
  , Event -> Bool
eLivemode :: Bool
  , Event -> Text
eType :: T.Text
  , Event -> Text
eApiVersion :: T.Text
  , Event -> EventData
eData :: EventData
  } deriving (Int -> Event -> String -> String
[Event] -> String -> String
Event -> String
(Int -> Event -> String -> String)
-> (Event -> String) -> ([Event] -> String -> String) -> Show Event
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Event] -> String -> String
$cshowList :: [Event] -> String -> String
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> String -> String
$cshowsPrec :: Int -> Event -> String -> String
Show, Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq)
data EventData
  = EventData
  { EventData -> Value
edObject :: A.Value
  } deriving (Int -> EventData -> String -> String
[EventData] -> String -> String
EventData -> String
(Int -> EventData -> String -> String)
-> (EventData -> String)
-> ([EventData] -> String -> String)
-> Show EventData
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EventData] -> String -> String
$cshowList :: [EventData] -> String -> String
show :: EventData -> String
$cshow :: EventData -> String
showsPrec :: Int -> EventData -> String -> String
$cshowsPrec :: Int -> EventData -> String -> String
Show, EventData -> EventData -> Bool
(EventData -> EventData -> Bool)
-> (EventData -> EventData -> Bool) -> Eq EventData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventData -> EventData -> Bool
$c/= :: EventData -> EventData -> Bool
== :: EventData -> EventData -> Bool
$c== :: EventData -> EventData -> Bool
Eq)
newtype PriceId
  = PriceId { PriceId -> Text
unPriceId :: T.Text }
  deriving (Int -> PriceId -> String -> String
[PriceId] -> String -> String
PriceId -> String
(Int -> PriceId -> String -> String)
-> (PriceId -> String)
-> ([PriceId] -> String -> String)
-> Show PriceId
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PriceId] -> String -> String
$cshowList :: [PriceId] -> String -> String
show :: PriceId -> String
$cshow :: PriceId -> String
showsPrec :: Int -> PriceId -> String -> String
$cshowsPrec :: Int -> PriceId -> String -> String
Show, PriceId -> PriceId -> Bool
(PriceId -> PriceId -> Bool)
-> (PriceId -> PriceId -> Bool) -> Eq PriceId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PriceId -> PriceId -> Bool
$c/= :: PriceId -> PriceId -> Bool
== :: PriceId -> PriceId -> Bool
$c== :: PriceId -> PriceId -> Bool
Eq, [PriceId] -> Encoding
[PriceId] -> Value
PriceId -> Encoding
PriceId -> Value
(PriceId -> Value)
-> (PriceId -> Encoding)
-> ([PriceId] -> Value)
-> ([PriceId] -> Encoding)
-> ToJSON PriceId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PriceId] -> Encoding
$ctoEncodingList :: [PriceId] -> Encoding
toJSONList :: [PriceId] -> Value
$ctoJSONList :: [PriceId] -> Value
toEncoding :: PriceId -> Encoding
$ctoEncoding :: PriceId -> Encoding
toJSON :: PriceId -> Value
$ctoJSON :: PriceId -> Value
ToJSON, Value -> Parser [PriceId]
Value -> Parser PriceId
(Value -> Parser PriceId)
-> (Value -> Parser [PriceId]) -> FromJSON PriceId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PriceId]
$cparseJSONList :: Value -> Parser [PriceId]
parseJSON :: Value -> Parser PriceId
$cparseJSON :: Value -> Parser PriceId
FromJSON, PriceId -> ByteString
PriceId -> Builder
PriceId -> Text
(PriceId -> Text)
-> (PriceId -> Builder)
-> (PriceId -> ByteString)
-> (PriceId -> Text)
-> ToHttpApiData PriceId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: PriceId -> Text
$ctoQueryParam :: PriceId -> Text
toHeader :: PriceId -> ByteString
$ctoHeader :: PriceId -> ByteString
toEncodedUrlPiece :: PriceId -> Builder
$ctoEncodedUrlPiece :: PriceId -> Builder
toUrlPiece :: PriceId -> Text
$ctoUrlPiece :: PriceId -> Text
ToHttpApiData)
data Price
  = Price
  { Price -> PriceId
pId :: PriceId
  , Price -> Bool
pActive :: Bool
  , Price -> Text
pCurrency :: T.Text
  , Price -> Maybe Text
pNickname :: Maybe T.Text
  , Price -> Text
pType :: T.Text 
  , Price -> Maybe PriceRecurring
pRecurring :: Maybe PriceRecurring
  , Price -> Maybe Int
pUnitAmount :: Maybe Int
  , Price -> ProductId
pProduct :: ProductId
  , Price -> Maybe Text
pLookupKey :: Maybe T.Text
  } deriving (Int -> Price -> String -> String
[Price] -> String -> String
Price -> String
(Int -> Price -> String -> String)
-> (Price -> String) -> ([Price] -> String -> String) -> Show Price
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Price] -> String -> String
$cshowList :: [Price] -> String -> String
show :: Price -> String
$cshow :: Price -> String
showsPrec :: Int -> Price -> String -> String
$cshowsPrec :: Int -> Price -> String -> String
Show, Price -> Price -> Bool
(Price -> Price -> Bool) -> (Price -> Price -> Bool) -> Eq Price
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Price -> Price -> Bool
$c/= :: Price -> Price -> Bool
== :: Price -> Price -> Bool
$c== :: Price -> Price -> Bool
Eq)
data PriceRecurring
  = PriceRecurring
  { PriceRecurring -> Text
prInterval :: T.Text 
  , PriceRecurring -> Int
prIntervalCount :: Int
  } deriving (Int -> PriceRecurring -> String -> String
[PriceRecurring] -> String -> String
PriceRecurring -> String
(Int -> PriceRecurring -> String -> String)
-> (PriceRecurring -> String)
-> ([PriceRecurring] -> String -> String)
-> Show PriceRecurring
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PriceRecurring] -> String -> String
$cshowList :: [PriceRecurring] -> String -> String
show :: PriceRecurring -> String
$cshow :: PriceRecurring -> String
showsPrec :: Int -> PriceRecurring -> String -> String
$cshowsPrec :: Int -> PriceRecurring -> String -> String
Show, PriceRecurring -> PriceRecurring -> Bool
(PriceRecurring -> PriceRecurring -> Bool)
-> (PriceRecurring -> PriceRecurring -> Bool) -> Eq PriceRecurring
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PriceRecurring -> PriceRecurring -> Bool
$c/= :: PriceRecurring -> PriceRecurring -> Bool
== :: PriceRecurring -> PriceRecurring -> Bool
$c== :: PriceRecurring -> PriceRecurring -> Bool
Eq)
data PriceCreate
  = PriceCreate
  { PriceCreate -> Text
pcCurrency :: T.Text
  , PriceCreate -> Maybe Int
pcUnitAmount :: Maybe Int
  , PriceCreate -> ProductId
pcProduct :: ProductId
  , PriceCreate -> Maybe Text
pcLookupKey :: Maybe T.Text
  , PriceCreate -> Bool
pcTransferLookupKey :: Bool
  , PriceCreate -> Maybe PriceCreateRecurring
pcRecurring :: Maybe PriceCreateRecurring
  } deriving (Int -> PriceCreate -> String -> String
[PriceCreate] -> String -> String
PriceCreate -> String
(Int -> PriceCreate -> String -> String)
-> (PriceCreate -> String)
-> ([PriceCreate] -> String -> String)
-> Show PriceCreate
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PriceCreate] -> String -> String
$cshowList :: [PriceCreate] -> String -> String
show :: PriceCreate -> String
$cshow :: PriceCreate -> String
showsPrec :: Int -> PriceCreate -> String -> String
$cshowsPrec :: Int -> PriceCreate -> String -> String
Show, PriceCreate -> PriceCreate -> Bool
(PriceCreate -> PriceCreate -> Bool)
-> (PriceCreate -> PriceCreate -> Bool) -> Eq PriceCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PriceCreate -> PriceCreate -> Bool
$c/= :: PriceCreate -> PriceCreate -> Bool
== :: PriceCreate -> PriceCreate -> Bool
$c== :: PriceCreate -> PriceCreate -> Bool
Eq, (forall x. PriceCreate -> Rep PriceCreate x)
-> (forall x. Rep PriceCreate x -> PriceCreate)
-> Generic PriceCreate
forall x. Rep PriceCreate x -> PriceCreate
forall x. PriceCreate -> Rep PriceCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PriceCreate x -> PriceCreate
$cfrom :: forall x. PriceCreate -> Rep PriceCreate x
Generic)
data PriceCreateRecurring
  = PriceCreateRecurring
  { PriceCreateRecurring -> Text
prcInterval :: T.Text 
  , PriceCreateRecurring -> Maybe Int
prcIntervalCount :: Maybe Int
  } deriving (Int -> PriceCreateRecurring -> String -> String
[PriceCreateRecurring] -> String -> String
PriceCreateRecurring -> String
(Int -> PriceCreateRecurring -> String -> String)
-> (PriceCreateRecurring -> String)
-> ([PriceCreateRecurring] -> String -> String)
-> Show PriceCreateRecurring
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PriceCreateRecurring] -> String -> String
$cshowList :: [PriceCreateRecurring] -> String -> String
show :: PriceCreateRecurring -> String
$cshow :: PriceCreateRecurring -> String
showsPrec :: Int -> PriceCreateRecurring -> String -> String
$cshowsPrec :: Int -> PriceCreateRecurring -> String -> String
Show, PriceCreateRecurring -> PriceCreateRecurring -> Bool
(PriceCreateRecurring -> PriceCreateRecurring -> Bool)
-> (PriceCreateRecurring -> PriceCreateRecurring -> Bool)
-> Eq PriceCreateRecurring
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PriceCreateRecurring -> PriceCreateRecurring -> Bool
$c/= :: PriceCreateRecurring -> PriceCreateRecurring -> Bool
== :: PriceCreateRecurring -> PriceCreateRecurring -> Bool
$c== :: PriceCreateRecurring -> PriceCreateRecurring -> Bool
Eq)
newtype ProductId
  = ProductId { ProductId -> Text
unProductId :: T.Text }
  deriving (Int -> ProductId -> String -> String
[ProductId] -> String -> String
ProductId -> String
(Int -> ProductId -> String -> String)
-> (ProductId -> String)
-> ([ProductId] -> String -> String)
-> Show ProductId
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ProductId] -> String -> String
$cshowList :: [ProductId] -> String -> String
show :: ProductId -> String
$cshow :: ProductId -> String
showsPrec :: Int -> ProductId -> String -> String
$cshowsPrec :: Int -> ProductId -> String -> String
Show, ProductId -> ProductId -> Bool
(ProductId -> ProductId -> Bool)
-> (ProductId -> ProductId -> Bool) -> Eq ProductId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProductId -> ProductId -> Bool
$c/= :: ProductId -> ProductId -> Bool
== :: ProductId -> ProductId -> Bool
$c== :: ProductId -> ProductId -> Bool
Eq, [ProductId] -> Encoding
[ProductId] -> Value
ProductId -> Encoding
ProductId -> Value
(ProductId -> Value)
-> (ProductId -> Encoding)
-> ([ProductId] -> Value)
-> ([ProductId] -> Encoding)
-> ToJSON ProductId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ProductId] -> Encoding
$ctoEncodingList :: [ProductId] -> Encoding
toJSONList :: [ProductId] -> Value
$ctoJSONList :: [ProductId] -> Value
toEncoding :: ProductId -> Encoding
$ctoEncoding :: ProductId -> Encoding
toJSON :: ProductId -> Value
$ctoJSON :: ProductId -> Value
ToJSON, Value -> Parser [ProductId]
Value -> Parser ProductId
(Value -> Parser ProductId)
-> (Value -> Parser [ProductId]) -> FromJSON ProductId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ProductId]
$cparseJSONList :: Value -> Parser [ProductId]
parseJSON :: Value -> Parser ProductId
$cparseJSON :: Value -> Parser ProductId
FromJSON, ProductId -> ByteString
ProductId -> Builder
ProductId -> Text
(ProductId -> Text)
-> (ProductId -> Builder)
-> (ProductId -> ByteString)
-> (ProductId -> Text)
-> ToHttpApiData ProductId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: ProductId -> Text
$ctoQueryParam :: ProductId -> Text
toHeader :: ProductId -> ByteString
$ctoHeader :: ProductId -> ByteString
toEncodedUrlPiece :: ProductId -> Builder
$ctoEncodedUrlPiece :: ProductId -> Builder
toUrlPiece :: ProductId -> Text
$ctoUrlPiece :: ProductId -> Text
ToHttpApiData)
data Product
  = Product
  { Product -> ProductId
prId :: ProductId
  , Product -> Bool
prActive :: Bool
  , Product -> Text
prName :: T.Text
  , Product -> Maybe Text
prDescription :: Maybe T.Text
  } deriving (Int -> Product -> String -> String
[Product] -> String -> String
Product -> String
(Int -> Product -> String -> String)
-> (Product -> String)
-> ([Product] -> String -> String)
-> Show Product
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Product] -> String -> String
$cshowList :: [Product] -> String -> String
show :: Product -> String
$cshow :: Product -> String
showsPrec :: Int -> Product -> String -> String
$cshowsPrec :: Int -> Product -> String -> String
Show, Product -> Product -> Bool
(Product -> Product -> Bool)
-> (Product -> Product -> Bool) -> Eq Product
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Product -> Product -> Bool
$c/= :: Product -> Product -> Bool
== :: Product -> Product -> Bool
$c== :: Product -> Product -> Bool
Eq)
data ProductCreate
  = ProductCreate
  { ProductCreate -> Text
prcName :: T.Text
  , ProductCreate -> Maybe Text
prcDescription :: Maybe T.Text
  } deriving (Int -> ProductCreate -> String -> String
[ProductCreate] -> String -> String
ProductCreate -> String
(Int -> ProductCreate -> String -> String)
-> (ProductCreate -> String)
-> ([ProductCreate] -> String -> String)
-> Show ProductCreate
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ProductCreate] -> String -> String
$cshowList :: [ProductCreate] -> String -> String
show :: ProductCreate -> String
$cshow :: ProductCreate -> String
showsPrec :: Int -> ProductCreate -> String -> String
$cshowsPrec :: Int -> ProductCreate -> String -> String
Show, ProductCreate -> ProductCreate -> Bool
(ProductCreate -> ProductCreate -> Bool)
-> (ProductCreate -> ProductCreate -> Bool) -> Eq ProductCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProductCreate -> ProductCreate -> Bool
$c/= :: ProductCreate -> ProductCreate -> Bool
== :: ProductCreate -> ProductCreate -> Bool
$c== :: ProductCreate -> ProductCreate -> Bool
Eq, (forall x. ProductCreate -> Rep ProductCreate x)
-> (forall x. Rep ProductCreate x -> ProductCreate)
-> Generic ProductCreate
forall x. Rep ProductCreate x -> ProductCreate
forall x. ProductCreate -> Rep ProductCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProductCreate x -> ProductCreate
$cfrom :: forall x. ProductCreate -> Rep ProductCreate x
Generic)
newtype SubscriptionId
  = SubscriptionId { SubscriptionId -> Text
unSubscriptionId :: T.Text }
  deriving (Int -> SubscriptionId -> String -> String
[SubscriptionId] -> String -> String
SubscriptionId -> String
(Int -> SubscriptionId -> String -> String)
-> (SubscriptionId -> String)
-> ([SubscriptionId] -> String -> String)
-> Show SubscriptionId
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SubscriptionId] -> String -> String
$cshowList :: [SubscriptionId] -> String -> String
show :: SubscriptionId -> String
$cshow :: SubscriptionId -> String
showsPrec :: Int -> SubscriptionId -> String -> String
$cshowsPrec :: Int -> SubscriptionId -> String -> String
Show, SubscriptionId -> SubscriptionId -> Bool
(SubscriptionId -> SubscriptionId -> Bool)
-> (SubscriptionId -> SubscriptionId -> Bool) -> Eq SubscriptionId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionId -> SubscriptionId -> Bool
$c/= :: SubscriptionId -> SubscriptionId -> Bool
== :: SubscriptionId -> SubscriptionId -> Bool
$c== :: SubscriptionId -> SubscriptionId -> Bool
Eq, [SubscriptionId] -> Encoding
[SubscriptionId] -> Value
SubscriptionId -> Encoding
SubscriptionId -> Value
(SubscriptionId -> Value)
-> (SubscriptionId -> Encoding)
-> ([SubscriptionId] -> Value)
-> ([SubscriptionId] -> Encoding)
-> ToJSON SubscriptionId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SubscriptionId] -> Encoding
$ctoEncodingList :: [SubscriptionId] -> Encoding
toJSONList :: [SubscriptionId] -> Value
$ctoJSONList :: [SubscriptionId] -> Value
toEncoding :: SubscriptionId -> Encoding
$ctoEncoding :: SubscriptionId -> Encoding
toJSON :: SubscriptionId -> Value
$ctoJSON :: SubscriptionId -> Value
ToJSON, Value -> Parser [SubscriptionId]
Value -> Parser SubscriptionId
(Value -> Parser SubscriptionId)
-> (Value -> Parser [SubscriptionId]) -> FromJSON SubscriptionId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SubscriptionId]
$cparseJSONList :: Value -> Parser [SubscriptionId]
parseJSON :: Value -> Parser SubscriptionId
$cparseJSON :: Value -> Parser SubscriptionId
FromJSON, SubscriptionId -> ByteString
SubscriptionId -> Builder
SubscriptionId -> Text
(SubscriptionId -> Text)
-> (SubscriptionId -> Builder)
-> (SubscriptionId -> ByteString)
-> (SubscriptionId -> Text)
-> ToHttpApiData SubscriptionId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: SubscriptionId -> Text
$ctoQueryParam :: SubscriptionId -> Text
toHeader :: SubscriptionId -> ByteString
$ctoHeader :: SubscriptionId -> ByteString
toEncodedUrlPiece :: SubscriptionId -> Builder
$ctoEncodedUrlPiece :: SubscriptionId -> Builder
toUrlPiece :: SubscriptionId -> Text
$ctoUrlPiece :: SubscriptionId -> Text
ToHttpApiData)
newtype CheckoutSessionId
  = CheckoutSessionId { CheckoutSessionId -> Text
unCheckoutSessionId :: T.Text }
  deriving (Int -> CheckoutSessionId -> String -> String
[CheckoutSessionId] -> String -> String
CheckoutSessionId -> String
(Int -> CheckoutSessionId -> String -> String)
-> (CheckoutSessionId -> String)
-> ([CheckoutSessionId] -> String -> String)
-> Show CheckoutSessionId
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CheckoutSessionId] -> String -> String
$cshowList :: [CheckoutSessionId] -> String -> String
show :: CheckoutSessionId -> String
$cshow :: CheckoutSessionId -> String
showsPrec :: Int -> CheckoutSessionId -> String -> String
$cshowsPrec :: Int -> CheckoutSessionId -> String -> String
Show, CheckoutSessionId -> CheckoutSessionId -> Bool
(CheckoutSessionId -> CheckoutSessionId -> Bool)
-> (CheckoutSessionId -> CheckoutSessionId -> Bool)
-> Eq CheckoutSessionId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckoutSessionId -> CheckoutSessionId -> Bool
$c/= :: CheckoutSessionId -> CheckoutSessionId -> Bool
== :: CheckoutSessionId -> CheckoutSessionId -> Bool
$c== :: CheckoutSessionId -> CheckoutSessionId -> Bool
Eq, [CheckoutSessionId] -> Encoding
[CheckoutSessionId] -> Value
CheckoutSessionId -> Encoding
CheckoutSessionId -> Value
(CheckoutSessionId -> Value)
-> (CheckoutSessionId -> Encoding)
-> ([CheckoutSessionId] -> Value)
-> ([CheckoutSessionId] -> Encoding)
-> ToJSON CheckoutSessionId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CheckoutSessionId] -> Encoding
$ctoEncodingList :: [CheckoutSessionId] -> Encoding
toJSONList :: [CheckoutSessionId] -> Value
$ctoJSONList :: [CheckoutSessionId] -> Value
toEncoding :: CheckoutSessionId -> Encoding
$ctoEncoding :: CheckoutSessionId -> Encoding
toJSON :: CheckoutSessionId -> Value
$ctoJSON :: CheckoutSessionId -> Value
ToJSON, Value -> Parser [CheckoutSessionId]
Value -> Parser CheckoutSessionId
(Value -> Parser CheckoutSessionId)
-> (Value -> Parser [CheckoutSessionId])
-> FromJSON CheckoutSessionId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CheckoutSessionId]
$cparseJSONList :: Value -> Parser [CheckoutSessionId]
parseJSON :: Value -> Parser CheckoutSessionId
$cparseJSON :: Value -> Parser CheckoutSessionId
FromJSON, CheckoutSessionId -> ByteString
CheckoutSessionId -> Builder
CheckoutSessionId -> Text
(CheckoutSessionId -> Text)
-> (CheckoutSessionId -> Builder)
-> (CheckoutSessionId -> ByteString)
-> (CheckoutSessionId -> Text)
-> ToHttpApiData CheckoutSessionId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: CheckoutSessionId -> Text
$ctoQueryParam :: CheckoutSessionId -> Text
toHeader :: CheckoutSessionId -> ByteString
$ctoHeader :: CheckoutSessionId -> ByteString
toEncodedUrlPiece :: CheckoutSessionId -> Builder
$ctoEncodedUrlPiece :: CheckoutSessionId -> Builder
toUrlPiece :: CheckoutSessionId -> Text
$ctoUrlPiece :: CheckoutSessionId -> Text
ToHttpApiData)
data CheckoutSession
  = CheckoutSession
  { CheckoutSession -> CheckoutSessionId
csId :: CheckoutSessionId
  , CheckoutSession -> Bool
csLivemode :: Bool
  , CheckoutSession -> Maybe Text
csClientReferenceId :: Maybe T.Text
  , CheckoutSession -> Text
csCancelUrl :: T.Text
  , CheckoutSession -> Text
csSuccessUrl :: T.Text
  , CheckoutSession -> Vector Text
csPaymentMethodTypes :: V.Vector T.Text  
  , CheckoutSession -> Maybe SubscriptionId
csSubscription :: Maybe SubscriptionId
  } deriving (Int -> CheckoutSession -> String -> String
[CheckoutSession] -> String -> String
CheckoutSession -> String
(Int -> CheckoutSession -> String -> String)
-> (CheckoutSession -> String)
-> ([CheckoutSession] -> String -> String)
-> Show CheckoutSession
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CheckoutSession] -> String -> String
$cshowList :: [CheckoutSession] -> String -> String
show :: CheckoutSession -> String
$cshow :: CheckoutSession -> String
showsPrec :: Int -> CheckoutSession -> String -> String
$cshowsPrec :: Int -> CheckoutSession -> String -> String
Show, CheckoutSession -> CheckoutSession -> Bool
(CheckoutSession -> CheckoutSession -> Bool)
-> (CheckoutSession -> CheckoutSession -> Bool)
-> Eq CheckoutSession
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckoutSession -> CheckoutSession -> Bool
$c/= :: CheckoutSession -> CheckoutSession -> Bool
== :: CheckoutSession -> CheckoutSession -> Bool
$c== :: CheckoutSession -> CheckoutSession -> Bool
Eq)
data CheckoutSessionCreate
  = CheckoutSessionCreate
  { CheckoutSessionCreate -> Text
cscCancelUrl :: T.Text
  , CheckoutSessionCreate -> Text
cscMode :: T.Text  
  , CheckoutSessionCreate -> [Text]
cscPaymentMethodTypes :: [T.Text]  
  , CheckoutSessionCreate -> Text
cscSuccessUrl :: T.Text
  , CheckoutSessionCreate -> Maybe Text
cscClientReferenceId :: Maybe T.Text
  , CheckoutSessionCreate -> Maybe CustomerId
cscCustomer :: Maybe CustomerId
  , CheckoutSessionCreate -> [CheckoutSessionCreateLineItem]
cscLineItems :: [CheckoutSessionCreateLineItem]
  } deriving (Int -> CheckoutSessionCreate -> String -> String
[CheckoutSessionCreate] -> String -> String
CheckoutSessionCreate -> String
(Int -> CheckoutSessionCreate -> String -> String)
-> (CheckoutSessionCreate -> String)
-> ([CheckoutSessionCreate] -> String -> String)
-> Show CheckoutSessionCreate
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CheckoutSessionCreate] -> String -> String
$cshowList :: [CheckoutSessionCreate] -> String -> String
show :: CheckoutSessionCreate -> String
$cshow :: CheckoutSessionCreate -> String
showsPrec :: Int -> CheckoutSessionCreate -> String -> String
$cshowsPrec :: Int -> CheckoutSessionCreate -> String -> String
Show, CheckoutSessionCreate -> CheckoutSessionCreate -> Bool
(CheckoutSessionCreate -> CheckoutSessionCreate -> Bool)
-> (CheckoutSessionCreate -> CheckoutSessionCreate -> Bool)
-> Eq CheckoutSessionCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckoutSessionCreate -> CheckoutSessionCreate -> Bool
$c/= :: CheckoutSessionCreate -> CheckoutSessionCreate -> Bool
== :: CheckoutSessionCreate -> CheckoutSessionCreate -> Bool
$c== :: CheckoutSessionCreate -> CheckoutSessionCreate -> Bool
Eq, (forall x. CheckoutSessionCreate -> Rep CheckoutSessionCreate x)
-> (forall x. Rep CheckoutSessionCreate x -> CheckoutSessionCreate)
-> Generic CheckoutSessionCreate
forall x. Rep CheckoutSessionCreate x -> CheckoutSessionCreate
forall x. CheckoutSessionCreate -> Rep CheckoutSessionCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckoutSessionCreate x -> CheckoutSessionCreate
$cfrom :: forall x. CheckoutSessionCreate -> Rep CheckoutSessionCreate x
Generic)
data CheckoutSessionCreateLineItem
  = CheckoutSessionCreateLineItem
  { CheckoutSessionCreateLineItem -> PriceId
cscliPrice :: PriceId
  , CheckoutSessionCreateLineItem -> Integer
cscliQuantity :: Integer
  } deriving (Int -> CheckoutSessionCreateLineItem -> String -> String
[CheckoutSessionCreateLineItem] -> String -> String
CheckoutSessionCreateLineItem -> String
(Int -> CheckoutSessionCreateLineItem -> String -> String)
-> (CheckoutSessionCreateLineItem -> String)
-> ([CheckoutSessionCreateLineItem] -> String -> String)
-> Show CheckoutSessionCreateLineItem
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CheckoutSessionCreateLineItem] -> String -> String
$cshowList :: [CheckoutSessionCreateLineItem] -> String -> String
show :: CheckoutSessionCreateLineItem -> String
$cshow :: CheckoutSessionCreateLineItem -> String
showsPrec :: Int -> CheckoutSessionCreateLineItem -> String -> String
$cshowsPrec :: Int -> CheckoutSessionCreateLineItem -> String -> String
Show, CheckoutSessionCreateLineItem
-> CheckoutSessionCreateLineItem -> Bool
(CheckoutSessionCreateLineItem
 -> CheckoutSessionCreateLineItem -> Bool)
-> (CheckoutSessionCreateLineItem
    -> CheckoutSessionCreateLineItem -> Bool)
-> Eq CheckoutSessionCreateLineItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckoutSessionCreateLineItem
-> CheckoutSessionCreateLineItem -> Bool
$c/= :: CheckoutSessionCreateLineItem
-> CheckoutSessionCreateLineItem -> Bool
== :: CheckoutSessionCreateLineItem
-> CheckoutSessionCreateLineItem -> Bool
$c== :: CheckoutSessionCreateLineItem
-> CheckoutSessionCreateLineItem -> Bool
Eq, (forall x.
 CheckoutSessionCreateLineItem
 -> Rep CheckoutSessionCreateLineItem x)
-> (forall x.
    Rep CheckoutSessionCreateLineItem x
    -> CheckoutSessionCreateLineItem)
-> Generic CheckoutSessionCreateLineItem
forall x.
Rep CheckoutSessionCreateLineItem x
-> CheckoutSessionCreateLineItem
forall x.
CheckoutSessionCreateLineItem
-> Rep CheckoutSessionCreateLineItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckoutSessionCreateLineItem x
-> CheckoutSessionCreateLineItem
$cfrom :: forall x.
CheckoutSessionCreateLineItem
-> Rep CheckoutSessionCreateLineItem x
Generic)
newtype CustomerPortalId
  = CustomerPortalId { CustomerPortalId -> Text
unCustomerPortalId :: T.Text }
  deriving (Int -> CustomerPortalId -> String -> String
[CustomerPortalId] -> String -> String
CustomerPortalId -> String
(Int -> CustomerPortalId -> String -> String)
-> (CustomerPortalId -> String)
-> ([CustomerPortalId] -> String -> String)
-> Show CustomerPortalId
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CustomerPortalId] -> String -> String
$cshowList :: [CustomerPortalId] -> String -> String
show :: CustomerPortalId -> String
$cshow :: CustomerPortalId -> String
showsPrec :: Int -> CustomerPortalId -> String -> String
$cshowsPrec :: Int -> CustomerPortalId -> String -> String
Show, CustomerPortalId -> CustomerPortalId -> Bool
(CustomerPortalId -> CustomerPortalId -> Bool)
-> (CustomerPortalId -> CustomerPortalId -> Bool)
-> Eq CustomerPortalId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerPortalId -> CustomerPortalId -> Bool
$c/= :: CustomerPortalId -> CustomerPortalId -> Bool
== :: CustomerPortalId -> CustomerPortalId -> Bool
$c== :: CustomerPortalId -> CustomerPortalId -> Bool
Eq, [CustomerPortalId] -> Encoding
[CustomerPortalId] -> Value
CustomerPortalId -> Encoding
CustomerPortalId -> Value
(CustomerPortalId -> Value)
-> (CustomerPortalId -> Encoding)
-> ([CustomerPortalId] -> Value)
-> ([CustomerPortalId] -> Encoding)
-> ToJSON CustomerPortalId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CustomerPortalId] -> Encoding
$ctoEncodingList :: [CustomerPortalId] -> Encoding
toJSONList :: [CustomerPortalId] -> Value
$ctoJSONList :: [CustomerPortalId] -> Value
toEncoding :: CustomerPortalId -> Encoding
$ctoEncoding :: CustomerPortalId -> Encoding
toJSON :: CustomerPortalId -> Value
$ctoJSON :: CustomerPortalId -> Value
ToJSON, Value -> Parser [CustomerPortalId]
Value -> Parser CustomerPortalId
(Value -> Parser CustomerPortalId)
-> (Value -> Parser [CustomerPortalId])
-> FromJSON CustomerPortalId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CustomerPortalId]
$cparseJSONList :: Value -> Parser [CustomerPortalId]
parseJSON :: Value -> Parser CustomerPortalId
$cparseJSON :: Value -> Parser CustomerPortalId
FromJSON, CustomerPortalId -> ByteString
CustomerPortalId -> Builder
CustomerPortalId -> Text
(CustomerPortalId -> Text)
-> (CustomerPortalId -> Builder)
-> (CustomerPortalId -> ByteString)
-> (CustomerPortalId -> Text)
-> ToHttpApiData CustomerPortalId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: CustomerPortalId -> Text
$ctoQueryParam :: CustomerPortalId -> Text
toHeader :: CustomerPortalId -> ByteString
$ctoHeader :: CustomerPortalId -> ByteString
toEncodedUrlPiece :: CustomerPortalId -> Builder
$ctoEncodedUrlPiece :: CustomerPortalId -> Builder
toUrlPiece :: CustomerPortalId -> Text
$ctoUrlPiece :: CustomerPortalId -> Text
ToHttpApiData)
data CustomerPortal
  = CustomerPortal
  { CustomerPortal -> CustomerPortalId
cpId :: CustomerPortalId
  , CustomerPortal -> Bool
cpLivemode :: Bool
  , CustomerPortal -> TimeStamp
cpCreated :: TimeStamp
  , CustomerPortal -> CustomerId
cpCustomer :: CustomerId
  , CustomerPortal -> Maybe Text
cpReturnUrl :: Maybe T.Text
  , CustomerPortal -> Text
cpUrl :: T.Text
  } deriving (Int -> CustomerPortal -> String -> String
[CustomerPortal] -> String -> String
CustomerPortal -> String
(Int -> CustomerPortal -> String -> String)
-> (CustomerPortal -> String)
-> ([CustomerPortal] -> String -> String)
-> Show CustomerPortal
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CustomerPortal] -> String -> String
$cshowList :: [CustomerPortal] -> String -> String
show :: CustomerPortal -> String
$cshow :: CustomerPortal -> String
showsPrec :: Int -> CustomerPortal -> String -> String
$cshowsPrec :: Int -> CustomerPortal -> String -> String
Show, CustomerPortal -> CustomerPortal -> Bool
(CustomerPortal -> CustomerPortal -> Bool)
-> (CustomerPortal -> CustomerPortal -> Bool) -> Eq CustomerPortal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerPortal -> CustomerPortal -> Bool
$c/= :: CustomerPortal -> CustomerPortal -> Bool
== :: CustomerPortal -> CustomerPortal -> Bool
$c== :: CustomerPortal -> CustomerPortal -> Bool
Eq)
data CustomerPortalCreate
  = CustomerPortalCreate
  { CustomerPortalCreate -> CustomerId
cpcCustomer :: CustomerId
  , CustomerPortalCreate -> Maybe Text
cpcReturnUrl :: Maybe T.Text
  } deriving (Int -> CustomerPortalCreate -> String -> String
[CustomerPortalCreate] -> String -> String
CustomerPortalCreate -> String
(Int -> CustomerPortalCreate -> String -> String)
-> (CustomerPortalCreate -> String)
-> ([CustomerPortalCreate] -> String -> String)
-> Show CustomerPortalCreate
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CustomerPortalCreate] -> String -> String
$cshowList :: [CustomerPortalCreate] -> String -> String
show :: CustomerPortalCreate -> String
$cshow :: CustomerPortalCreate -> String
showsPrec :: Int -> CustomerPortalCreate -> String -> String
$cshowsPrec :: Int -> CustomerPortalCreate -> String -> String
Show, CustomerPortalCreate -> CustomerPortalCreate -> Bool
(CustomerPortalCreate -> CustomerPortalCreate -> Bool)
-> (CustomerPortalCreate -> CustomerPortalCreate -> Bool)
-> Eq CustomerPortalCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomerPortalCreate -> CustomerPortalCreate -> Bool
$c/= :: CustomerPortalCreate -> CustomerPortalCreate -> Bool
== :: CustomerPortalCreate -> CustomerPortalCreate -> Bool
$c== :: CustomerPortalCreate -> CustomerPortalCreate -> Bool
Eq, (forall x. CustomerPortalCreate -> Rep CustomerPortalCreate x)
-> (forall x. Rep CustomerPortalCreate x -> CustomerPortalCreate)
-> Generic CustomerPortalCreate
forall x. Rep CustomerPortalCreate x -> CustomerPortalCreate
forall x. CustomerPortalCreate -> Rep CustomerPortalCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomerPortalCreate x -> CustomerPortalCreate
$cfrom :: forall x. CustomerPortalCreate -> Rep CustomerPortalCreate x
Generic)
$(deriveJSON (jsonOpts 2) ''StripeList)
$(deriveJSON (jsonOpts 1) ''Customer)
$(deriveJSON (jsonOpts 1) ''Event)
$(deriveJSON (jsonOpts 2) ''EventData)
$(deriveJSON (jsonOpts 2) ''CheckoutSession)
$(deriveJSON (jsonOpts 1) ''Price)
$(deriveJSON (jsonOpts 2) ''PriceRecurring)
$(deriveJSON (jsonOpts 2) ''Product)
$(deriveJSON (jsonOpts 2) ''CustomerPortal)
instance ToForm CustomerCreate where
  toForm :: CustomerCreate -> Form
toForm = FormOptions -> CustomerCreate -> Form
forall a.
(Generic a, GToForm a (Rep a)) =>
FormOptions -> a -> Form
genericToForm (Int -> FormOptions
formOptions Int
2)
instance ToForm CustomerUpdate where
  toForm :: CustomerUpdate -> Form
toForm = FormOptions -> CustomerUpdate -> Form
forall a.
(Generic a, GToForm a (Rep a)) =>
FormOptions -> a -> Form
genericToForm (Int -> FormOptions
formOptions Int
2)
instance ToForm CustomerPortalCreate where
  toForm :: CustomerPortalCreate -> Form
toForm = FormOptions -> CustomerPortalCreate -> Form
forall a.
(Generic a, GToForm a (Rep a)) =>
FormOptions -> a -> Form
genericToForm (Int -> FormOptions
formOptions Int
3)
instance ToForm ProductCreate where
  toForm :: ProductCreate -> Form
toForm = FormOptions -> ProductCreate -> Form
forall a.
(Generic a, GToForm a (Rep a)) =>
FormOptions -> a -> Form
genericToForm (Int -> FormOptions
formOptions Int
3)
instance ToForm PriceCreate where
  toForm :: PriceCreate -> Form
toForm PriceCreate
pc =
    let recurringPiece :: [(Text, [Text])]
recurringPiece =
          case PriceCreate -> Maybe PriceCreateRecurring
pcRecurring PriceCreate
pc of
            Maybe PriceCreateRecurring
Nothing -> []
            Just PriceCreateRecurring
x ->
              [ (Text
"recurring[interval]", [PriceCreateRecurring -> Text
prcInterval PriceCreateRecurring
x])
              , (Text
"recurring[interval_count]", Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ (Int -> Text) -> Maybe Int -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (Maybe Int -> Maybe Text) -> Maybe Int -> Maybe Text
forall a b. (a -> b) -> a -> b
$ PriceCreateRecurring -> Maybe Int
prcIntervalCount PriceCreateRecurring
x)
              ]
    in HashMap Text [Text] -> Form
Form (HashMap Text [Text] -> Form) -> HashMap Text [Text] -> Form
forall a b. (a -> b) -> a -> b
$ [(Text, [Text])] -> HashMap Text [Text]
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(Text, [Text])] -> HashMap Text [Text])
-> [(Text, [Text])] -> HashMap Text [Text]
forall a b. (a -> b) -> a -> b
$
       [ (Text
"currency", [PriceCreate -> Text
pcCurrency PriceCreate
pc])
       , (Text
"product", [ProductId -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (ProductId -> Text) -> ProductId -> Text
forall a b. (a -> b) -> a -> b
$ PriceCreate -> ProductId
pcProduct PriceCreate
pc])
       , (Text
"unit_amount", Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ (Int -> Text) -> Maybe Int -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (Maybe Int -> Maybe Text) -> Maybe Int -> Maybe Text
forall a b. (a -> b) -> a -> b
$ PriceCreate -> Maybe Int
pcUnitAmount PriceCreate
pc)
       , (Text
"lookup_key", Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ PriceCreate -> Maybe Text
pcLookupKey PriceCreate
pc)
       , (Text
"transfer_lookup_key", [Bool -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (Bool -> Text) -> Bool -> Text
forall a b. (a -> b) -> a -> b
$ PriceCreate -> Bool
pcTransferLookupKey PriceCreate
pc])
       ] [(Text, [Text])] -> [(Text, [Text])] -> [(Text, [Text])]
forall a. Semigroup a => a -> a -> a
<> [(Text, [Text])]
recurringPiece
instance ToForm CheckoutSessionCreate where
  toForm :: CheckoutSessionCreate -> Form
toForm CheckoutSessionCreate
csc =
    let convertItem :: (a, CheckoutSessionCreateLineItem) -> [(Text, [Text])]
convertItem (a
idx, CheckoutSessionCreateLineItem
itm) =
          [ (Text
"line_items[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece a
idx Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"][price]", [PriceId -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (PriceId -> Text) -> PriceId -> Text
forall a b. (a -> b) -> a -> b
$ CheckoutSessionCreateLineItem -> PriceId
cscliPrice CheckoutSessionCreateLineItem
itm])
          , (Text
"line_items[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece a
idx Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"][quantity]", [Integer -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (Integer -> Text) -> Integer -> Text
forall a b. (a -> b) -> a -> b
$ CheckoutSessionCreateLineItem -> Integer
cscliQuantity CheckoutSessionCreateLineItem
itm])
          ]
        lineItems :: [(Text, [Text])]
lineItems =
          ((Int, CheckoutSessionCreateLineItem) -> [(Text, [Text])])
-> [(Int, CheckoutSessionCreateLineItem)] -> [(Text, [Text])]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int, CheckoutSessionCreateLineItem) -> [(Text, [Text])]
forall a.
ToHttpApiData a =>
(a, CheckoutSessionCreateLineItem) -> [(Text, [Text])]
convertItem ([Int]
-> [CheckoutSessionCreateLineItem]
-> [(Int, CheckoutSessionCreateLineItem)]
forall a b. [a] -> [b] -> [(a, b)]
zip ([Int
0..] :: [Int]) (CheckoutSessionCreate -> [CheckoutSessionCreateLineItem]
cscLineItems CheckoutSessionCreate
csc))
        convertPmt :: (a, a) -> (Text, [a])
convertPmt (a
idx, a
pm) =
          ( Text
"payment_method_types[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece a
idx Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
          , [a
pm]
          )
        pmt :: [(Text, [Text])]
pmt =
          ((Int, Text) -> (Text, [Text]))
-> [(Int, Text)] -> [(Text, [Text])]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Text) -> (Text, [Text])
forall a a. ToHttpApiData a => (a, a) -> (Text, [a])
convertPmt ([Int] -> [Text] -> [(Int, Text)]
forall a b. [a] -> [b] -> [(a, b)]
zip ([Int
0..] :: [Int]) (CheckoutSessionCreate -> [Text]
cscPaymentMethodTypes CheckoutSessionCreate
csc))
    in HashMap Text [Text] -> Form
Form (HashMap Text [Text] -> Form) -> HashMap Text [Text] -> Form
forall a b. (a -> b) -> a -> b
$ [(Text, [Text])] -> HashMap Text [Text]
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(Text, [Text])] -> HashMap Text [Text])
-> [(Text, [Text])] -> HashMap Text [Text]
forall a b. (a -> b) -> a -> b
$
       [ (Text
"cancel_url", [CheckoutSessionCreate -> Text
cscCancelUrl CheckoutSessionCreate
csc])
       , (Text
"success_url", [CheckoutSessionCreate -> Text
cscSuccessUrl CheckoutSessionCreate
csc])
       , (Text
"mode", [CheckoutSessionCreate -> Text
cscMode CheckoutSessionCreate
csc])
       , (Text
"client_reference_id", Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ CheckoutSessionCreate -> Maybe Text
cscClientReferenceId CheckoutSessionCreate
csc)
       , (Text
"customer", Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ (CustomerId -> Text) -> Maybe CustomerId -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CustomerId -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece (Maybe CustomerId -> Maybe Text) -> Maybe CustomerId -> Maybe Text
forall a b. (a -> b) -> a -> b
$ CheckoutSessionCreate -> Maybe CustomerId
cscCustomer CheckoutSessionCreate
csc)
       ] [(Text, [Text])] -> [(Text, [Text])] -> [(Text, [Text])]
forall a. Semigroup a => a -> a -> a
<> [(Text, [Text])]
lineItems [(Text, [Text])] -> [(Text, [Text])] -> [(Text, [Text])]
forall a. Semigroup a => a -> a -> a
<> [(Text, [Text])]
pmt