stripe-concepts-1.0.3.3: Types for the Stripe API
Safe HaskellSafe-Inferred
LanguageGHC2021

Stripe.Concepts

Synopsis

Modes

data Mode Source #

"To make the API as explorable as possible, accounts have test mode and live mode API keys. There is no switch for changing between modes, just use the appropriate key to perform a live or test transaction. Requests made with test mode credentials never hit the banking networks and incur no cost." - Stripe

This library provides functions to convert back and forth between Mode and Bool:

Constructors

LiveMode 
TestMode 

Instances

Instances details
Data Mode Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mode -> c Mode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Mode #

toConstr :: Mode -> Constr #

dataTypeOf :: Mode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Mode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mode) #

gmapT :: (forall b. Data b => b -> b) -> Mode -> Mode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r #

gmapQ :: (forall d. Data d => d -> u) -> Mode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Mode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mode -> m Mode #

Bounded Mode Source # 
Instance details

Defined in Stripe.Concepts

Enum Mode Source # 
Instance details

Defined in Stripe.Concepts

Methods

succ :: Mode -> Mode #

pred :: Mode -> Mode #

toEnum :: Int -> Mode #

fromEnum :: Mode -> Int #

enumFrom :: Mode -> [Mode] #

enumFromThen :: Mode -> Mode -> [Mode] #

enumFromTo :: Mode -> Mode -> [Mode] #

enumFromThenTo :: Mode -> Mode -> Mode -> [Mode] #

Generic Mode Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Show Mode Source # 
Instance details

Defined in Stripe.Concepts

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Eq Mode Source # 
Instance details

Defined in Stripe.Concepts

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

Ord Mode Source # 
Instance details

Defined in Stripe.Concepts

Methods

compare :: Mode -> Mode -> Ordering #

(<) :: Mode -> Mode -> Bool #

(<=) :: Mode -> Mode -> Bool #

(>) :: Mode -> Mode -> Bool #

(>=) :: Mode -> Mode -> Bool #

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

type Rep Mode Source # 
Instance details

Defined in Stripe.Concepts

type Rep Mode = D1 ('MetaData "Mode" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'False) (C1 ('MetaCons "LiveMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TestMode" 'PrefixI 'False) (U1 :: Type -> Type))

data BothModes a Source #

A pair of values of the same type, one for live mode and one for test mode.

For example, you may wish to use a value of type BothModes PublishableApiKey to represent your publishable API keys for both live mode and test mode.

Constructors

BothModes 

Fields

Instances

Instances details
Functor BothModes Source # 
Instance details

Defined in Stripe.Concepts

Methods

fmap :: (a -> b) -> BothModes a -> BothModes b #

(<$) :: a -> BothModes b -> BothModes a #

Data a => Data (BothModes a) Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BothModes a -> c (BothModes a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BothModes a) #

toConstr :: BothModes a -> Constr #

dataTypeOf :: BothModes a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BothModes a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BothModes a)) #

gmapT :: (forall b. Data b => b -> b) -> BothModes a -> BothModes a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BothModes a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BothModes a -> r #

gmapQ :: (forall d. Data d => d -> u) -> BothModes a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BothModes a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BothModes a -> m (BothModes a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BothModes a -> m (BothModes a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BothModes a -> m (BothModes a) #

Generic (BothModes a) Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep (BothModes a) :: Type -> Type #

Methods

from :: BothModes a -> Rep (BothModes a) x #

to :: Rep (BothModes a) x -> BothModes a #

Show a => Show (BothModes a) Source # 
Instance details

Defined in Stripe.Concepts

Eq a => Eq (BothModes a) Source # 
Instance details

Defined in Stripe.Concepts

Methods

(==) :: BothModes a -> BothModes a -> Bool #

(/=) :: BothModes a -> BothModes a -> Bool #

type Rep (BothModes a) Source # 
Instance details

Defined in Stripe.Concepts

type Rep (BothModes a) = D1 ('MetaData "BothModes" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'False) (C1 ('MetaCons "BothModes" 'PrefixI 'True) (S1 ('MetaSel ('Just "liveMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "testMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Conversion with Bool

isLiveMode :: Mode -> Bool Source #

LiveMode → True; TestMode → False

isTestMode :: Mode -> Bool Source #

LiveMode → False; TestMode → True

isLiveMode' :: Bool -> Mode Source #

True → LiveMode; False → TestMode

isTestMode' :: Bool -> Mode Source #

True → TestMode; False → LiveMode

Keys

Each Stripe account has a pair of API keys involved in making requests to the Stripe API:

Each webhook endpoint you set up has a "signing secret" (WebhookSecretKey) that you use to verify the authenticity of the webhook events you receive *from* Stripe.

newtype PublishableApiKey Source #

Publishable API keys are used in client-side code.

"Publishable API keys are meant solely to identify your account with Stripe, they aren’t secret. In other words, they can safely be published in places like your Stripe.js JavaScript code, or in an Android or iPhone app. Publishable keys only have the power to create tokens." - Stripe

Constructors

PublishableApiKey Text 

Instances

Instances details
Data PublishableApiKey Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PublishableApiKey -> c PublishableApiKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PublishableApiKey #

toConstr :: PublishableApiKey -> Constr #

dataTypeOf :: PublishableApiKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PublishableApiKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublishableApiKey) #

gmapT :: (forall b. Data b => b -> b) -> PublishableApiKey -> PublishableApiKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PublishableApiKey -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PublishableApiKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> PublishableApiKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PublishableApiKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PublishableApiKey -> m PublishableApiKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishableApiKey -> m PublishableApiKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishableApiKey -> m PublishableApiKey #

Generic PublishableApiKey Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep PublishableApiKey :: Type -> Type #

Show PublishableApiKey Source # 
Instance details

Defined in Stripe.Concepts

Eq PublishableApiKey Source # 
Instance details

Defined in Stripe.Concepts

Ord PublishableApiKey Source # 
Instance details

Defined in Stripe.Concepts

type Rep PublishableApiKey Source # 
Instance details

Defined in Stripe.Concepts

type Rep PublishableApiKey = D1 ('MetaData "PublishableApiKey" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "PublishableApiKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Secret API key

newtype ApiSecretKey Source #

API secret keys are used to make requests to Stripe.

"Authenticate your account when using the API by including your secret API key in the request. You can manage your API keys in the Dashboard. Your API keys carry many privileges, so be sure to keep them secret!" - Stripe

The key is represented here as a ByteString, but you are likely have the data as a Text value. You can use textToApiSecretKey to do this conversion.

Constructors

ApiSecretKey ByteString 

textToApiSecretKey :: Text -> ApiSecretKey Source #

Convert a Text representation of a Stripe API key (that looks something like "sk_test_BQokikJOvBiI2HlWgH4olfQ2") to an ApiSecretKey.

Webhook secret

newtype WebhookSecretKey Source #

Webhook secrets are used to verify the authenticity of webhook events that you receive from Stripe.

"Stripe can optionally sign the webhook events it sends to your endpoints. We do so by including a signature in each event’s Stripe-Signature header. This allows you to validate that the events were sent by Stripe, not by a third party. [...] Before you can verify signatures, you need to retrieve your endpoint’s secret from your Dashboard’s Webhooks settings. - Stripe

The key is represented here as a ByteString, but you are likely have the data as a Text value. You can use textToWebhookSecretKey to do this conversion.

textToWebhookSecretKey :: Text -> WebhookSecretKey Source #

Convert a Text representation of a Stripe webhook secret (that looks something like "whsec_ojm5cmJMGMTw3w7ngjI7mgkRsFGLRtCt") to a WebhookSecretKey.

Identifiers

newtype TokenId Source #

Identifier of a Stripe "token", which represents a payment source that was submitted by a user to Stripe.

"This ensures that no sensitive card data touches your server, and allows your integration to operate in a PCI-compliant way." - Stripe

Constructors

TokenId Text 

Instances

Instances details
Data TokenId Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenId -> c TokenId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenId #

toConstr :: TokenId -> Constr #

dataTypeOf :: TokenId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenId) #

gmapT :: (forall b. Data b => b -> b) -> TokenId -> TokenId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenId -> r #

gmapQ :: (forall d. Data d => d -> u) -> TokenId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenId -> m TokenId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenId -> m TokenId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenId -> m TokenId #

Generic TokenId Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep TokenId :: Type -> Type #

Methods

from :: TokenId -> Rep TokenId x #

to :: Rep TokenId x -> TokenId #

Show TokenId Source # 
Instance details

Defined in Stripe.Concepts

Eq TokenId Source # 
Instance details

Defined in Stripe.Concepts

Methods

(==) :: TokenId -> TokenId -> Bool #

(/=) :: TokenId -> TokenId -> Bool #

Ord TokenId Source # 
Instance details

Defined in Stripe.Concepts

type Rep TokenId Source # 
Instance details

Defined in Stripe.Concepts

type Rep TokenId = D1 ('MetaData "TokenId" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "TokenId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype CustomerId Source #

A customer identifier assigned by Stripe.

"Customer objects allow you to perform recurring charges, and to track multiple charges, that are associated with the same customer." - Stripe

Constructors

CustomerId Text 

Instances

Instances details
Data CustomerId Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CustomerId -> c CustomerId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CustomerId #

toConstr :: CustomerId -> Constr #

dataTypeOf :: CustomerId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CustomerId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CustomerId) #

gmapT :: (forall b. Data b => b -> b) -> CustomerId -> CustomerId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CustomerId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CustomerId -> r #

gmapQ :: (forall d. Data d => d -> u) -> CustomerId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CustomerId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CustomerId -> m CustomerId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomerId -> m CustomerId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CustomerId -> m CustomerId #

Generic CustomerId Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep CustomerId :: Type -> Type #

Show CustomerId Source # 
Instance details

Defined in Stripe.Concepts

Eq CustomerId Source # 
Instance details

Defined in Stripe.Concepts

Ord CustomerId Source # 
Instance details

Defined in Stripe.Concepts

type Rep CustomerId Source # 
Instance details

Defined in Stripe.Concepts

type Rep CustomerId = D1 ('MetaData "CustomerId" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "CustomerId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype ProductId Source #

The ID of a Stripe product.

"Product objects describe items that your customers can subscribe to with a Subscription. An associated Plan determines the product pricing." - Stripe

Constructors

ProductId Text 

Instances

Instances details
Data ProductId Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProductId -> c ProductId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProductId #

toConstr :: ProductId -> Constr #

dataTypeOf :: ProductId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProductId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProductId) #

gmapT :: (forall b. Data b => b -> b) -> ProductId -> ProductId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProductId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProductId -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProductId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProductId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProductId -> m ProductId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProductId -> m ProductId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProductId -> m ProductId #

Generic ProductId Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep ProductId :: Type -> Type #

Show ProductId Source # 
Instance details

Defined in Stripe.Concepts

Eq ProductId Source # 
Instance details

Defined in Stripe.Concepts

Ord ProductId Source # 
Instance details

Defined in Stripe.Concepts

type Rep ProductId Source # 
Instance details

Defined in Stripe.Concepts

type Rep ProductId = D1 ('MetaData "ProductId" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "ProductId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype PlanId Source #

The ID of a Stripe subscription plan.

"Plans define the base price, currency, and billing cycle for subscriptions. For example, you might have a $5/month plan that provides limited access to your products, and a $15/month plan that allows full access." - Stripe

Constructors

PlanId Text 

Instances

Instances details
Data PlanId Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlanId -> c PlanId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlanId #

toConstr :: PlanId -> Constr #

dataTypeOf :: PlanId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PlanId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlanId) #

gmapT :: (forall b. Data b => b -> b) -> PlanId -> PlanId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlanId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlanId -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlanId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlanId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlanId -> m PlanId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanId -> m PlanId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanId -> m PlanId #

Generic PlanId Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep PlanId :: Type -> Type #

Methods

from :: PlanId -> Rep PlanId x #

to :: Rep PlanId x -> PlanId #

Show PlanId Source # 
Instance details

Defined in Stripe.Concepts

Eq PlanId Source # 
Instance details

Defined in Stripe.Concepts

Methods

(==) :: PlanId -> PlanId -> Bool #

(/=) :: PlanId -> PlanId -> Bool #

Ord PlanId Source # 
Instance details

Defined in Stripe.Concepts

type Rep PlanId Source # 
Instance details

Defined in Stripe.Concepts

type Rep PlanId = D1 ('MetaData "PlanId" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "PlanId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype SubscriptionId Source #

Identifier for a customer's subscription to a product.

"Subscriptions allow you to charge a customer on a recurring basis. A subscription ties a customer to a particular plan you've created." - Stripe

Constructors

SubscriptionId Text 

Instances

Instances details
Data SubscriptionId Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SubscriptionId -> c SubscriptionId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SubscriptionId #

toConstr :: SubscriptionId -> Constr #

dataTypeOf :: SubscriptionId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SubscriptionId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SubscriptionId) #

gmapT :: (forall b. Data b => b -> b) -> SubscriptionId -> SubscriptionId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SubscriptionId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SubscriptionId -> r #

gmapQ :: (forall d. Data d => d -> u) -> SubscriptionId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SubscriptionId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SubscriptionId -> m SubscriptionId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SubscriptionId -> m SubscriptionId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SubscriptionId -> m SubscriptionId #

Generic SubscriptionId Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep SubscriptionId :: Type -> Type #

Show SubscriptionId Source # 
Instance details

Defined in Stripe.Concepts

Eq SubscriptionId Source # 
Instance details

Defined in Stripe.Concepts

Ord SubscriptionId Source # 
Instance details

Defined in Stripe.Concepts

type Rep SubscriptionId Source # 
Instance details

Defined in Stripe.Concepts

type Rep SubscriptionId = D1 ('MetaData "SubscriptionId" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "SubscriptionId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype InvoiceId Source #

The ID of a Stripe invoice.

"Invoices are statements of amounts owed by a customer, and are either generated one-off, or generated periodically from a subscription." - Stripe

Constructors

InvoiceId Text 

Instances

Instances details
Data InvoiceId Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InvoiceId -> c InvoiceId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InvoiceId #

toConstr :: InvoiceId -> Constr #

dataTypeOf :: InvoiceId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InvoiceId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InvoiceId) #

gmapT :: (forall b. Data b => b -> b) -> InvoiceId -> InvoiceId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InvoiceId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InvoiceId -> r #

gmapQ :: (forall d. Data d => d -> u) -> InvoiceId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InvoiceId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InvoiceId -> m InvoiceId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InvoiceId -> m InvoiceId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InvoiceId -> m InvoiceId #

Generic InvoiceId Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep InvoiceId :: Type -> Type #

Show InvoiceId Source # 
Instance details

Defined in Stripe.Concepts

Eq InvoiceId Source # 
Instance details

Defined in Stripe.Concepts

Ord InvoiceId Source # 
Instance details

Defined in Stripe.Concepts

type Rep InvoiceId Source # 
Instance details

Defined in Stripe.Concepts

type Rep InvoiceId = D1 ('MetaData "InvoiceId" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "InvoiceId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype CouponId Source #

The ID of a Stripe coupon.

"A coupon contains information about a percent-off or amount-off discount you might want to apply to a customer. Coupons may be applied to invoices or orders." - Stripe

Constructors

CouponId Text 

Instances

Instances details
Data CouponId Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CouponId -> c CouponId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CouponId #

toConstr :: CouponId -> Constr #

dataTypeOf :: CouponId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CouponId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CouponId) #

gmapT :: (forall b. Data b => b -> b) -> CouponId -> CouponId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CouponId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CouponId -> r #

gmapQ :: (forall d. Data d => d -> u) -> CouponId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CouponId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CouponId -> m CouponId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CouponId -> m CouponId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CouponId -> m CouponId #

Generic CouponId Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep CouponId :: Type -> Type #

Methods

from :: CouponId -> Rep CouponId x #

to :: Rep CouponId x -> CouponId #

Show CouponId Source # 
Instance details

Defined in Stripe.Concepts

Eq CouponId Source # 
Instance details

Defined in Stripe.Concepts

Ord CouponId Source # 
Instance details

Defined in Stripe.Concepts

type Rep CouponId Source # 
Instance details

Defined in Stripe.Concepts

type Rep CouponId = D1 ('MetaData "CouponId" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "CouponId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

API Versioning

newtype ApiVersion Source #

When Stripe makes a backwards-incompatible change to the API, they release a new API version. The versions are named by the date of their release (e.g. "2019-09-09").

Constructors

ApiVersion Text 

Instances

Instances details
Data ApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApiVersion -> c ApiVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApiVersion #

toConstr :: ApiVersion -> Constr #

dataTypeOf :: ApiVersion -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ApiVersion) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApiVersion) #

gmapT :: (forall b. Data b => b -> b) -> ApiVersion -> ApiVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApiVersion -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApiVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApiVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApiVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApiVersion -> m ApiVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApiVersion -> m ApiVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApiVersion -> m ApiVersion #

Generic ApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep ApiVersion :: Type -> Type #

Show ApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Eq ApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Ord ApiVersion Source # 
Instance details

Defined in Stripe.Concepts

type Rep ApiVersion Source # 
Instance details

Defined in Stripe.Concepts

type Rep ApiVersion = D1 ('MetaData "ApiVersion" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'True) (C1 ('MetaCons "ApiVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data RequestApiVersion Source #

Your account API settings specify:

  • Which API version is used by default for requests;
  • Which API version is used for webhook events.

However, you can override the API version for specific requests. "To set the API version on a specific request, send a Stripe-Version header." - Stripe

Constructors

DefaultApiVersion

Use the default API version specified by your account settings.

OverrideApiVersion ApiVersion

Use a specific API version for this request. (Please note however that any webhook events generated as a result of this request will still use your account's default API version.)

Instances

Instances details
Data RequestApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RequestApiVersion -> c RequestApiVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RequestApiVersion #

toConstr :: RequestApiVersion -> Constr #

dataTypeOf :: RequestApiVersion -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RequestApiVersion) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RequestApiVersion) #

gmapT :: (forall b. Data b => b -> b) -> RequestApiVersion -> RequestApiVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RequestApiVersion -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RequestApiVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> RequestApiVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RequestApiVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RequestApiVersion -> m RequestApiVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestApiVersion -> m RequestApiVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RequestApiVersion -> m RequestApiVersion #

Generic RequestApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Associated Types

type Rep RequestApiVersion :: Type -> Type #

Show RequestApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Eq RequestApiVersion Source # 
Instance details

Defined in Stripe.Concepts

Ord RequestApiVersion Source # 
Instance details

Defined in Stripe.Concepts

type Rep RequestApiVersion Source # 
Instance details

Defined in Stripe.Concepts

type Rep RequestApiVersion = D1 ('MetaData "RequestApiVersion" "Stripe.Concepts" "stripe-concepts-1.0.3.3-J89sDiwWUM3J6hhvvzyVOC" 'False) (C1 ('MetaCons "DefaultApiVersion" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverrideApiVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ApiVersion)))