mollie-api-haskell-2.0.0.0: Mollie API client for Haskell http://www.mollie.com

Safe HaskellNone
LanguageHaskell2010

Mollie.API.Mandates

Synopsis

Documentation

data MandateAPI route Source #

Instances
Generic (MandateAPI route) Source # 
Instance details

Defined in Mollie.API.Mandates

Associated Types

type Rep (MandateAPI route) :: Type -> Type #

Methods

from :: MandateAPI route -> Rep (MandateAPI route) x #

to :: Rep (MandateAPI route) x -> MandateAPI route #

type Rep (MandateAPI route) Source # 
Instance details

Defined in Mollie.API.Mandates

type Rep (MandateAPI route) = D1 (MetaData "MandateAPI" "Mollie.API.Mandates" "mollie-api-haskell-2.0.0.0-79op8QUDPdyAagRpBQOely" False) (C1 (MetaCons "MandateAPI" PrefixI True) ((S1 (MetaSel (Just "getCustomerMandatesPaginated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (QueryParam "limit" Int :> (QueryParam "from" MandateId :> Get (HalJSON ': ([] :: [Type])) (List Mandate)))))))) :*: S1 (MetaSel (Just "getCustomerMandates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> Get (HalJSON ': ([] :: [Type])) (List Mandate))))))) :*: (S1 (MetaSel (Just "createCustomerMandate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (ReqBody (JSON ': ([] :: [Type])) NewMandate :> Post (HalJSON ': ([] :: [Type])) Mandate)))))) :*: (S1 (MetaSel (Just "getCustomerMandate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (Capture "id" MandateId :> Get (HalJSON ': ([] :: [Type])) Mandate)))))) :*: S1 (MetaSel (Just "revokeCustomerMandate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (Capture "mandateId" MandateId :> DeleteNoContent (HalJSON ': ([] :: [Type])) NoContent))))))))))

newMandate Source #

Arguments

:: PaymentMethod

_method

-> Text

_consumerName

-> Text

_consumerAccount

-> NewMandate 

createCustomerMandate :: MandateAPI route -> route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (ReqBody '[JSON] NewMandate :> Post '[HalJSON] Mandate)))) Source #

Handler to create a new mandate for a specific customer. See https://docs.mollie.com/reference/v2/mandates-api/create-mandate

getCustomerMandate :: MandateAPI route -> route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (Capture "id" MandateId :> Get '[HalJSON] Mandate)))) Source #

Handler to get a mandate by its identifier for a specific customer. See https://docs.mollie.com/reference/v2/mandates-api/get-mandate

getCustomerMandates :: MandateAPI route -> route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> Get '[HalJSON] (List Mandate)))) Source #

Handler to get a paginated list of mandates for a specific customer. Applies default pagination for newest 250 customers. See https://docs.mollie.com/reference/v2/mandates-api/list-mandates

getCustomerMandatesPaginated :: MandateAPI route -> route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (QueryParam "limit" Int :> (QueryParam "from" MandateId :> Get '[HalJSON] (List Mandate)))))) Source #

Handler to get a paginated list of mandates for a specific customer. Offset the results by passing the last mandate ID in the from query param. The mandate with this ID is included in the result set as well. See https://docs.mollie.com/reference/v2/mandates-api/list-mandates

Example for fetching the last mandate for a customer:

import Mollie.API
import Mollie.API.Mandates

env <- createEnv "test_mollieapikeyexample"
let customerMandatesResult = runMollie env (getCustomerMandatesPaginated customerClient "cst_exampleid" (Just 1) Nothing)

revokeCustomerMandate :: MandateAPI route -> route :- ("customers" :> (Capture "customerId" CustomerId :> ("mandates" :> (Capture "mandateId" MandateId :> DeleteNoContent '[HalJSON] NoContent)))) Source #

Handler to remove a mandate by its identifier for a specific customer. See https://docs.mollie.com/reference/v2/mandates-api/revoke-mandate