Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Web.Stripe.Event
Description
https://stripe.com/docs/api#events
{-# LANGUAGE OverloadedStrings #-} import Web.Stripe import Web.Stripe.Event main :: IO () main = do let config = StripeConfig (StripeKey "secret_key") result <- stripe config $ getEvents case result of Right events -> print events Left stripeError -> print stripeError
Synopsis
- data GetEvent
- getEvent :: EventId -> StripeRequest GetEvent
- data GetEvents
- getEvents :: StripeRequest GetEvents
- newtype Created = Created UTCTime
- newtype EndingBefore a = EndingBefore a
- newtype EventId = EventId Text
- data Event = Event {}
- data EventData
- = TransferEvent Transfer
- | AccountEvent Account
- | AccountApplicationEvent ConnectApp
- | ApplicationFeeEvent ApplicationFee
- | InvoiceEvent Invoice
- | PlanEvent Plan
- | RecipientEvent Recipient
- | CouponEvent Coupon
- | BalanceEvent Balance
- | ChargeEvent Charge
- | DisputeEvent Dispute
- | CustomerEvent Customer
- | CardEvent Card
- | SubscriptionEvent Subscription
- | DiscountEvent Discount
- | InvoiceItemEvent InvoiceItem
- | UnknownEventData
- | Ping
- data EventType
- = AccountUpdatedEvent
- | AccountApplicationDeauthorizedEvent
- | ApplicationFeeCreatedEvent
- | ApplicationFeeRefundedEvent
- | BalanceAvailableEvent
- | ChargeSucceededEvent
- | ChargeFailedEvent
- | ChargeRefundedEvent
- | ChargeCapturedEvent
- | ChargeUpdatedEvent
- | ChargeDisputeCreatedEvent
- | ChargeDisputeUpdatedEvent
- | ChargeDisputeClosedEvent
- | ChargeDisputeFundsWithdrawnEvent
- | ChargeDisputeFundsReinstatedEvent
- | CustomerCreatedEvent
- | CustomerUpdatedEvent
- | CustomerDeletedEvent
- | CustomerCardCreatedEvent
- | CustomerCardUpdatedEvent
- | CustomerCardDeletedEvent
- | CustomerSubscriptionCreatedEvent
- | CustomerSubscriptionUpdatedEvent
- | CustomerSubscriptionDeletedEvent
- | CustomerSubscriptionTrialWillEndEvent
- | CustomerDiscountCreatedEvent
- | CustomerDiscountUpdatedEvent
- | CustomerDiscountDeletedEvent
- | InvoiceCreatedEvent
- | InvoiceUpdatedEvent
- | InvoicePaymentSucceededEvent
- | InvoicePaymentFailedEvent
- | InvoiceItemCreatedEvent
- | InvoiceItemUpdatedEvent
- | InvoiceItemDeletedEvent
- | PlanCreatedEvent
- | PlanUpdatedEvent
- | PlanDeletedEvent
- | CouponCreatedEvent
- | CouponUpdatedEvent
- | CouponDeletedEvent
- | RecipientCreatedEvent
- | RecipientUpdatedEvent
- | RecipientDeletedEvent
- | TransferCreatedEvent
- | TransferUpdatedEvent
- | TransferCanceledEvent
- | TransferPaidEvent
- | TransferFailedEvent
- | PingEvent
- | UnknownEvent
- data StripeList a = StripeList {}
- newtype Limit = Limit Int
- newtype StartingAfter a = StartingAfter a
API
Instances
type StripeReturn GetEvent Source # | |
Defined in Web.Stripe.Event |
Arguments
:: EventId | The ID of the Event to retrieve |
-> StripeRequest GetEvent |
Instances
StripeHasParam GetEvents Limit Source # | |
Defined in Web.Stripe.Event | |
StripeHasParam GetEvents Created Source # | |
Defined in Web.Stripe.Event | |
StripeHasParam GetEvents (EndingBefore EventId) Source # | |
Defined in Web.Stripe.Event | |
StripeHasParam GetEvents (StartingAfter EventId) Source # | |
Defined in Web.Stripe.Event | |
type StripeReturn GetEvents Source # | |
Defined in Web.Stripe.Event |
getEvents :: StripeRequest GetEvents Source #
StripeList
of Event
s to retrieve
Types
Instances
newtype EndingBefore a Source #
Pagination Option for StripeList
Constructors
EndingBefore a |
Instances
Instances
Eq EventId Source # | |
Data EventId Source # | |
Defined in Web.Stripe.Types 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 # | |
Defined in Web.Stripe.StripeRequest Methods toStripeParam :: EventId -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam GetEvents (EndingBefore EventId) Source # | |
Defined in Web.Stripe.Event | |
StripeHasParam GetEvents (StartingAfter EventId) Source # | |
Defined in Web.Stripe.Event |
Event
Object
Constructors
Event | |
Fields
|
Instances
Eq Event Source # | |
Data Event Source # | |
Defined in Web.Stripe.Types 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 # 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 # | |
Read Event Source # | |
Show Event Source # | |
FromJSON Event Source # | JSON Instance for |
EventData
Constructors
Instances
Eq EventData Source # | |
Data EventData Source # | |
Defined in Web.Stripe.Types 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 # | |
Event
Types
Constructors
Instances
Eq EventType Source # | |
Data EventType Source # | |
Defined in Web.Stripe.Types 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 |
data StripeList a Source #
Generic handling of Stripe JSON arrays
Constructors
StripeList | |
Instances
Eq a => Eq (StripeList a) Source # | |
Defined in Web.Stripe.Types | |
Data a => Data (StripeList a) Source # | |
Defined in Web.Stripe.Types 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 # | |
Defined in Web.Stripe.Types Methods compare :: StripeList a -> StripeList a -> Ordering # (<) :: StripeList a -> StripeList a -> Bool # (<=) :: StripeList a -> StripeList a -> Bool # (>) :: StripeList a -> StripeList a -> Bool # (>=) :: StripeList a -> StripeList a -> Bool # max :: StripeList a -> StripeList a -> StripeList a # min :: StripeList a -> StripeList a -> StripeList a # | |
Read a => Read (StripeList a) Source # | |
Defined in Web.Stripe.Types Methods readsPrec :: Int -> ReadS (StripeList a) # readList :: ReadS [StripeList a] # readPrec :: ReadPrec (StripeList a) # readListPrec :: ReadPrec [StripeList a] # | |
Show a => Show (StripeList a) Source # | |
Defined in Web.Stripe.Types Methods showsPrec :: Int -> StripeList a -> ShowS # show :: StripeList a -> String # showList :: [StripeList a] -> ShowS # | |
FromJSON a => FromJSON (StripeList a) Source # | JSON Instance for |
Defined in Web.Stripe.Types Methods parseJSON :: Value -> Parser (StripeList a) # parseJSONList :: Value -> Parser [StripeList a] # |
Pagination Option for StripeList
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Constructors
StartingAfter a |