stripe-core-2.2.0: Stripe API for Haskell - Pure Core

Copyright(c) David Johnson 2014
Maintainerdjohnson.m@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Web.Stripe.Types

Description

 

Synopsis

Documentation

data Expandable id Source #

a wrapper for fields which can either be an id or an expanded object

Constructors

Id id

an id such as CardId, AccountId, CustomerId, etc

Expanded (ExpandsTo id)

expanded object such as Card, Account, Customer, etc

Instances

(Eq id, Eq (ExpandsTo id)) => Eq (Expandable id) Source # 

Methods

(==) :: Expandable id -> Expandable id -> Bool #

(/=) :: Expandable id -> Expandable id -> Bool #

(Data id, Data (ExpandsTo id)) => Data (Expandable id) Source # 

Methods

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

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

toConstr :: Expandable id -> Constr #

dataTypeOf :: Expandable id -> DataType #

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

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

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

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

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

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

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

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

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

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

(Ord id, Ord (ExpandsTo id)) => Ord (Expandable id) Source # 

Methods

compare :: Expandable id -> Expandable id -> Ordering #

(<) :: Expandable id -> Expandable id -> Bool #

(<=) :: Expandable id -> Expandable id -> Bool #

(>) :: Expandable id -> Expandable id -> Bool #

(>=) :: Expandable id -> Expandable id -> Bool #

max :: Expandable id -> Expandable id -> Expandable id #

min :: Expandable id -> Expandable id -> Expandable id #

(Read id, Read (ExpandsTo id)) => Read (Expandable id) Source # 
(Show id, Show (ExpandsTo id)) => Show (Expandable id) Source # 

Methods

showsPrec :: Int -> Expandable id -> ShowS #

show :: Expandable id -> String #

showList :: [Expandable id] -> ShowS #

(FromJSON id, FromJSON (ExpandsTo id)) => FromJSON (Expandable id) Source #

JSON Instance for Expandable

data TimeRange a Source #

specify a TimeRange FIXME: this is a little awkward to use. How can we make it moar better?

Constructors

TimeRange 

Fields

Instances

StripeHasParam GetBalanceTransactionHistory (TimeRange Created) Source # 
StripeHasParam GetBalanceTransactionHistory (TimeRange AvailableOn) Source # 
Eq a => Eq (TimeRange a) Source # 

Methods

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

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

Data a => Data (TimeRange a) Source # 

Methods

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

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

toConstr :: TimeRange a -> Constr #

dataTypeOf :: TimeRange a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (TimeRange a) Source # 
Read a => Read (TimeRange a) Source # 
Show a => Show (TimeRange a) Source # 
ToStripeParam a => ToStripeParam (TimeRange a) Source # 

emptyTimeRange :: TimeRange a Source #

Time range with all values set to Nothing

newtype AvailableOn Source #

Constructors

AvailableOn UTCTime 

Instances

Eq AvailableOn Source # 
Data AvailableOn Source # 

Methods

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

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

toConstr :: AvailableOn -> Constr #

dataTypeOf :: AvailableOn -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AvailableOn Source # 
Read AvailableOn Source # 
Show AvailableOn Source # 
ToStripeParam AvailableOn Source # 
StripeHasParam GetBalanceTransactionHistory AvailableOn Source # 
StripeHasParam GetBalanceTransactionHistory (TimeRange AvailableOn) Source # 

newtype Created Source #

Constructors

Created UTCTime 

Instances

Eq Created Source # 

Methods

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

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

Data Created Source # 

Methods

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

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

toConstr :: Created -> Constr #

dataTypeOf :: Created -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Created Source # 
Read Created Source # 
Show Created Source # 
ToStripeParam Created Source # 
StripeHasParam GetTransfers Created Source # 
StripeHasParam GetInvoiceItems Created Source # 
StripeHasParam GetEvents Created Source # 
StripeHasParam GetCustomers Created Source # 
StripeHasParam GetCharges Created Source # 
StripeHasParam GetBalanceTransactionHistory Created Source # 
StripeHasParam GetApplicationFees Created Source # 
StripeHasParam GetBalanceTransactionHistory (TimeRange Created) Source # 

newtype Date Source #

Constructors

Date UTCTime 

Instances

Eq Date Source # 

Methods

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

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

Data Date Source # 

Methods

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

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

toConstr :: Date -> Constr #

dataTypeOf :: Date -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Date Source # 

Methods

compare :: Date -> Date -> Ordering #

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

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

(>) :: Date -> Date -> Bool #

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

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

Read Date Source # 
Show Date Source # 

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

ToStripeParam Date Source # 
StripeHasParam GetTransfers Date Source # 

newtype ChargeId Source #

ChargeId associated with a Charge

Constructors

ChargeId Text 

Instances

Eq ChargeId Source # 
Data ChargeId Source # 

Methods

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

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

toConstr :: ChargeId -> Constr #

dataTypeOf :: ChargeId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChargeId Source # 
Read ChargeId Source # 
Show ChargeId Source # 
FromJSON ChargeId Source #

JSON Instance for ChargeId

ToStripeParam ChargeId Source # 
StripeHasParam GetApplicationFees ChargeId Source # 
StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
StripeHasParam GetCharges (StartingAfter ChargeId) Source # 
type ExpandsTo ChargeId Source # 

newtype StatementDescription Source #

StatementDescription to be added to a Charge

Instances

Eq StatementDescription Source # 
Data StatementDescription Source # 

Methods

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

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

toConstr :: StatementDescription -> Constr #

dataTypeOf :: StatementDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StatementDescription Source # 
Read StatementDescription Source # 
Show StatementDescription Source # 
FromJSON StatementDescription Source # 
ToStripeParam StatementDescription Source # 
StripeHasParam CreateTransfer StatementDescription Source # 
StripeHasParam UpdatePlan StatementDescription Source # 
StripeHasParam CreatePlan StatementDescription Source # 
StripeHasParam UpdateInvoice StatementDescription Source # 
StripeHasParam CreateInvoice StatementDescription Source # 
StripeHasParam CreateCharge StatementDescription Source # 

data Charge Source #

Charge object in Stripe API

Instances

Eq Charge Source # 

Methods

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

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

Data Charge Source # 

Methods

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

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

toConstr :: Charge -> Constr #

dataTypeOf :: Charge -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Charge Source # 
Read Charge Source # 
Show Charge Source # 
FromJSON Charge Source #

JSON Instance for Charge

newtype Capture Source #

Capture for Charge

Constructors

Capture 

Fields

Instances

Eq Capture Source # 

Methods

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

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

Data Capture Source # 

Methods

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

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

toConstr :: Capture -> Constr #

dataTypeOf :: Capture -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Capture Source # 
Read Capture Source # 
Show Capture Source # 
ToStripeParam Capture Source # 
StripeHasParam CreateCharge Capture Source # 

newtype RefundId Source #

Constructors

RefundId Text 

Instances

Eq RefundId Source # 
Data RefundId Source # 

Methods

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

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

toConstr :: RefundId -> Constr #

dataTypeOf :: RefundId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RefundId Source # 
Read RefundId Source # 
Show RefundId Source # 
ToStripeParam RefundId Source # 
StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 

data Refund Source #

Refund Object

Instances

Eq Refund Source # 

Methods

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

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

Data Refund Source # 

Methods

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

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

toConstr :: Refund -> Constr #

dataTypeOf :: Refund -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Refund Source # 
Read Refund Source # 
Show Refund Source # 
FromJSON Refund Source #

JSON Instance for Refund

newtype RefundApplicationFee Source #

Instances

Eq RefundApplicationFee Source # 
Data RefundApplicationFee Source # 

Methods

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

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

toConstr :: RefundApplicationFee -> Constr #

dataTypeOf :: RefundApplicationFee -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RefundApplicationFee Source # 
Read RefundApplicationFee Source # 
Show RefundApplicationFee Source # 
ToStripeParam RefundApplicationFee Source # 
StripeHasParam CreateRefund RefundApplicationFee Source # 

data RefundReason Source #

Instances

Eq RefundReason Source # 
Data RefundReason Source # 

Methods

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

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

toConstr :: RefundReason -> Constr #

dataTypeOf :: RefundReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RefundReason Source # 
Read RefundReason Source # 
Show RefundReason Source # 
ToStripeParam RefundReason Source # 
StripeHasParam CreateRefund RefundReason Source # 

newtype CustomerId Source #

Constructors

CustomerId Text 

Instances

Eq CustomerId Source # 
Data CustomerId Source # 

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 :: (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 #

Ord CustomerId Source # 
Read CustomerId Source # 
Show CustomerId Source # 
FromJSON CustomerId Source #

JSON Instance for CustomerId

ToStripeParam CustomerId Source # 
StripeHasParam CreateCardToken CustomerId Source # 
StripeHasParam GetInvoiceItems CustomerId Source # 
StripeHasParam GetInvoiceLineItems CustomerId Source # 
StripeHasParam GetCharges CustomerId Source # 
StripeHasParam CreateCharge CustomerId Source # 
StripeHasParam GetCustomers (EndingBefore CustomerId) Source # 
StripeHasParam GetCustomers (StartingAfter CustomerId) Source # 
type ExpandsTo CustomerId Source # 

data Customer Source #

Customer object

Instances

Eq Customer Source # 
Data Customer Source # 

Methods

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

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

toConstr :: Customer -> Constr #

dataTypeOf :: Customer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Customer Source # 
Read Customer Source # 
Show Customer Source # 
FromJSON Customer Source #

JSON Instance for Customer

newtype AccountBalance Source #

AccountBalance for a Customer

Constructors

AccountBalance Int 

Instances

Eq AccountBalance Source # 
Data AccountBalance Source # 

Methods

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

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

toConstr :: AccountBalance -> Constr #

dataTypeOf :: AccountBalance -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AccountBalance Source # 
Read AccountBalance Source # 
Show AccountBalance Source # 
ToStripeParam AccountBalance Source # 
StripeHasParam UpdateCustomer AccountBalance Source # 
StripeHasParam CreateCustomer AccountBalance Source # 

newtype CardId Source #

CardId for a Customer

Constructors

CardId Text 

Instances

Eq CardId Source # 

Methods

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

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

Data CardId Source # 

Methods

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

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

toConstr :: CardId -> Constr #

dataTypeOf :: CardId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CardId Source # 
Read CardId Source # 
Show CardId Source # 
FromJSON CardId Source #

JSON Instance for CardId

ToStripeParam CardId Source # 
StripeHasParam UpdateSubscription CardId Source # 
StripeHasParam CreateSubscription CardId Source # 
StripeHasParam CreateTransfer CardId Source # 
StripeHasParam UpdateRecipient CardId Source # 
StripeHasParam CreateRecipient CardId Source # 
StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
StripeHasParam GetRecipientCards (StartingAfter CardId) Source # 
StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
StripeHasParam GetCustomerCards (StartingAfter CardId) Source # 
type ExpandsTo CardId Source # 

newtype RecipientCardId Source #

CardId for a Recipient

Constructors

RecipientCardId Text 

Instances

Eq RecipientCardId Source # 
Data RecipientCardId Source # 

Methods

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

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

toConstr :: RecipientCardId -> Constr #

dataTypeOf :: RecipientCardId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecipientCardId Source # 
Read RecipientCardId Source # 
Show RecipientCardId Source # 
FromJSON RecipientCardId Source #

JSON Instance for RecipientCardId

type ExpandsTo RecipientCardId Source # 

newtype CardNumber Source #

Number associated with a Card

Constructors

CardNumber Text 

Instances

Eq CardNumber Source # 
Data CardNumber Source # 

Methods

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

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

toConstr :: CardNumber -> Constr #

dataTypeOf :: CardNumber -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CardNumber Source # 
Read CardNumber Source # 
Show CardNumber Source # 
ToStripeParam CardNumber Source # 

newtype ExpMonth Source #

Expiration Month for a Card

Constructors

ExpMonth Int 

Instances

Eq ExpMonth Source # 
Data ExpMonth Source # 

Methods

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

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

toConstr :: ExpMonth -> Constr #

dataTypeOf :: ExpMonth -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExpMonth Source # 
Read ExpMonth Source # 
Show ExpMonth Source # 
ToStripeParam ExpMonth Source # 
StripeHasParam UpdateRecipientCard ExpMonth Source # 
StripeHasParam UpdateCustomerCard ExpMonth Source # 

newtype ExpYear Source #

Expiration Year for a Card

Constructors

ExpYear Int 

Instances

Eq ExpYear Source # 

Methods

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

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

Data ExpYear Source # 

Methods

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

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

toConstr :: ExpYear -> Constr #

dataTypeOf :: ExpYear -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExpYear Source # 
Read ExpYear Source # 
Show ExpYear Source # 
ToStripeParam ExpYear Source # 
StripeHasParam UpdateRecipientCard ExpYear Source # 
StripeHasParam UpdateCustomerCard ExpYear Source # 

newtype CVC Source #

CVC for a Card

Constructors

CVC Text 

Instances

Eq CVC Source # 

Methods

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

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

Data CVC Source # 

Methods

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

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

toConstr :: CVC -> Constr #

dataTypeOf :: CVC -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CVC Source # 

Methods

compare :: CVC -> CVC -> Ordering #

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

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

(>) :: CVC -> CVC -> Bool #

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

max :: CVC -> CVC -> CVC #

min :: CVC -> CVC -> CVC #

Read CVC Source # 
Show CVC Source # 

Methods

showsPrec :: Int -> CVC -> ShowS #

show :: CVC -> String #

showList :: [CVC] -> ShowS #

ToStripeParam CVC Source # 

newtype AddressCity Source #

City address for a Card

Constructors

AddressCity Text 

Instances

Eq AddressCity Source # 
Data AddressCity Source # 

Methods

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

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

toConstr :: AddressCity -> Constr #

dataTypeOf :: AddressCity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddressCity Source # 
Read AddressCity Source # 
Show AddressCity Source # 
ToStripeParam AddressCity Source # 
StripeHasParam UpdateRecipientCard AddressCity Source # 
StripeHasParam UpdateCustomerCard AddressCity Source # 

newtype AddressCountry Source #

Country address for a Card

Constructors

AddressCountry Text 

Instances

Eq AddressCountry Source # 
Data AddressCountry Source # 

Methods

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

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

toConstr :: AddressCountry -> Constr #

dataTypeOf :: AddressCountry -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddressCountry Source # 
Read AddressCountry Source # 
Show AddressCountry Source # 
ToStripeParam AddressCountry Source # 
StripeHasParam UpdateRecipientCard AddressCountry Source # 
StripeHasParam UpdateCustomerCard AddressCountry Source # 

newtype AddressLine1 Source #

Address Line One for a Card

Constructors

AddressLine1 Text 

Instances

Eq AddressLine1 Source # 
Data AddressLine1 Source # 

Methods

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

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

toConstr :: AddressLine1 -> Constr #

dataTypeOf :: AddressLine1 -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddressLine1 Source # 
Read AddressLine1 Source # 
Show AddressLine1 Source # 
ToStripeParam AddressLine1 Source # 
StripeHasParam UpdateRecipientCard AddressLine1 Source # 
StripeHasParam UpdateCustomerCard AddressLine1 Source # 

newtype AddressLine2 Source #

Address Line Two for a Card

Constructors

AddressLine2 Text 

Instances

Eq AddressLine2 Source # 
Data AddressLine2 Source # 

Methods

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

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

toConstr :: AddressLine2 -> Constr #

dataTypeOf :: AddressLine2 -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddressLine2 Source # 
Read AddressLine2 Source # 
Show AddressLine2 Source # 
ToStripeParam AddressLine2 Source # 
StripeHasParam UpdateRecipientCard AddressLine2 Source # 
StripeHasParam UpdateCustomerCard AddressLine2 Source # 

newtype AddressState Source #

Address State for a Card

Constructors

AddressState Text 

Instances

Eq AddressState Source # 
Data AddressState Source # 

Methods

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

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

toConstr :: AddressState -> Constr #

dataTypeOf :: AddressState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddressState Source # 
Read AddressState Source # 
Show AddressState Source # 
ToStripeParam AddressState Source # 
StripeHasParam UpdateRecipientCard AddressState Source # 
StripeHasParam UpdateCustomerCard AddressState Source # 

newtype AddressZip Source #

Address Zip Code for a Card

Constructors

AddressZip Text 

Instances

Eq AddressZip Source # 
Data AddressZip Source # 

Methods

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

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

toConstr :: AddressZip -> Constr #

dataTypeOf :: AddressZip -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AddressZip Source # 
Read AddressZip Source # 
Show AddressZip Source # 
ToStripeParam AddressZip Source # 
StripeHasParam UpdateRecipientCard AddressZip Source # 
StripeHasParam UpdateCustomerCard AddressZip Source # 

newtype IsVerified Source #

IsVerified Recipients

Constructors

IsVerified 

Fields

Instances

Eq IsVerified Source # 
Data IsVerified Source # 

Methods

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

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

toConstr :: IsVerified -> Constr #

dataTypeOf :: IsVerified -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IsVerified Source # 
Read IsVerified Source # 
Show IsVerified Source # 
ToStripeParam IsVerified Source # 
StripeHasParam GetRecipients IsVerified Source # 

data Brand Source #

Credit / Debit Card Brand

Instances

Eq Brand Source # 

Methods

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

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

Data Brand Source # 

Methods

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

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

toConstr :: Brand -> Constr #

dataTypeOf :: Brand -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Brand Source # 

Methods

compare :: Brand -> Brand -> Ordering #

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

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

(>) :: Brand -> Brand -> Bool #

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

max :: Brand -> Brand -> Brand #

min :: Brand -> Brand -> Brand #

Read Brand Source # 
Show Brand Source # 

Methods

showsPrec :: Int -> Brand -> ShowS #

show :: Brand -> String #

showList :: [Brand] -> ShowS #

FromJSON Brand Source #

JSON Instance for Brand

data Card Source #

Card Object

Instances

Eq Card Source # 

Methods

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

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

Data Card Source # 

Methods

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

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

toConstr :: Card -> Constr #

dataTypeOf :: Card -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Card Source # 

Methods

compare :: Card -> Card -> Ordering #

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

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

(>) :: Card -> Card -> Bool #

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

max :: Card -> Card -> Card #

min :: Card -> Card -> Card #

Read Card Source # 
Show Card Source # 

Methods

showsPrec :: Int -> Card -> ShowS #

show :: Card -> String #

showList :: [Card] -> ShowS #

FromJSON Card Source #

JSON Instance for Card

data RecipientCard Source #

Instances

Eq RecipientCard Source # 
Data RecipientCard Source # 

Methods

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

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

toConstr :: RecipientCard -> Constr #

dataTypeOf :: RecipientCard -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecipientCard Source # 
Read RecipientCard Source # 
Show RecipientCard Source # 
FromJSON RecipientCard Source #

JSON Instance for RecipientCard

data NewCard Source #

NewCard contains the data needed to create a new Card

Instances

Eq NewCard Source # 

Methods

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

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

Data NewCard Source # 

Methods

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

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

toConstr :: NewCard -> Constr #

dataTypeOf :: NewCard -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NewCard Source # 
Read NewCard Source # 
Show NewCard Source # 
ToStripeParam NewCard Source # 
StripeHasParam UpdateRecipient NewCard Source # 
StripeHasParam CreateRecipient NewCard Source # 
StripeHasParam UpdateCustomer NewCard Source # 
StripeHasParam CreateCustomer NewCard Source # 
StripeHasParam CreateCharge NewCard Source # 

mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard Source #

create a NewCard with only the required fields

data DefaultCard Source #

set the DefaultCard

Constructors

DefaultCard 

Instances

Eq DefaultCard Source # 
Data DefaultCard Source # 

Methods

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

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

toConstr :: DefaultCard -> Constr #

dataTypeOf :: DefaultCard -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DefaultCard Source # 
Read DefaultCard Source # 
Show DefaultCard Source # 
ToStripeParam DefaultCard Source # 
StripeHasParam UpdateRecipient DefaultCard Source # 
StripeHasParam UpdateCustomer DefaultCard Source # 

newtype SubscriptionId Source #

Constructors

SubscriptionId 

Instances

Eq SubscriptionId Source # 
Data SubscriptionId Source # 

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 :: (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 #

Ord SubscriptionId Source # 
Read SubscriptionId Source # 
Show SubscriptionId Source # 
ToStripeParam SubscriptionId Source # 
StripeHasParam CreateInvoiceItem SubscriptionId Source # 
StripeHasParam GetUpcomingInvoice SubscriptionId Source # 
StripeHasParam GetInvoiceLineItems SubscriptionId Source # 
StripeHasParam CreateInvoice SubscriptionId Source # 
StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source # 

data Subscription Source #

Subscription Object

Instances

Eq Subscription Source # 
Data Subscription Source # 

Methods

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

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

toConstr :: Subscription -> Constr #

dataTypeOf :: Subscription -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Subscription Source # 
Read Subscription Source # 
Show Subscription Source # 
FromJSON Subscription Source #

JSON Instance for Subscription

data SubscriptionStatus Source #

Status of a Subscription

Instances

Eq SubscriptionStatus Source # 
Data SubscriptionStatus Source # 

Methods

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

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

toConstr :: SubscriptionStatus -> Constr #

dataTypeOf :: SubscriptionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SubscriptionStatus Source # 
Read SubscriptionStatus Source # 
Show SubscriptionStatus Source # 
FromJSON SubscriptionStatus Source #

JSON Instance for SubscriptionStatus

newtype TaxPercent Source #

Constructors

TaxPercent Double 

Instances

Eq TaxPercent Source # 
Data TaxPercent Source # 

Methods

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

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

toConstr :: TaxPercent -> Constr #

dataTypeOf :: TaxPercent -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TaxPercent Source # 
Read TaxPercent Source # 
Show TaxPercent Source # 
ToStripeParam TaxPercent Source # 
StripeHasParam UpdateSubscription TaxPercent Source # 
StripeHasParam CreateSubscription TaxPercent Source # 

newtype PlanId Source #

PlanId for a Plan

Constructors

PlanId Text 

Instances

Eq PlanId Source # 

Methods

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

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

Data PlanId Source # 

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 :: (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 #

Ord PlanId Source # 
Read PlanId Source # 
Show PlanId Source # 
ToStripeParam PlanId Source # 
StripeHasParam UpdateSubscription PlanId Source # 
StripeHasParam CreateCustomer PlanId Source # 
StripeHasParam GetPlans (EndingBefore PlanId) Source # 
StripeHasParam GetPlans (StartingAfter PlanId) Source # 

data Plan Source #

Plan object

Instances

Eq Plan Source # 

Methods

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

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

Data Plan Source # 

Methods

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

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

toConstr :: Plan -> Constr #

dataTypeOf :: Plan -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Plan Source # 

Methods

compare :: Plan -> Plan -> Ordering #

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

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

(>) :: Plan -> Plan -> Bool #

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

max :: Plan -> Plan -> Plan #

min :: Plan -> Plan -> Plan #

Read Plan Source # 
Show Plan Source # 

Methods

showsPrec :: Int -> Plan -> ShowS #

show :: Plan -> String #

showList :: [Plan] -> ShowS #

FromJSON Plan Source #

JSON Instance for Plan

newtype TrialEnd Source #

TrialEnd for a Plan

Constructors

TrialEnd UTCTime 

Instances

Eq TrialEnd Source # 
Data TrialEnd Source # 

Methods

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

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

toConstr :: TrialEnd -> Constr #

dataTypeOf :: TrialEnd -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrialEnd Source # 
Read TrialEnd Source # 
Show TrialEnd Source # 
ToStripeParam TrialEnd Source # 
StripeHasParam UpdateSubscription TrialEnd Source # 
StripeHasParam CreateSubscription TrialEnd Source # 
StripeHasParam CreateCustomer TrialEnd Source # 

data Interval Source #

Interval for Plans

Constructors

Day 
Week 
Month 
Year 

Instances

Eq Interval Source # 
Data Interval Source # 

Methods

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

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

toConstr :: Interval -> Constr #

dataTypeOf :: Interval -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Interval Source # 
Read Interval Source #

Read instance for Interval

Show Interval Source #

Show instance for Interval

FromJSON Interval Source #

JSON Instance for Interval

ToStripeParam Interval Source # 

data Duration Source #

Coupon Duration

Constructors

Forever 
Once 
Repeating 

Instances

Eq Duration Source # 
Data Duration Source # 

Methods

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

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

toConstr :: Duration -> Constr #

dataTypeOf :: Duration -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Duration Source # 
Read Duration Source #

Read instance for Duration

Show Duration Source #

Show instance for Duration

FromJSON Duration Source #

JSON Instance for Duration

ToStripeParam Duration Source # 

data Coupon Source #

Coupon Object

Instances

Eq Coupon Source # 

Methods

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

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

Data Coupon Source # 

Methods

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

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

toConstr :: Coupon -> Constr #

dataTypeOf :: Coupon -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Coupon Source # 
Read Coupon Source # 
Show Coupon Source # 
FromJSON Coupon Source #

JSON Instance for Coupon

newtype CouponId Source #

Constructors

CouponId Text 

Instances

Eq CouponId Source # 
Data CouponId Source # 

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 :: (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 #

Ord CouponId Source # 
Read CouponId Source # 
Show CouponId Source # 
ToStripeParam CouponId Source # 
StripeHasParam UpdateSubscription CouponId Source # 
StripeHasParam CreateSubscription CouponId Source # 
StripeHasParam UpdateCustomer CouponId Source # 
StripeHasParam CreateCustomer CouponId Source # 
StripeHasParam GetCoupons (EndingBefore CouponId) Source # 
StripeHasParam GetCoupons (StartingAfter CouponId) Source # 

newtype AmountOff Source #

Constructors

AmountOff Int 

Instances

Eq AmountOff Source # 
Data AmountOff Source # 

Methods

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

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

toConstr :: AmountOff -> Constr #

dataTypeOf :: AmountOff -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AmountOff Source # 
Read AmountOff Source # 
Show AmountOff Source # 
ToStripeParam AmountOff Source # 
StripeHasParam CreateCoupon AmountOff Source # 

newtype MaxRedemptions Source #

Constructors

MaxRedemptions Int 

Instances

Eq MaxRedemptions Source # 
Data MaxRedemptions Source # 

Methods

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

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

toConstr :: MaxRedemptions -> Constr #

dataTypeOf :: MaxRedemptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MaxRedemptions Source # 
Read MaxRedemptions Source # 
Show MaxRedemptions Source # 
ToStripeParam MaxRedemptions Source # 
StripeHasParam CreateCoupon MaxRedemptions Source # 

newtype PercentOff Source #

Constructors

PercentOff Int 

Instances

Eq PercentOff Source # 
Data PercentOff Source # 

Methods

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

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

toConstr :: PercentOff -> Constr #

dataTypeOf :: PercentOff -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PercentOff Source # 
Read PercentOff Source # 
Show PercentOff Source # 
ToStripeParam PercentOff Source # 
StripeHasParam CreateCoupon PercentOff Source # 

newtype RedeemBy Source #

RedeemBy date for a Coupon

Constructors

RedeemBy UTCTime 

Instances

Eq RedeemBy Source # 
Data RedeemBy Source # 

Methods

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

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

toConstr :: RedeemBy -> Constr #

dataTypeOf :: RedeemBy -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RedeemBy Source # 
Read RedeemBy Source # 
Show RedeemBy Source # 
ToStripeParam RedeemBy Source # 
StripeHasParam CreateCoupon RedeemBy Source # 

newtype DurationInMonths Source #

Constructors

DurationInMonths Int 

Instances

Eq DurationInMonths Source # 
Data DurationInMonths Source # 

Methods

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

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

toConstr :: DurationInMonths -> Constr #

dataTypeOf :: DurationInMonths -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DurationInMonths Source # 
Read DurationInMonths Source # 
Show DurationInMonths Source # 
ToStripeParam DurationInMonths Source # 
StripeHasParam CreateCoupon DurationInMonths Source # 

newtype IntervalCount Source #

Constructors

IntervalCount Int 

Instances

Eq IntervalCount Source # 
Data IntervalCount Source # 

Methods

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

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

toConstr :: IntervalCount -> Constr #

dataTypeOf :: IntervalCount -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IntervalCount Source # 
Read IntervalCount Source # 
Show IntervalCount Source # 
ToStripeParam IntervalCount Source # 
StripeHasParam CreatePlan IntervalCount Source # 

newtype TrialPeriodDays Source #

Constructors

TrialPeriodDays Int 

Instances

Eq TrialPeriodDays Source # 
Data TrialPeriodDays Source # 

Methods

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

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

toConstr :: TrialPeriodDays -> Constr #

dataTypeOf :: TrialPeriodDays -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrialPeriodDays Source # 
Read TrialPeriodDays Source # 
Show TrialPeriodDays Source # 
ToStripeParam TrialPeriodDays Source # 
StripeHasParam CreatePlan TrialPeriodDays Source # 

newtype Amount Source #

Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1

Constructors

Amount 

Fields

Instances

Eq Amount Source # 

Methods

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

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

Data Amount Source # 

Methods

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

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

toConstr :: Amount -> Constr #

dataTypeOf :: Amount -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Amount Source # 
Read Amount Source # 
Show Amount Source # 
ToStripeParam Amount Source # 
StripeHasParam CreateRefund Amount Source # 
StripeHasParam UpdateInvoiceItem Amount Source # 
StripeHasParam CaptureCharge Amount Source # 
StripeHasParam CreateApplicationFeeRefund Amount Source # 

data Discount Source #

Instances

Eq Discount Source # 
Data Discount Source # 

Methods

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

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

toConstr :: Discount -> Constr #

dataTypeOf :: Discount -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Discount Source # 
Read Discount Source # 
Show Discount Source # 
FromJSON Discount Source #

JSON Instance for Discount

newtype InvoiceId Source #

Constructors

InvoiceId Text 

Instances

Eq InvoiceId Source # 
Data InvoiceId Source # 

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 :: (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 #

Ord InvoiceId Source # 
Read InvoiceId Source # 
Show InvoiceId Source # 
FromJSON InvoiceId Source #

JSON Instance for InvoiceId

ToStripeParam InvoiceId Source # 
StripeHasParam CreateInvoiceItem InvoiceId Source # 
StripeHasParam GetInvoices (EndingBefore InvoiceId) Source # 
StripeHasParam GetInvoices (StartingAfter InvoiceId) Source # 
type ExpandsTo InvoiceId Source # 

data Invoice Source #

Invoice Object

Instances

Eq Invoice Source # 

Methods

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

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

Data Invoice Source # 

Methods

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

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

toConstr :: Invoice -> Constr #

dataTypeOf :: Invoice -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Invoice Source # 
Read Invoice Source # 
Show Invoice Source # 
FromJSON Invoice Source #

JSON Instance for Invoice

newtype InvoiceItemId Source #

Constructors

InvoiceItemId Text 

Instances

Eq InvoiceItemId Source # 
Data InvoiceItemId Source # 

Methods

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

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

toConstr :: InvoiceItemId -> Constr #

dataTypeOf :: InvoiceItemId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceItemId Source # 
Read InvoiceItemId Source # 
Show InvoiceItemId Source # 
ToStripeParam InvoiceItemId Source # 
StripeHasParam GetInvoiceItems (EndingBefore InvoiceItemId) Source # 
StripeHasParam GetInvoiceItems (StartingAfter InvoiceItemId) Source # 
type ExpandsTo InvoiceItemId Source # 

data InvoiceItem Source #

Instances

Eq InvoiceItem Source # 
Data InvoiceItem Source # 

Methods

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

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

toConstr :: InvoiceItem -> Constr #

dataTypeOf :: InvoiceItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceItem Source # 
Read InvoiceItem Source # 
Show InvoiceItem Source # 
FromJSON InvoiceItem Source #

JSON Instance for InvoiceItem

newtype InvoiceLineItemId Source #

Constructors

InvoiceLineItemId Text 

Instances

Eq InvoiceLineItemId Source # 
Data InvoiceLineItemId Source # 

Methods

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

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

toConstr :: InvoiceLineItemId -> Constr #

dataTypeOf :: InvoiceLineItemId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceLineItemId Source # 
Read InvoiceLineItemId Source # 
Show InvoiceLineItemId Source # 
ToStripeParam InvoiceLineItemId Source # 
StripeHasParam GetInvoiceLineItems (EndingBefore InvoiceLineItemId) Source # 
StripeHasParam GetInvoiceLineItems (StartingAfter InvoiceLineItemId) Source # 

data InvoiceLineItemType Source #

Type of InvoiceItem

Instances

Eq InvoiceLineItemType Source # 
Data InvoiceLineItemType Source # 

Methods

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

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

toConstr :: InvoiceLineItemType -> Constr #

dataTypeOf :: InvoiceLineItemType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceLineItemType Source # 
Read InvoiceLineItemType Source # 
Show InvoiceLineItemType Source # 
FromJSON InvoiceLineItemType Source #

JSON Instance for InvoiceLineItemType

data InvoiceLineItem Source #

Instances

Eq InvoiceLineItem Source # 
Data InvoiceLineItem Source # 

Methods

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

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

toConstr :: InvoiceLineItem -> Constr #

dataTypeOf :: InvoiceLineItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceLineItem Source # 
Read InvoiceLineItem Source # 
Show InvoiceLineItem Source # 
FromJSON InvoiceLineItem Source #

JSON Instance for InvoiceLineItem

data Period Source #

Period for an InvoiceLineItem

Constructors

Period 

Fields

Instances

Eq Period Source # 

Methods

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

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

Data Period Source # 

Methods

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

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

toConstr :: Period -> Constr #

dataTypeOf :: Period -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Period Source # 
Read Period Source # 
Show Period Source # 
FromJSON Period Source #

JSON Instance for Period

newtype Closed Source #

Closed - invoice closed or not

Constructors

Closed 

Fields

Instances

Eq Closed Source # 

Methods

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

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

Data Closed Source # 

Methods

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

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

toConstr :: Closed -> Constr #

dataTypeOf :: Closed -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Closed Source # 
Read Closed Source # 
Show Closed Source # 
ToStripeParam Closed Source # 
StripeHasParam UpdateInvoice Closed Source # 

newtype Forgiven Source #

Forgiven - invoice forgiven or not

Constructors

Forgiven 

Fields

Instances

Eq Forgiven Source # 
Data Forgiven Source # 

Methods

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

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

toConstr :: Forgiven -> Constr #

dataTypeOf :: Forgiven -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Forgiven Source # 
Read Forgiven Source # 
Show Forgiven Source # 
ToStripeParam Forgiven Source # 
StripeHasParam UpdateInvoice Forgiven Source # 

data DisputeStatus Source #

Status of a Dispute

Instances

Eq DisputeStatus Source # 
Data DisputeStatus Source # 

Methods

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

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

toConstr :: DisputeStatus -> Constr #

dataTypeOf :: DisputeStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DisputeStatus Source # 
Read DisputeStatus Source # 
Show DisputeStatus Source # 
FromJSON DisputeStatus Source #

JSON Instance for DisputeStatus

data DisputeReason Source #

Reason of a Dispute

Instances

Eq DisputeReason Source # 
Data DisputeReason Source # 

Methods

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

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

toConstr :: DisputeReason -> Constr #

dataTypeOf :: DisputeReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DisputeReason Source # 
Read DisputeReason Source # 
Show DisputeReason Source # 
FromJSON DisputeReason Source #

JSON Instance for DisputeReason

data Dispute Source #

Dispute Object

Instances

Eq Dispute Source # 

Methods

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

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

Data Dispute Source # 

Methods

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

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

toConstr :: Dispute -> Constr #

dataTypeOf :: Dispute -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Dispute Source # 
Read Dispute Source # 
Show Dispute Source # 
FromJSON Dispute Source #

JSON Instance for Dispute

newtype Evidence Source #

Evidence associated with a Dispute

Constructors

Evidence Text 

Instances

Eq Evidence Source # 
Data Evidence Source # 

Methods

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

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Evidence #

toConstr :: Evidence -> Constr #

dataTypeOf :: Evidence -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Evidence) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Evidence) #

gmapT :: (forall b. Data b => b -> b) -> Evidence -> Evidence #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Evidence -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Evidence -> r #

gmapQ :: (forall d. Data d => d -> u) -> Evidence -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Evidence -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Evidence -> m Evidence #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Evidence -> m Evidence #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Evidence -> m Evidence #

Ord Evidence Source # 
Read Evidence Source # 
Show Evidence Source # 
ToStripeParam Evidence Source # 
StripeHasParam UpdateDispute Evidence Source # 

newtype TransferId Source #

Constructors

TransferId Text 

Instances

Eq TransferId Source # 
Data TransferId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransferId -> c TransferId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransferId #

toConstr :: TransferId -> Constr #

dataTypeOf :: TransferId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TransferId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransferId) #

gmapT :: (forall b. Data b => b -> b) -> TransferId -> TransferId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransferId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransferId -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransferId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransferId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransferId -> m TransferId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferId -> m TransferId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferId -> m TransferId #

Ord TransferId Source # 
Read TransferId Source # 
Show TransferId Source # 
ToStripeParam TransferId Source # 
StripeHasParam GetBalanceTransactionHistory TransferId Source # 
StripeHasParam GetTransfers (EndingBefore TransferId) Source # 
StripeHasParam GetTransfers (StartingAfter TransferId) Source # 

data TransferStatus Source #

Status of a Transfer

Instances

Eq TransferStatus Source # 
Data TransferStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransferStatus -> c TransferStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransferStatus #

toConstr :: TransferStatus -> Constr #

dataTypeOf :: TransferStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TransferStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransferStatus) #

gmapT :: (forall b. Data b => b -> b) -> TransferStatus -> TransferStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransferStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransferStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransferStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransferStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransferStatus -> m TransferStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferStatus -> m TransferStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferStatus -> m TransferStatus #

Ord TransferStatus Source # 
Read TransferStatus Source # 
Show TransferStatus Source # 
FromJSON TransferStatus Source #

JSON Instance for TransferStatus

ToStripeParam TransferStatus Source # 
StripeHasParam GetTransfers TransferStatus Source # 

data TransferType Source #

Type of a Transfer

Instances

Eq TransferType Source # 
Data TransferType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransferType -> c TransferType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransferType #

toConstr :: TransferType -> Constr #

dataTypeOf :: TransferType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TransferType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransferType) #

gmapT :: (forall b. Data b => b -> b) -> TransferType -> TransferType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransferType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransferType -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransferType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransferType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransferType -> m TransferType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferType -> m TransferType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransferType -> m TransferType #

Ord TransferType Source # 
Read TransferType Source # 
Show TransferType Source # 
FromJSON TransferType Source #

JSON Instance for TransferType

data Transfer Source #

Transfer Object

Instances

Eq Transfer Source # 
Data Transfer Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Transfer -> c Transfer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Transfer #

toConstr :: Transfer -> Constr #

dataTypeOf :: Transfer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Transfer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Transfer) #

gmapT :: (forall b. Data b => b -> b) -> Transfer -> Transfer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Transfer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Transfer -> r #

gmapQ :: (forall d. Data d => d -> u) -> Transfer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Transfer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Transfer -> m Transfer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Transfer -> m Transfer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Transfer -> m Transfer #

Ord Transfer Source # 
Read Transfer Source # 
Show Transfer Source # 
FromJSON Transfer Source #

JSON Instance for Transfer

data BankAccount Source #

Instances

Eq BankAccount Source # 
Data BankAccount Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BankAccount -> c BankAccount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BankAccount #

toConstr :: BankAccount -> Constr #

dataTypeOf :: BankAccount -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BankAccount) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BankAccount) #

gmapT :: (forall b. Data b => b -> b) -> BankAccount -> BankAccount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BankAccount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BankAccount -> r #

gmapQ :: (forall d. Data d => d -> u) -> BankAccount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BankAccount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BankAccount -> m BankAccount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BankAccount -> m BankAccount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BankAccount -> m BankAccount #

Ord BankAccount Source # 
Read BankAccount Source # 
Show BankAccount Source # 
FromJSON BankAccount Source #

BankAccount JSON Instance

newtype BankAccountId Source #

Constructors

BankAccountId Text 

Instances

Eq BankAccountId Source # 
Data BankAccountId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BankAccountId -> c BankAccountId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BankAccountId #

toConstr :: BankAccountId -> Constr #

dataTypeOf :: BankAccountId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BankAccountId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BankAccountId) #

gmapT :: (forall b. Data b => b -> b) -> BankAccountId -> BankAccountId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BankAccountId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BankAccountId -> r #

gmapQ :: (forall d. Data d => d -> u) -> BankAccountId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BankAccountId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BankAccountId -> m BankAccountId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BankAccountId -> m BankAccountId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BankAccountId -> m BankAccountId #

Ord BankAccountId Source # 
Read BankAccountId Source # 
Show BankAccountId Source # 
ToStripeParam BankAccountId Source # 
StripeHasParam CreateTransfer BankAccountId Source # 

data BankAccountStatus Source #

Constructors

New 
Validated 
Verified 
Errored 

Instances

Eq BankAccountStatus Source # 
Data BankAccountStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BankAccountStatus -> c BankAccountStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BankAccountStatus #

toConstr :: BankAccountStatus -> Constr #

dataTypeOf :: BankAccountStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BankAccountStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BankAccountStatus) #

gmapT :: (forall b. Data b => b -> b) -> BankAccountStatus -> BankAccountStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BankAccountStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BankAccountStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> BankAccountStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BankAccountStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BankAccountStatus -> m BankAccountStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BankAccountStatus -> m BankAccountStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BankAccountStatus -> m BankAccountStatus #

Ord BankAccountStatus Source # 
Read BankAccountStatus Source # 
Show BankAccountStatus Source # 
FromJSON BankAccountStatus Source #

BankAccountStatus JSON instance

newtype RoutingNumber Source #

Routing Number for Bank Account

Constructors

RoutingNumber Text 

Instances

Eq RoutingNumber Source # 
Data RoutingNumber Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoutingNumber -> c RoutingNumber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RoutingNumber #

toConstr :: RoutingNumber -> Constr #

dataTypeOf :: RoutingNumber -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RoutingNumber) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RoutingNumber) #

gmapT :: (forall b. Data b => b -> b) -> RoutingNumber -> RoutingNumber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoutingNumber -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoutingNumber -> r #

gmapQ :: (forall d. Data d => d -> u) -> RoutingNumber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoutingNumber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoutingNumber -> m RoutingNumber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoutingNumber -> m RoutingNumber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoutingNumber -> m RoutingNumber #

Ord RoutingNumber Source # 
Read RoutingNumber Source # 
Show RoutingNumber Source # 

newtype Country Source #

Country

Constructors

Country Text 

Instances

Eq Country Source # 

Methods

(==) :: Country -> Country -> Bool #

(/=) :: Country -> Country -> Bool #

Data Country Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Country -> c Country #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Country #

toConstr :: Country -> Constr #

dataTypeOf :: Country -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Country) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Country) #

gmapT :: (forall b. Data b => b -> b) -> Country -> Country #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r #

gmapQ :: (forall d. Data d => d -> u) -> Country -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Country -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Country -> m Country #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country #

Ord Country Source # 
Read Country Source # 
Show Country Source # 

newtype AccountNumber Source #

Account Number of a Bank Account

Constructors

AccountNumber Text 

Instances

Eq AccountNumber Source # 
Data AccountNumber Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountNumber -> c AccountNumber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountNumber #

toConstr :: AccountNumber -> Constr #

dataTypeOf :: AccountNumber -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountNumber) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountNumber) #

gmapT :: (forall b. Data b => b -> b) -> AccountNumber -> AccountNumber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountNumber -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountNumber -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountNumber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountNumber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountNumber -> m AccountNumber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountNumber -> m AccountNumber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountNumber -> m AccountNumber #

Ord AccountNumber Source # 
Read AccountNumber Source # 
Show AccountNumber Source # 

data NewBankAccount Source #

create a new BankAccount

Instances

Eq NewBankAccount Source # 
Data NewBankAccount Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewBankAccount -> c NewBankAccount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewBankAccount #

toConstr :: NewBankAccount -> Constr #

dataTypeOf :: NewBankAccount -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NewBankAccount) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewBankAccount) #

gmapT :: (forall b. Data b => b -> b) -> NewBankAccount -> NewBankAccount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewBankAccount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewBankAccount -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewBankAccount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewBankAccount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewBankAccount -> m NewBankAccount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewBankAccount -> m NewBankAccount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewBankAccount -> m NewBankAccount #

Ord NewBankAccount Source # 
Read NewBankAccount Source # 
Show NewBankAccount Source # 
ToStripeParam NewBankAccount Source # 
StripeHasParam UpdateRecipient NewBankAccount Source # 
StripeHasParam CreateRecipient NewBankAccount Source # 

newtype FirstName Source #

Recipients

FirstName of a Recipient

Constructors

FirstName Text 

Instances

Eq FirstName Source # 
Data FirstName Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FirstName -> c FirstName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FirstName #

toConstr :: FirstName -> Constr #

dataTypeOf :: FirstName -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FirstName) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FirstName) #

gmapT :: (forall b. Data b => b -> b) -> FirstName -> FirstName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FirstName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FirstName -> r #

gmapQ :: (forall d. Data d => d -> u) -> FirstName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FirstName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FirstName -> m FirstName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FirstName -> m FirstName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FirstName -> m FirstName #

Ord FirstName Source # 
Read FirstName Source # 
Show FirstName Source # 

newtype LastName Source #

Constructors

LastName Text 

Instances

Eq LastName Source # 
Data LastName Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LastName -> c LastName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LastName #

toConstr :: LastName -> Constr #

dataTypeOf :: LastName -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LastName) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LastName) #

gmapT :: (forall b. Data b => b -> b) -> LastName -> LastName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LastName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LastName -> r #

gmapQ :: (forall d. Data d => d -> u) -> LastName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LastName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LastName -> m LastName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LastName -> m LastName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LastName -> m LastName #

Ord LastName Source # 
Read LastName Source # 
Show LastName Source # 

type MiddleInitial = Char Source #

Middle Initial of a Recipient

newtype RecipientId Source #

Constructors

RecipientId Text 

Instances

Eq RecipientId Source # 
Data RecipientId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecipientId -> c RecipientId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecipientId #

toConstr :: RecipientId -> Constr #

dataTypeOf :: RecipientId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RecipientId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecipientId) #

gmapT :: (forall b. Data b => b -> b) -> RecipientId -> RecipientId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecipientId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecipientId -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecipientId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecipientId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecipientId -> m RecipientId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecipientId -> m RecipientId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecipientId -> m RecipientId #

Ord RecipientId Source # 
Read RecipientId Source # 
Show RecipientId Source # 
FromJSON RecipientId Source #

JSON Instance for RecipientId

ToStripeParam RecipientId Source # 
StripeHasParam GetTransfers RecipientId Source # 
StripeHasParam GetRecipients (EndingBefore RecipientId) Source # 
StripeHasParam GetRecipients (StartingAfter RecipientId) Source # 
type ExpandsTo RecipientId Source # 

newtype TaxID Source #

Constructors

TaxID 

Fields

Instances

Eq TaxID Source # 

Methods

(==) :: TaxID -> TaxID -> Bool #

(/=) :: TaxID -> TaxID -> Bool #

Data TaxID Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TaxID -> c TaxID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TaxID #

toConstr :: TaxID -> Constr #

dataTypeOf :: TaxID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TaxID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaxID) #

gmapT :: (forall b. Data b => b -> b) -> TaxID -> TaxID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TaxID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TaxID -> r #

gmapQ :: (forall d. Data d => d -> u) -> TaxID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TaxID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID #

Ord TaxID Source # 

Methods

compare :: TaxID -> TaxID -> Ordering #

(<) :: TaxID -> TaxID -> Bool #

(<=) :: TaxID -> TaxID -> Bool #

(>) :: TaxID -> TaxID -> Bool #

(>=) :: TaxID -> TaxID -> Bool #

max :: TaxID -> TaxID -> TaxID #

min :: TaxID -> TaxID -> TaxID #

Read TaxID Source # 
Show TaxID Source # 

Methods

showsPrec :: Int -> TaxID -> ShowS #

show :: TaxID -> String #

showList :: [TaxID] -> ShowS #

ToStripeParam TaxID Source # 
StripeHasParam UpdateRecipient TaxID Source # 
StripeHasParam CreateRecipient TaxID Source # 

data RecipientType Source #

Type of Recipient

Constructors

Individual 
Corporation 

Instances

Eq RecipientType Source # 
Data RecipientType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecipientType -> c RecipientType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecipientType #

toConstr :: RecipientType -> Constr #

dataTypeOf :: RecipientType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RecipientType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecipientType) #

gmapT :: (forall b. Data b => b -> b) -> RecipientType -> RecipientType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecipientType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecipientType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecipientType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecipientType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecipientType -> m RecipientType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecipientType -> m RecipientType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecipientType -> m RecipientType #

Ord RecipientType Source # 
Read RecipientType Source #

Read instance for RecipientType

Show RecipientType Source #

Show instance for RecipientType

FromJSON RecipientType Source #

JSON Instance for RecipientType

ToStripeParam RecipientType Source # 

data Recipient Source #

Recipient Object

Instances

Eq Recipient Source # 
Data Recipient Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Recipient -> c Recipient #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Recipient #

toConstr :: Recipient -> Constr #

dataTypeOf :: Recipient -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Recipient) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Recipient) #

gmapT :: (forall b. Data b => b -> b) -> Recipient -> Recipient #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r #

gmapQ :: (forall d. Data d => d -> u) -> Recipient -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Recipient -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient #

Ord Recipient Source # 
Read Recipient Source # 
Show Recipient Source # 
FromJSON Recipient Source #

JSON Instance for Recipient

newtype ApplicationFeeId Source #

PlanId for a Plan

Constructors

ApplicationFeeId Text 

Instances

Eq ApplicationFeeId Source # 
Data ApplicationFeeId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationFeeId -> c ApplicationFeeId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationFeeId #

toConstr :: ApplicationFeeId -> Constr #

dataTypeOf :: ApplicationFeeId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationFeeId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationFeeId) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationFeeId -> ApplicationFeeId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeeId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeeId -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationFeeId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationFeeId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationFeeId -> m ApplicationFeeId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeeId -> m ApplicationFeeId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeeId -> m ApplicationFeeId #

Ord ApplicationFeeId Source # 
Read ApplicationFeeId Source # 
Show ApplicationFeeId Source # 
ToStripeParam ApplicationFeeId Source # 
StripeHasParam UpdateInvoice ApplicationFeeId Source # 
StripeHasParam CreateInvoice ApplicationFeeId Source # 
StripeHasParam GetApplicationFees (EndingBefore ApplicationFeeId) Source # 
StripeHasParam GetApplicationFees (StartingAfter ApplicationFeeId) Source # 

data ApplicationFee Source #

ApplicationFee Object

Instances

Eq ApplicationFee Source # 
Data ApplicationFee Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationFee -> c ApplicationFee #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationFee #

toConstr :: ApplicationFee -> Constr #

dataTypeOf :: ApplicationFee -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationFee) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationFee) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationFee -> ApplicationFee #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFee -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFee -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationFee -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationFee -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationFee -> m ApplicationFee #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFee -> m ApplicationFee #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFee -> m ApplicationFee #

Ord ApplicationFee Source # 
Read ApplicationFee Source # 
Show ApplicationFee Source # 
FromJSON ApplicationFee Source #

JSON Instance for ApplicationFee

newtype ApplicationFeePercent Source #

ApplicationFeePercent

Instances

Eq ApplicationFeePercent Source # 
Data ApplicationFeePercent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationFeePercent -> c ApplicationFeePercent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationFeePercent #

toConstr :: ApplicationFeePercent -> Constr #

dataTypeOf :: ApplicationFeePercent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationFeePercent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationFeePercent) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationFeePercent -> ApplicationFeePercent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeePercent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeePercent -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationFeePercent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationFeePercent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationFeePercent -> m ApplicationFeePercent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeePercent -> m ApplicationFeePercent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeePercent -> m ApplicationFeePercent #

Ord ApplicationFeePercent Source # 
Read ApplicationFeePercent Source # 
Show ApplicationFeePercent Source # 
ToStripeParam ApplicationFeePercent Source # 
StripeHasParam UpdateSubscription ApplicationFeePercent Source # 
StripeHasParam CreateSubscription ApplicationFeePercent Source # 

newtype ApplicationFeeAmount Source #

ApplicationFeeAmount

Instances

Eq ApplicationFeeAmount Source # 
Data ApplicationFeeAmount Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationFeeAmount -> c ApplicationFeeAmount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationFeeAmount #

toConstr :: ApplicationFeeAmount -> Constr #

dataTypeOf :: ApplicationFeeAmount -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationFeeAmount) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationFeeAmount) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationFeeAmount -> ApplicationFeeAmount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeeAmount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeeAmount -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationFeeAmount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationFeeAmount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationFeeAmount -> m ApplicationFeeAmount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeeAmount -> m ApplicationFeeAmount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeeAmount -> m ApplicationFeeAmount #

Ord ApplicationFeeAmount Source # 
Read ApplicationFeeAmount Source # 
Show ApplicationFeeAmount Source # 
ToStripeParam ApplicationFeeAmount Source # 
StripeHasParam CreateCharge ApplicationFeeAmount Source # 

newtype ApplicationId Source #

Constructors

ApplicationId Text 

Instances

Eq ApplicationId Source # 
Data ApplicationId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationId -> c ApplicationId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationId #

toConstr :: ApplicationId -> Constr #

dataTypeOf :: ApplicationId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationId) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationId -> ApplicationId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationId -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationId -> m ApplicationId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationId -> m ApplicationId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationId -> m ApplicationId #

Ord ApplicationId Source # 
Read ApplicationId Source # 
Show ApplicationId Source # 

newtype FeeId Source #

FeeId for objects with Fees

Constructors

FeeId Text 

Instances

Eq FeeId Source # 

Methods

(==) :: FeeId -> FeeId -> Bool #

(/=) :: FeeId -> FeeId -> Bool #

Data FeeId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FeeId -> c FeeId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FeeId #

toConstr :: FeeId -> Constr #

dataTypeOf :: FeeId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FeeId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FeeId) #

gmapT :: (forall b. Data b => b -> b) -> FeeId -> FeeId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FeeId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FeeId -> r #

gmapQ :: (forall d. Data d => d -> u) -> FeeId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FeeId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId #

Ord FeeId Source # 

Methods

compare :: FeeId -> FeeId -> Ordering #

(<) :: FeeId -> FeeId -> Bool #

(<=) :: FeeId -> FeeId -> Bool #

(>) :: FeeId -> FeeId -> Bool #

(>=) :: FeeId -> FeeId -> Bool #

max :: FeeId -> FeeId -> FeeId #

min :: FeeId -> FeeId -> FeeId #

Read FeeId Source # 
Show FeeId Source # 

Methods

showsPrec :: Int -> FeeId -> ShowS #

show :: FeeId -> String #

showList :: [FeeId] -> ShowS #

data ApplicationFeeRefund Source #

Application Fee Refunds

Instances

Eq ApplicationFeeRefund Source # 
Data ApplicationFeeRefund Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationFeeRefund -> c ApplicationFeeRefund #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationFeeRefund #

toConstr :: ApplicationFeeRefund -> Constr #

dataTypeOf :: ApplicationFeeRefund -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationFeeRefund) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationFeeRefund) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationFeeRefund -> ApplicationFeeRefund #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeeRefund -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationFeeRefund -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationFeeRefund -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationFeeRefund -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationFeeRefund -> m ApplicationFeeRefund #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeeRefund -> m ApplicationFeeRefund #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationFeeRefund -> m ApplicationFeeRefund #

Ord ApplicationFeeRefund Source # 
Read ApplicationFeeRefund Source # 
Show ApplicationFeeRefund Source # 
FromJSON ApplicationFeeRefund Source #

JSON Instance for ApplicationFeeRefund

newtype AccountId Source #

Constructors

AccountId Text 

Instances

Eq AccountId Source # 
Data AccountId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountId -> c AccountId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountId #

toConstr :: AccountId -> Constr #

dataTypeOf :: AccountId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountId) #

gmapT :: (forall b. Data b => b -> b) -> AccountId -> AccountId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId #

Ord AccountId Source # 
Read AccountId Source # 
Show AccountId Source # 
FromJSON AccountId Source #

JSON Instance for AccountId

type ExpandsTo AccountId Source # 

data Account Source #

Account Object

Instances

Eq Account Source # 

Methods

(==) :: Account -> Account -> Bool #

(/=) :: Account -> Account -> Bool #

Data Account Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account #

toConstr :: Account -> Constr #

dataTypeOf :: Account -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Account) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) #

gmapT :: (forall b. Data b => b -> b) -> Account -> Account #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

Ord Account Source # 
Read Account Source # 
Show Account Source # 
FromJSON Account Source #

JSON Instance for Account

data Balance Source #

Balance Object

Instances

Eq Balance Source # 

Methods

(==) :: Balance -> Balance -> Bool #

(/=) :: Balance -> Balance -> Bool #

Data Balance Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Balance -> c Balance #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Balance #

toConstr :: Balance -> Constr #

dataTypeOf :: Balance -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Balance) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Balance) #

gmapT :: (forall b. Data b => b -> b) -> Balance -> Balance #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Balance -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Balance -> r #

gmapQ :: (forall d. Data d => d -> u) -> Balance -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Balance -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Balance -> m Balance #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Balance -> m Balance #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Balance -> m Balance #

Ord Balance Source # 
Read Balance Source # 
Show Balance Source # 
FromJSON Balance Source #

JSON Instance for Balance

data BalanceAmount Source #

Instances

Eq BalanceAmount Source # 
Data BalanceAmount Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BalanceAmount -> c BalanceAmount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BalanceAmount #

toConstr :: BalanceAmount -> Constr #

dataTypeOf :: BalanceAmount -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BalanceAmount) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BalanceAmount) #

gmapT :: (forall b. Data b => b -> b) -> BalanceAmount -> BalanceAmount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BalanceAmount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BalanceAmount -> r #

gmapQ :: (forall d. Data d => d -> u) -> BalanceAmount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BalanceAmount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BalanceAmount -> m BalanceAmount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceAmount -> m BalanceAmount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceAmount -> m BalanceAmount #

Ord BalanceAmount Source # 
Read BalanceAmount Source # 
Show BalanceAmount Source # 
FromJSON BalanceAmount Source #

JSON Instance for BalanceAmount

data BalanceTransaction Source #

Instances

Eq BalanceTransaction Source # 
Data BalanceTransaction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BalanceTransaction -> c BalanceTransaction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BalanceTransaction #

toConstr :: BalanceTransaction -> Constr #

dataTypeOf :: BalanceTransaction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BalanceTransaction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BalanceTransaction) #

gmapT :: (forall b. Data b => b -> b) -> BalanceTransaction -> BalanceTransaction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BalanceTransaction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BalanceTransaction -> r #

gmapQ :: (forall d. Data d => d -> u) -> BalanceTransaction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BalanceTransaction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BalanceTransaction -> m BalanceTransaction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceTransaction -> m BalanceTransaction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceTransaction -> m BalanceTransaction #

Ord BalanceTransaction Source # 
Read BalanceTransaction Source # 
Show BalanceTransaction Source # 
FromJSON BalanceTransaction Source #

JSON Instance for BalanceTransaction

newtype TransactionId Source #

TransactionId of a Transaction

Constructors

TransactionId Text 

Instances

Eq TransactionId Source # 
Data TransactionId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransactionId -> c TransactionId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransactionId #

toConstr :: TransactionId -> Constr #

dataTypeOf :: TransactionId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TransactionId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransactionId) #

gmapT :: (forall b. Data b => b -> b) -> TransactionId -> TransactionId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransactionId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransactionId -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransactionId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransactionId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransactionId -> m TransactionId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransactionId -> m TransactionId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransactionId -> m TransactionId #

Ord TransactionId Source # 
Read TransactionId Source # 
Show TransactionId Source # 
FromJSON TransactionId Source #

JSON Instance for TransactionId

ToStripeParam TransactionId Source # 
StripeHasParam GetBalanceTransactionHistory (EndingBefore TransactionId) Source # 
StripeHasParam GetBalanceTransactionHistory (StartingAfter TransactionId) Source # 
type ExpandsTo TransactionId Source # 

data FeeDetails Source #

FeeDetails Object

Instances

Eq FeeDetails Source # 
Data FeeDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FeeDetails -> c FeeDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FeeDetails #

toConstr :: FeeDetails -> Constr #

dataTypeOf :: FeeDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FeeDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FeeDetails) #

gmapT :: (forall b. Data b => b -> b) -> FeeDetails -> FeeDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FeeDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FeeDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> FeeDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FeeDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FeeDetails -> m FeeDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeDetails -> m FeeDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeDetails -> m FeeDetails #

Ord FeeDetails Source # 
Read FeeDetails Source # 
Show FeeDetails Source # 
FromJSON FeeDetails Source #

JSON Instance for FeeDetails

newtype Source a Source #

Source used for filtering Balance transactions. It should contain an object Id such as a ChargeId

Constructors

Source 

Fields

Instances

ToStripeParam a => StripeHasParam GetBalanceTransactionHistory (Source a) Source # 
Eq a => Eq (Source a) Source # 

Methods

(==) :: Source a -> Source a -> Bool #

(/=) :: Source a -> Source a -> Bool #

Data a => Data (Source a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Source a -> c (Source a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Source a) #

toConstr :: Source a -> Constr #

dataTypeOf :: Source a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Source a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Source a)) #

gmapT :: (forall b. Data b => b -> b) -> Source a -> Source a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Source a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Source a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Source a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Source a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Source a -> m (Source a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Source a -> m (Source a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Source a -> m (Source a) #

Ord a => Ord (Source a) Source # 

Methods

compare :: Source a -> Source a -> Ordering #

(<) :: Source a -> Source a -> Bool #

(<=) :: Source a -> Source a -> Bool #

(>) :: Source a -> Source a -> Bool #

(>=) :: Source a -> Source a -> Bool #

max :: Source a -> Source a -> Source a #

min :: Source a -> Source a -> Source a #

Read a => Read (Source a) Source # 
Show a => Show (Source a) Source # 

Methods

showsPrec :: Int -> Source a -> ShowS #

show :: Source a -> String #

showList :: [Source a] -> ShowS #

ToStripeParam a => ToStripeParam (Source a) Source # 

data TransactionType Source #

transaction type for BalanceTransaction

Instances

Eq TransactionType Source # 
Data TransactionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransactionType -> c TransactionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransactionType #

toConstr :: TransactionType -> Constr #

dataTypeOf :: TransactionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TransactionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransactionType) #

gmapT :: (forall b. Data b => b -> b) -> TransactionType -> TransactionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransactionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransactionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransactionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransactionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransactionType -> m TransactionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransactionType -> m TransactionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransactionType -> m TransactionType #

Ord TransactionType Source # 
Read TransactionType Source # 
Show TransactionType Source # 
ToJSON TransactionType Source # 
FromJSON TransactionType Source # 
ToStripeParam TransactionType Source # 
StripeHasParam GetBalanceTransactionHistory TransactionType Source # 

data EventType Source #

Event Types

Instances

Eq EventType Source # 
Data EventType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventType -> c EventType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventType #

toConstr :: EventType -> Constr #

dataTypeOf :: EventType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventType) #

gmapT :: (forall b. Data b => b -> b) -> EventType -> EventType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventType -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventType -> m EventType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventType -> m EventType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventType -> m EventType #

Ord EventType Source # 
Read EventType Source # 
Show EventType Source # 
FromJSON EventType Source #

Event Types JSON Instance

newtype EventId Source #

Constructors

EventId Text 

Instances

Eq EventId Source # 

Methods

(==) :: EventId -> EventId -> Bool #

(/=) :: EventId -> EventId -> Bool #

Data EventId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventId -> c EventId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventId #

toConstr :: EventId -> Constr #

dataTypeOf :: EventId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventId) #

gmapT :: (forall b. Data b => b -> b) -> EventId -> EventId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventId -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventId -> m EventId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventId -> m EventId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventId -> m EventId #

Ord EventId Source # 
Read EventId Source # 
Show EventId Source # 
ToStripeParam EventId Source # 
StripeHasParam GetEvents (EndingBefore EventId) Source # 
StripeHasParam GetEvents (StartingAfter EventId) Source # 

data EventData Source #

EventData

Instances

Eq EventData Source # 
Data EventData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventData -> c EventData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventData #

toConstr :: EventData -> Constr #

dataTypeOf :: EventData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventData) #

gmapT :: (forall b. Data b => b -> b) -> EventData -> EventData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventData -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventData -> m EventData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventData -> m EventData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventData -> m EventData #

Ord EventData Source # 
Read EventData Source # 
Show EventData Source # 

data Event Source #

Event Object

Instances

Eq Event Source # 

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Data Event Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Event -> c Event #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Event #

toConstr :: Event -> Constr #

dataTypeOf :: Event -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Event) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event) #

gmapT :: (forall b. Data b => b -> b) -> Event -> Event #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r #

gmapQ :: (forall d. Data d => d -> u) -> Event -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Event -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Event -> m Event #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event #

Ord Event Source # 

Methods

compare :: Event -> Event -> Ordering #

(<) :: Event -> Event -> Bool #

(<=) :: Event -> Event -> Bool #

(>) :: Event -> Event -> Bool #

(>=) :: Event -> Event -> Bool #

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Read Event Source # 
Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

FromJSON Event Source #

JSON Instance for Event

data ConnectApp Source #

Connect Application

Instances

Eq ConnectApp Source # 
Data ConnectApp Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConnectApp -> c ConnectApp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConnectApp #

toConstr :: ConnectApp -> Constr #

dataTypeOf :: ConnectApp -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConnectApp) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConnectApp) #

gmapT :: (forall b. Data b => b -> b) -> ConnectApp -> ConnectApp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConnectApp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConnectApp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConnectApp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConnectApp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConnectApp -> m ConnectApp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectApp -> m ConnectApp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConnectApp -> m ConnectApp #

Ord ConnectApp Source # 
Read ConnectApp Source # 
Show ConnectApp Source # 
FromJSON ConnectApp Source #

Connect Application JSON instance

newtype TokenId Source #

Constructors

TokenId Text 

Instances

Eq TokenId Source # 

Methods

(==) :: TokenId -> TokenId -> Bool #

(/=) :: TokenId -> TokenId -> Bool #

Data TokenId Source # 

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 :: (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 #

Ord TokenId Source # 
Read TokenId Source # 
Show TokenId Source # 
ToStripeParam TokenId Source # 
StripeHasParam UpdateRecipient TokenId Source # 
StripeHasParam CreateRecipient TokenId Source # 
StripeHasParam UpdateCustomer TokenId Source # 
StripeHasParam CreateCustomer TokenId Source # 
StripeHasParam CreateCharge TokenId Source # 

data TokenType Source #

Type of Token

Instances

Eq TokenType Source # 
Data TokenType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenType -> c TokenType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenType #

toConstr :: TokenType -> Constr #

dataTypeOf :: TokenType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TokenType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType) #

gmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r #

gmapQ :: (forall d. Data d => d -> u) -> TokenType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType #

Ord TokenType Source # 
Read TokenType Source # 
Show TokenType Source # 
FromJSON TokenType Source #

JSON Instance for TokenType

data Token a Source #

Token Object

Instances

Eq a => Eq (Token a) Source # 

Methods

(==) :: Token a -> Token a -> Bool #

(/=) :: Token a -> Token a -> Bool #

Data a => Data (Token a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Token a -> c (Token a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Token a) #

toConstr :: Token a -> Constr #

dataTypeOf :: Token a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Token a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Token a)) #

gmapT :: (forall b. Data b => b -> b) -> Token a -> Token a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Token a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Token a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Token a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Token a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Token a -> m (Token a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Token a -> m (Token a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Token a -> m (Token a) #

Ord a => Ord (Token a) Source # 

Methods

compare :: Token a -> Token a -> Ordering #

(<) :: Token a -> Token a -> Bool #

(<=) :: Token a -> Token a -> Bool #

(>) :: Token a -> Token a -> Bool #

(>=) :: Token a -> Token a -> Bool #

max :: Token a -> Token a -> Token a #

min :: Token a -> Token a -> Token a #

Read a => Read (Token a) Source # 
Show a => Show (Token a) Source # 

Methods

showsPrec :: Int -> Token a -> ShowS #

show :: Token a -> String #

showList :: [Token a] -> ShowS #

FromJSON a => FromJSON (Token a) Source #

JSON Instance for Token

data StripeList a Source #

Generic handling of Stripe JSON arrays

Constructors

StripeList 

Fields

Instances

Eq a => Eq (StripeList a) Source # 

Methods

(==) :: StripeList a -> StripeList a -> Bool #

(/=) :: StripeList a -> StripeList a -> Bool #

Data a => Data (StripeList a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StripeList a -> c (StripeList a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StripeList a) #

toConstr :: StripeList a -> Constr #

dataTypeOf :: StripeList a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (StripeList a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StripeList a)) #

gmapT :: (forall b. Data b => b -> b) -> StripeList a -> StripeList a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StripeList a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StripeList a -> r #

gmapQ :: (forall d. Data d => d -> u) -> StripeList a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StripeList a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StripeList a -> m (StripeList a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeList a -> m (StripeList a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeList a -> m (StripeList a) #

Ord a => Ord (StripeList a) Source # 
Read a => Read (StripeList a) Source # 
Show a => Show (StripeList a) Source # 
FromJSON a => FromJSON (StripeList a) Source #

JSON Instance for StripeList

newtype Limit Source #

Pagination Option for StripeList

Constructors

Limit Int 

Instances

Eq Limit Source # 

Methods

(==) :: Limit -> Limit -> Bool #

(/=) :: Limit -> Limit -> Bool #

Data Limit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Limit -> c Limit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Limit #

toConstr :: Limit -> Constr #

dataTypeOf :: Limit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Limit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Limit) #

gmapT :: (forall b. Data b => b -> b) -> Limit -> Limit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Limit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Limit -> r #

gmapQ :: (forall d. Data d => d -> u) -> Limit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Limit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Limit -> m Limit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Limit -> m Limit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Limit -> m Limit #

Ord Limit Source # 

Methods

compare :: Limit -> Limit -> Ordering #

(<) :: Limit -> Limit -> Bool #

(<=) :: Limit -> Limit -> Bool #

(>) :: Limit -> Limit -> Bool #

(>=) :: Limit -> Limit -> Bool #

max :: Limit -> Limit -> Limit #

min :: Limit -> Limit -> Limit #

Read Limit Source # 
Show Limit Source # 

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

ToStripeParam Limit Source # 
StripeHasParam GetSubscriptions Limit Source # 
StripeHasParam GetTransfers Limit Source # 
StripeHasParam GetRefunds Limit Source # 
StripeHasParam GetRecipients Limit Source # 
StripeHasParam GetPlans Limit Source # 
StripeHasParam GetInvoiceItems Limit Source # 
StripeHasParam GetInvoiceLineItems Limit Source # 
StripeHasParam GetInvoices Limit Source # 
StripeHasParam GetEvents Limit Source # 
StripeHasParam GetCustomers Limit Source # 
StripeHasParam GetCoupons Limit Source # 
StripeHasParam GetCharges Limit Source # 
StripeHasParam GetRecipientCards Limit Source # 
StripeHasParam GetCustomerCards Limit Source # 
StripeHasParam GetBalanceTransactionHistory Limit Source # 
StripeHasParam GetApplicationFeeRefunds Limit Source # 
StripeHasParam GetApplicationFees Limit Source # 

newtype StartingAfter a Source #

Pagination Option for StripeList

Constructors

StartingAfter a 

Instances

StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source # 
StripeHasParam GetTransfers (StartingAfter TransferId) Source # 
StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetRecipients (StartingAfter RecipientId) Source # 
StripeHasParam GetPlans (StartingAfter PlanId) Source # 
StripeHasParam GetInvoiceItems (StartingAfter InvoiceItemId) Source # 
StripeHasParam GetInvoiceLineItems (StartingAfter InvoiceLineItemId) Source # 
StripeHasParam GetInvoices (StartingAfter InvoiceId) Source # 
StripeHasParam GetEvents (StartingAfter EventId) Source # 
StripeHasParam GetCustomers (StartingAfter CustomerId) Source # 
StripeHasParam GetCoupons (StartingAfter CouponId) Source # 
StripeHasParam GetCharges (StartingAfter ChargeId) Source # 
StripeHasParam GetRecipientCards (StartingAfter CardId) Source # 
StripeHasParam GetCustomerCards (StartingAfter CardId) Source # 
StripeHasParam GetBalanceTransactionHistory (StartingAfter TransactionId) Source # 
StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetApplicationFees (StartingAfter ApplicationFeeId) Source # 
Eq a => Eq (StartingAfter a) Source # 
Data a => Data (StartingAfter a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StartingAfter a -> c (StartingAfter a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StartingAfter a) #

toConstr :: StartingAfter a -> Constr #

dataTypeOf :: StartingAfter a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (StartingAfter a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StartingAfter a)) #

gmapT :: (forall b. Data b => b -> b) -> StartingAfter a -> StartingAfter a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StartingAfter a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StartingAfter a -> r #

gmapQ :: (forall d. Data d => d -> u) -> StartingAfter a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StartingAfter a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StartingAfter a -> m (StartingAfter a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StartingAfter a -> m (StartingAfter a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StartingAfter a -> m (StartingAfter a) #

Ord a => Ord (StartingAfter a) Source # 
Read a => Read (StartingAfter a) Source # 
Show a => Show (StartingAfter a) Source # 
ToStripeParam param => ToStripeParam (StartingAfter param) Source # 

newtype EndingBefore a Source #

Pagination Option for StripeList

Constructors

EndingBefore a 

Instances

StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
StripeHasParam GetTransfers (EndingBefore TransferId) Source # 
StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetRecipients (EndingBefore RecipientId) Source # 
StripeHasParam GetPlans (EndingBefore PlanId) Source # 
StripeHasParam GetInvoiceItems (EndingBefore InvoiceItemId) Source # 
StripeHasParam GetInvoiceLineItems (EndingBefore InvoiceLineItemId) Source # 
StripeHasParam GetInvoices (EndingBefore InvoiceId) Source # 
StripeHasParam GetEvents (EndingBefore EventId) Source # 
StripeHasParam GetCustomers (EndingBefore CustomerId) Source # 
StripeHasParam GetCoupons (EndingBefore CouponId) Source # 
StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
StripeHasParam GetBalanceTransactionHistory (EndingBefore TransactionId) Source # 
StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetApplicationFees (EndingBefore ApplicationFeeId) Source # 
Eq a => Eq (EndingBefore a) Source # 
Data a => Data (EndingBefore a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndingBefore a -> c (EndingBefore a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EndingBefore a) #

toConstr :: EndingBefore a -> Constr #

dataTypeOf :: EndingBefore a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (EndingBefore a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EndingBefore a)) #

gmapT :: (forall b. Data b => b -> b) -> EndingBefore a -> EndingBefore a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndingBefore a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndingBefore a -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndingBefore a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndingBefore a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndingBefore a -> m (EndingBefore a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndingBefore a -> m (EndingBefore a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndingBefore a -> m (EndingBefore a) #

Ord a => Ord (EndingBefore a) Source # 
Read a => Read (EndingBefore a) Source # 
Show a => Show (EndingBefore a) Source # 
ToStripeParam param => ToStripeParam (EndingBefore param) Source # 

data StripeDeleteResult Source #

JSON returned from a Stripe deletion request

Constructors

StripeDeleteResult 

Instances

Eq StripeDeleteResult Source # 
Data StripeDeleteResult Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StripeDeleteResult -> c StripeDeleteResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StripeDeleteResult #

toConstr :: StripeDeleteResult -> Constr #

dataTypeOf :: StripeDeleteResult -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StripeDeleteResult) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StripeDeleteResult) #

gmapT :: (forall b. Data b => b -> b) -> StripeDeleteResult -> StripeDeleteResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StripeDeleteResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StripeDeleteResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> StripeDeleteResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StripeDeleteResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StripeDeleteResult -> m StripeDeleteResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeDeleteResult -> m StripeDeleteResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeDeleteResult -> m StripeDeleteResult #

Ord StripeDeleteResult Source # 
Read StripeDeleteResult Source # 
Show StripeDeleteResult Source # 
FromJSON StripeDeleteResult Source #

JSON Instance for StripeDeleteResult

newtype MetaData Source #

Type of MetaData for use on Stripe objects

Constructors

MetaData [(Text, Text)] 

Instances

Eq MetaData Source # 
Data MetaData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MetaData -> c MetaData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MetaData #

toConstr :: MetaData -> Constr #

dataTypeOf :: MetaData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MetaData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaData) #

gmapT :: (forall b. Data b => b -> b) -> MetaData -> MetaData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MetaData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetaData -> r #

gmapQ :: (forall d. Data d => d -> u) -> MetaData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MetaData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetaData -> m MetaData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetaData -> m MetaData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetaData -> m MetaData #

Ord MetaData Source # 
Read MetaData Source # 
Show MetaData Source # 
FromJSON MetaData Source # 
ToStripeParam MetaData Source # 
StripeHasParam UpdateSubscription MetaData Source # 
StripeHasParam CreateSubscription MetaData Source # 
StripeHasParam UpdateTransfer MetaData Source # 
StripeHasParam CreateTransfer MetaData Source # 
StripeHasParam UpdateRefund MetaData Source # 
StripeHasParam CreateRefund MetaData Source # 
StripeHasParam UpdateRecipient MetaData Source # 
StripeHasParam CreateRecipient MetaData Source # 
StripeHasParam UpdatePlan MetaData Source # 
StripeHasParam CreatePlan MetaData Source # 
StripeHasParam UpdateInvoiceItem MetaData Source # 
StripeHasParam CreateInvoiceItem MetaData Source # 
StripeHasParam UpdateInvoice MetaData Source # 
StripeHasParam CreateInvoice MetaData Source # 
StripeHasParam UpdateDispute MetaData Source # 
StripeHasParam UpdateCustomer MetaData Source # 
StripeHasParam CreateCustomer MetaData Source # 
StripeHasParam UpdateCoupon MetaData Source # 
StripeHasParam CreateCoupon MetaData Source # 
StripeHasParam UpdateCharge MetaData Source # 
StripeHasParam CreateCharge MetaData Source # 
StripeHasParam UpdateApplicationFeeRefund MetaData Source # 
StripeHasParam CreateApplicationFeeRefund MetaData Source # 

newtype ExpandParams Source #

Type of Expansion Parameters for use on Stripe objects

Constructors

ExpandParams 

Fields

Instances

Eq ExpandParams Source # 
Data ExpandParams Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpandParams -> c ExpandParams #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpandParams #

toConstr :: ExpandParams -> Constr #

dataTypeOf :: ExpandParams -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExpandParams) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpandParams) #

gmapT :: (forall b. Data b => b -> b) -> ExpandParams -> ExpandParams #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpandParams -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpandParams -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExpandParams -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpandParams -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

Ord ExpandParams Source # 
Read ExpandParams Source # 
Show ExpandParams Source # 
ToStripeParam ExpandParams Source # 
StripeHasParam GetSubscriptions ExpandParams Source # 
StripeHasParam GetSubscription ExpandParams Source # 
StripeHasParam GetTransfers ExpandParams Source # 
StripeHasParam GetTransfer ExpandParams Source # 
StripeHasParam GetRefunds ExpandParams Source # 
StripeHasParam GetRefund ExpandParams Source # 
StripeHasParam GetRecipients ExpandParams Source # 
StripeHasParam GetRecipient ExpandParams Source # 
StripeHasParam GetInvoiceItems ExpandParams Source # 
StripeHasParam GetInvoiceItem ExpandParams Source # 
StripeHasParam GetInvoices ExpandParams Source # 
StripeHasParam GetInvoice ExpandParams Source # 
StripeHasParam GetCustomers ExpandParams Source # 
StripeHasParam GetCustomer ExpandParams Source # 
StripeHasParam GetCharges ExpandParams Source # 
StripeHasParam GetCharge ExpandParams Source # 
StripeHasParam CreateCharge ExpandParams Source # 
StripeHasParam GetRecipientCards ExpandParams Source # 
StripeHasParam GetCustomerCards ExpandParams Source # 
StripeHasParam GetRecipientCard ExpandParams Source # 
StripeHasParam GetCustomerCard ExpandParams Source # 
StripeHasParam GetBalanceTransaction ExpandParams Source # 
StripeHasParam GetApplicationFeeRefunds ExpandParams Source # 
StripeHasParam GetApplicationFeeRefund ExpandParams Source # 
StripeHasParam GetApplicationFees ExpandParams Source # 
StripeHasParam GetApplicationFee ExpandParams Source # 

type ID = Text Source #

Generic ID for use in constructing API Calls

type URL = Text Source #

Generic URL for use in constructing API Calls

newtype Name Source #

a cardholder's full name

Constructors

Name 

Fields

Instances

Eq Name Source # 

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Data Name Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

Ord Name Source # 

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Read Name Source # 
Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

FromJSON Name Source # 
ToStripeParam Name Source # 
StripeHasParam UpdateRecipient Name Source # 
StripeHasParam UpdateRecipientCard Name Source # 
StripeHasParam UpdateCustomerCard Name Source # 

newtype PlanName Source #

a plan name

Constructors

PlanName 

Fields

Instances

Eq PlanName Source # 
Data PlanName Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlanName -> c PlanName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlanName #

toConstr :: PlanName -> Constr #

dataTypeOf :: PlanName -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PlanName) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlanName) #

gmapT :: (forall b. Data b => b -> b) -> PlanName -> PlanName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlanName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlanName -> r #

gmapQ :: (forall d. Data d => d -> u) -> PlanName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PlanName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlanName -> m PlanName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanName -> m PlanName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanName -> m PlanName #

Ord PlanName Source # 
Read PlanName Source # 
Show PlanName Source # 
FromJSON PlanName Source # 
ToStripeParam PlanName Source # 
StripeHasParam UpdatePlan PlanName Source # 

newtype Description Source #

Generic Description for use in constructing API Calls

Constructors

Description Text 

Instances

Eq Description Source # 
Data Description Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Description -> c Description #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Description #

toConstr :: Description -> Constr #

dataTypeOf :: Description -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Description) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Description) #

gmapT :: (forall b. Data b => b -> b) -> Description -> Description #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Description -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Description -> r #

gmapQ :: (forall d. Data d => d -> u) -> Description -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Description -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Description -> m Description #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Description -> m Description #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Description -> m Description #

Ord Description Source # 
Read Description Source # 
Show Description Source # 
FromJSON Description Source # 
ToStripeParam Description Source # 
StripeHasParam UpdateTransfer Description Source # 
StripeHasParam CreateTransfer Description Source # 
StripeHasParam UpdateRecipient Description Source # 
StripeHasParam CreateRecipient Description Source # 
StripeHasParam UpdateInvoiceItem Description Source # 
StripeHasParam CreateInvoiceItem Description Source # 
StripeHasParam UpdateInvoice Description Source # 
StripeHasParam CreateInvoice Description Source # 
StripeHasParam UpdateCustomer Description Source # 
StripeHasParam CreateCustomer Description Source # 
StripeHasParam UpdateCharge Description Source # 
StripeHasParam CreateCharge Description Source # 

newtype Quantity Source #

Generic Quantity type to be used with Customer, Subscription and InvoiceLineItem API requests

Constructors

Quantity Int 

Instances

Eq Quantity Source # 
Data Quantity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quantity -> c Quantity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Quantity #

toConstr :: Quantity -> Constr #

dataTypeOf :: Quantity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Quantity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quantity) #

gmapT :: (forall b. Data b => b -> b) -> Quantity -> Quantity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quantity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quantity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Quantity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Quantity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity #

Ord Quantity Source # 
Read Quantity Source # 
Show Quantity Source # 
ToStripeParam Quantity Source # 
StripeHasParam UpdateSubscription Quantity Source # 
StripeHasParam CreateSubscription Quantity Source # 
StripeHasParam CreateCustomer Quantity Source # 

newtype Prorate Source #

Prorate

Constructors

Prorate Bool 

Instances

Eq Prorate Source # 

Methods

(==) :: Prorate -> Prorate -> Bool #

(/=) :: Prorate -> Prorate -> Bool #

Data Prorate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Prorate -> c Prorate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Prorate #

toConstr :: Prorate -> Constr #

dataTypeOf :: Prorate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Prorate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prorate) #

gmapT :: (forall b. Data b => b -> b) -> Prorate -> Prorate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prorate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prorate -> r #

gmapQ :: (forall d. Data d => d -> u) -> Prorate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Prorate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Prorate -> m Prorate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Prorate -> m Prorate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Prorate -> m Prorate #

Ord Prorate Source # 
Read Prorate Source # 
Show Prorate Source # 
ToStripeParam Prorate Source # 
StripeHasParam UpdateSubscription Prorate Source # 
StripeHasParam CreateSubscription Prorate Source # 

newtype AtPeriodEnd Source #

A flag that if set to true will delay the cancellation of the subscription until the end of the current period.

Constructors

AtPeriodEnd Bool 

Instances

Eq AtPeriodEnd Source # 
Data AtPeriodEnd Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AtPeriodEnd -> c AtPeriodEnd #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AtPeriodEnd #

toConstr :: AtPeriodEnd -> Constr #

dataTypeOf :: AtPeriodEnd -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AtPeriodEnd) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AtPeriodEnd) #

gmapT :: (forall b. Data b => b -> b) -> AtPeriodEnd -> AtPeriodEnd #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AtPeriodEnd -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AtPeriodEnd -> r #

gmapQ :: (forall d. Data d => d -> u) -> AtPeriodEnd -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AtPeriodEnd -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AtPeriodEnd -> m AtPeriodEnd #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AtPeriodEnd -> m AtPeriodEnd #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AtPeriodEnd -> m AtPeriodEnd #

Ord AtPeriodEnd Source # 
Read AtPeriodEnd Source # 
Show AtPeriodEnd Source # 
ToStripeParam AtPeriodEnd Source # 
StripeHasParam CancelSubscription AtPeriodEnd Source # 

newtype Email Source #

Email associated with a Customer, Recipient or Charge

Constructors

Email Text 

Instances

Eq Email Source # 

Methods

(==) :: Email -> Email -> Bool #

(/=) :: Email -> Email -> Bool #

Data Email Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Email -> c Email #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Email #

toConstr :: Email -> Constr #

dataTypeOf :: Email -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Email) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Email) #

gmapT :: (forall b. Data b => b -> b) -> Email -> Email #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r #

gmapQ :: (forall d. Data d => d -> u) -> Email -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Email -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Email -> m Email #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email #

Ord Email Source # 

Methods

compare :: Email -> Email -> Ordering #

(<) :: Email -> Email -> Bool #

(<=) :: Email -> Email -> Bool #

(>) :: Email -> Email -> Bool #

(>=) :: Email -> Email -> Bool #

max :: Email -> Email -> Email #

min :: Email -> Email -> Email #

Read Email Source # 
Show Email Source # 

Methods

showsPrec :: Int -> Email -> ShowS #

show :: Email -> String #

showList :: [Email] -> ShowS #

ToStripeParam Email Source # 
StripeHasParam UpdateRecipient Email Source # 
StripeHasParam CreateRecipient Email Source # 
StripeHasParam UpdateCustomer Email Source # 
StripeHasParam CreateCustomer Email Source # 

newtype ReceiptEmail Source #

Email to send receipt to

Constructors

ReceiptEmail Text 

Instances

Eq ReceiptEmail Source # 
Data ReceiptEmail Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReceiptEmail -> c ReceiptEmail #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReceiptEmail #

toConstr :: ReceiptEmail -> Constr #

dataTypeOf :: ReceiptEmail -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReceiptEmail) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReceiptEmail) #

gmapT :: (forall b. Data b => b -> b) -> ReceiptEmail -> ReceiptEmail #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReceiptEmail -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReceiptEmail -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReceiptEmail -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReceiptEmail -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReceiptEmail -> m ReceiptEmail #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReceiptEmail -> m ReceiptEmail #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReceiptEmail -> m ReceiptEmail #

Ord ReceiptEmail Source # 
Read ReceiptEmail Source # 
Show ReceiptEmail Source # 
ToStripeParam ReceiptEmail Source # 
StripeHasParam CaptureCharge ReceiptEmail Source # 
StripeHasParam CreateCharge ReceiptEmail Source # 

data Currency Source #

Stripe supports 138 currencies

Constructors

AED

United Arab Emirates Dirham

AFN

Afghan Afghani

ALL

Albanian Lek

AMD

Armenian Dram

ANG

Netherlands Antillean Gulden

AOA

Angolan Kwanza

ARS

Argentine Peso

AUD

Australian Dollar

AWG

Aruban Florin

AZN

Azerbaijani Manat

BAM

Bosnia & Herzegovina Convertible Mark

BBD

Barbadian Dollar

BDT

Bangladeshi Taka

BGN

Bulgarian Lev

BIF

Burundian Franc

BMD

Bermudian Dollar

BND

Brunei Dollar

BOB

Bolivian Boliviano

BRL

Brazilian Real

BSD

Bahamian Dollar

BWP

Botswana Pula

BZD

Belize Dollar

CAD

Canadian Dollar

CDF

Congolese Franc

CHF

Swiss Franc

CLP

Chilean Peso

CNY

Chinese Renminbi Yuan

COP

Colombian Peso

CRC

Costa Rican Colón

CVE

Cape Verdean Escudo

CZK

Czech Koruna

DJF

Djiboutian Franc

DKK

Danish Krone

DOP

Dominican Peso

DZD

Algerian Dinar

EEK

Estonian Kroon

EGP

Egyptian Pound

ETB

Ethiopian Birr

EUR

Euro

FJD

Fijian Dollar

FKP

Falkland Islands Pound

GBP

British Pound

GEL

Georgian Lari

GIP

Gibraltar Pound

GMD

Gambian Dalasi

GNF

Guinean Franc

GTQ

Guatemalan Quetzal

GYD

Guyanese Dollar

HKD

Hong Kong Dollar

HNL

Honduran Lempira

HRK

Croatian Kuna

HTG

Haitian Gourde

HUF

Hungarian Forint

IDR

Indonesian Rupiah

ILS

Israeli New Sheqel

INR

Indian Rupee

ISK

Icelandic Króna

JMD

Jamaican Dollar

JPY

Japanese Yen

KES

Kenyan Shilling

KGS

Kyrgyzstani Som

KHR

Cambodian Riel

KMF

Comorian Franc

KRW

South Korean Won

KYD

Cayman Islands Dollar

KZT

Kazakhstani Tenge

LAK

Lao Kip

LBP

Lebanese Pound

LKR

Sri Lankan Rupee

LRD

Liberian Dollar

LSL

Lesotho Loti

LTL

Lithuanian Litas

LVL

Latvian Lats

MAD

Moroccan Dirham

MDL

Moldovan Leu

MGA

Malagasy Ariary

MKD

Macedonian Denar

MNT

Mongolian Tögrög

MOP

Macanese Pataca

MRO

Mauritanian Ouguiya

MUR

Mauritian Rupee

MVR

Maldivian Rufiyaa

MWK

Malawian Kwacha

MXN

Mexican Peso

MYR

Malaysian Ringgit

MZN

Mozambican Metical

NAD

Namibian Dollar

NGN

Nigerian Naira

NIO

Nicaraguan Córdoba

NOK

Norwegian Krone

NPR

Nepalese Rupee

NZD

New Zealand Dollar

PAB

Panamanian Balboa

PEN

Peruvian Nuevo Sol

PGK

Papua New Guinean Kina

PHP

Philippine Peso

PKR

Pakistani Rupee

PLN

Polish Złoty

PYG

Paraguayan Guaraní

QAR

Qatari Riyal

RON

Romanian Leu

RSD

Serbian Dinar

RUB

Russian Ruble

RWF

Rwandan Franc

SAR

Saudi Riyal

SBD

Solomon Islands Dollar

SCR

Seychellois Rupee

SEK

Swedish Krona

SGD

Singapore Dollar

SHP

Saint Helenian Pound

SLL

Sierra Leonean Leone

SOS

Somali Shilling

SRD

Surinamese Dollar

STD

São Tomé and Príncipe Dobra

SVC

Salvadoran Colón

SZL

Swazi Lilangeni

THB

Thai Baht

TJS

Tajikistani Somoni

TOP

Tongan Paʻanga

TRY

Turkish Lira

TTD

Trinidad and Tobago Dollar

TWD

New Taiwan Dollar

TZS

Tanzanian Shilling

UAH

Ukrainian Hryvnia

UGX

Ugandan Shilling

USD

United States Dollar

UYU

Uruguayan Peso

UZS

Uzbekistani Som

VND

Vietnamese Đồng

VUV

Vanuatu Vatu

WST

Samoan Tala

XAF

Central African Cfa Franc

XCD

East Caribbean Dollar

XOF

West African Cfa Franc

XPF

Cfp Franc

YER

Yemeni Rial

ZAR

South African Rand

ZMW

Zambian Kwacha

UnknownCurrency

Unknown Currency

Instances

Eq Currency Source # 
Data Currency Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Currency -> c Currency #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Currency #

toConstr :: Currency -> Constr #

dataTypeOf :: Currency -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Currency) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Currency) #

gmapT :: (forall b. Data b => b -> b) -> Currency -> Currency #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Currency -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Currency -> r #

gmapQ :: (forall d. Data d => d -> u) -> Currency -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Currency -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Currency -> m Currency #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Currency -> m Currency #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Currency -> m Currency #

Ord Currency Source # 
Read Currency Source # 
Show Currency Source # 
FromJSON Currency Source #

Currency JSON instances

ToStripeParam Currency Source # 
StripeHasParam CreateCoupon Currency Source # 
StripeHasParam GetBalanceTransactionHistory Currency Source # 

newtype PaymentId Source #

BTC PaymentId

Constructors

PaymentId Text 

showAmount Source #

Show an amount accounting for zero currencies

https://support.stripe.com/questions/which-zero-decimal-currencies-does-stripe-support

currencyDivisor Source #

Arguments

:: Currency

Currency

-> Int -> Float

function to convert amount to a float