mangopay-1.9.2: Bindings to the MangoPay API

Safe HaskellNone

Web.MangoPay

Description

API entry point

Synopsis

Documentation

data MangoPayT m a Source

the mangopay monad transformer this encapsulates the data necessary to pass the app credentials, etc

Instances

MonadTrans MangoPayT 
MonadTransControl MangoPayT 
MonadBaseControl b m => MonadBaseControl b (MangoPayT m) 
MonadBase b m => MonadBase b (MangoPayT m) 
Monad m => Monad (MangoPayT m) 
Functor m => Functor (MangoPayT m) 
MonadFix m => MonadFix (MangoPayT m) 
MonadPlus m => MonadPlus (MangoPayT m) 
Applicative m => Applicative (MangoPayT m) 
Alternative m => Alternative (MangoPayT m) 
MonadThrow m => MonadThrow (MangoPayT m) 
MonadLogger m => MonadLogger (MangoPayT m) 
MonadIO m => MonadIO (MangoPayT m) 
MonadResource m => MonadResource (MangoPayT m) 

runMangoPayTSource

Arguments

:: Credentials

Your app's credentials.

-> Manager

Connection manager (see withManager).

-> AccessPoint 
-> MangoPayT m a

the action to run

-> m a

the result

Run a computation in the MangoPayT monad transformer with your credentials.

runResourceInMp :: MPUsableMonad m => MangoPayT (ResourceT m) a -> MangoPayT m aSource

Run a ResourceT inside a MangoPayT.

data MpException Source

an exception that a call to MangoPay may throw

Instances

Show MpException 
Typeable MpException 
ToJSON MpException

to json

FromJSON MpException 
Exception MpException

make our exception type a normal exception

getAll :: (MPUsableMonad m, FromJSON v) => (Maybe Pagination -> AccessToken -> MangoPayT m (PagedList v)) -> AccessToken -> MangoPayT m [v]Source

get all items, hiding the pagination system

data Credentials Source

the app credentials

Constructors

Credentials 

Fields

cClientId :: Text

client id

cName :: Text

the name

cEmail :: Text

the email

cClientSecret :: Maybe Text

client secret, maybe be Nothing if we haven't generated it

Instances

Eq Credentials 
Ord Credentials 
Read Credentials 
Show Credentials 
Typeable Credentials 
ToJSON Credentials

to json as per MangoPay format

FromJSON Credentials

from json as per MangoPay format

data AccessPoint Source

the MangoPay access point

Instances

newtype AccessToken Source

the access token is simply a Text

Constructors

AccessToken ByteString 

Instances

data OAuthToken Source

the oauth token returned after authentication

Constructors

OAuthToken 

Fields

oaAccessToken :: Text

the access token

oaTokenType :: Text

the token type

oaExpires :: Int

expiration

Instances

Eq OAuthToken 
Ord OAuthToken 
Read OAuthToken 
Show OAuthToken 
Typeable OAuthToken 
ToJSON OAuthToken

to json as per MangoPay format

FromJSON OAuthToken

from json as per MangoPay format

data Pagination Source

Constructors

Pagination 

Fields

pPage :: Integer
 
pPerPage :: Integer
 

Instances

data PagedList a Source

A partial list with pagination information.

Constructors

PagedList 

Fields

plData :: [a]
 
plItemCount :: Integer
 
plPageCount :: Integer
 

Instances

Typeable1 PagedList 
Eq a => Eq (PagedList a) 
Ord a => Ord (PagedList a) 
Read a => Read (PagedList a) 
Show a => Show (PagedList a) 

type MPUsableMonad m = (MonadBaseControl IO m, MonadResource m, MonadLogger m)Source

put our constraints in one synonym

class ToHtQuery a whereSource

simple class used to hide the serialization of parameters and simplify the calling code

Methods

(?+) :: ByteString -> a -> (ByteString, Maybe ByteString)Source

Instances

ToHtQuery Double 
ToHtQuery Integer 
ToHtQuery String 
ToHtQuery Text 
ToHtQuery (Maybe Double) 
ToHtQuery (Maybe Integer) 
ToHtQuery (Maybe String) 
ToHtQuery (Maybe Text) 
ToHtQuery (Maybe POSIXTime) 
ToHtQuery (Maybe EventType) 

data CardExpiration Source

the expiration date of a card

Constructors

CardExpiration 

Fields

ceMonth :: Int
 
ceYear :: Int
 

Instances

Eq CardExpiration 
Ord CardExpiration 
Read CardExpiration 
Show CardExpiration 
Typeable CardExpiration 
IsString CardExpiration 
ToJSON CardExpiration

show Card Expiration to JSON string (MMYY)

FromJSON CardExpiration

read Card Expiration from JSON string (MMYY)

readCardExpiration :: Reader CardExpirationSource

read Card Expiration from text representation (MMYY)

writeCardExpiration :: CardExpiration -> TextSource

write card expiration

createCredentialsSecret :: MPUsableMonad m => MangoPayT m CredentialsSource

Populate the passphrase for our clientId IFF we don't have one.

oauthLogin :: MPUsableMonad m => Text -> Text -> MangoPayT m OAuthTokenSource

Login with given user name and password. Returns the OAuth token that can be used to generate the opaque AccessToken and carries the expiration delay.

toAccessToken :: OAuthToken -> AccessTokenSource

build the access token from the OAuthToken

data NaturalUser Source

Constructors

NaturalUser 

Fields

uId :: Maybe NaturalUserId

The Id of the object

uCreationDate :: Maybe POSIXTime

The creation date of the user object

uEmail :: Text

User’s e-mail

uFirstName :: Text

User’s firstname

uLastName :: Text

User’s lastname

uAddress :: Maybe Text

User’s address

uBirthday :: POSIXTime

User’s birthdate

uNationality :: CountryCode

User’s Nationality

uCountryOfResidence :: CountryCode

User’s country of residence

uOccupation :: Maybe Text

User’s occupation (ie. Work)

uIncomeRange :: Maybe IncomeRange

User’s income range

uTag :: Maybe Text

Custom data

uProofOfIdentity :: Maybe Text
 
uProofOfAddress :: Maybe Text
 

Instances

Eq NaturalUser 
Ord NaturalUser 
Show NaturalUser 
Typeable NaturalUser 
ToJSON NaturalUser

to json as per MangoPay format

FromJSON NaturalUser

from json as per MangoPay format

FromJSON (Either NaturalUser LegalUser) 

data IncomeRange Source

supported income ranges

Instances

Bounded IncomeRange 
Enum IncomeRange 
Eq IncomeRange 
Ord IncomeRange 
Read IncomeRange 
Show IncomeRange 
Typeable IncomeRange 
ToJSON IncomeRange

to json as per MangoPay format the samples do show string format when writing, integer format when reading...

FromJSON IncomeRange

from json as per MangoPay format the samples do show string format when writing, integer format when reading...

incomeBounds :: IncomeRange -> (Amount, Amount)Source

bounds in euros for income range

incomeRange :: Amount -> IncomeRangeSource

get Income Range for given Euro amount

type NaturalUserId = TextSource

User Id

data LegalUser Source

Constructors

LegalUser 

Fields

lId :: Maybe Text

The Id of the object

lCreationDate :: Maybe POSIXTime

The creation date of the user object

lEmail :: Text

The email of the company or the organization

lName :: Text

The name of the company or the organization

lLegalPersonType :: LegalUserType

The type of the legal user (‘BUSINESS’ or ’ORGANIZATION’)

lHeadquartersAddress :: Maybe Text

The address of the company’s headquarters

lLegalRepresentativeFirstName :: Text

The firstname of the company’s Legal representative person

lLegalRepresentativeLastName :: Text

The lastname of the company’s Legal representative person

lLegalRepresentativeAddress :: Maybe Text

The address of the company’s Legal representative person

lLegalRepresentativeEmail :: Maybe Text

The email of the company’s Legal representative person

lLegalRepresentativeBirthday :: POSIXTime

The birthdate of the company’s Legal representative person

lLegalRepresentativeNationality :: CountryCode

the nationality of the company’s Legal representative person

lLegalRepresentativeCountryOfResidence :: CountryCode

The country of residence of the company’s Legal representative person

lStatute :: Maybe Text

The business statute of the company

lTag :: Maybe Text

Custom data

lProofOfRegistration :: Maybe Text

The proof of registration of the company

lShareholderDeclaration :: Maybe Text

The shareholder declaration of the company

Instances

Eq LegalUser 
Ord LegalUser 
Show LegalUser 
Typeable LegalUser 
ToJSON LegalUser

to json as per MangoPay format

FromJSON LegalUser

from json as per MangoPay format

FromJSON (Either NaturalUser LegalUser) 

data LegalUserType Source

the type of legal user

Constructors

Business 
Organization 

Instances

Bounded LegalUserType 
Enum LegalUserType 
Eq LegalUserType 
Ord LegalUserType 
Read LegalUserType 
Show LegalUserType 
Typeable LegalUserType 
ToJSON LegalUserType

to json as per MangoPay format

FromJSON LegalUserType

from json as per MangoPay format

type LegalUserId = TextSource

User Id

data UserRef Source

a short user reference

Constructors

UserRef 

Fields

urId :: AnyUserId
 
urCreationDate :: POSIXTime
 
urPersonType :: PersonType
 
urEmail :: Text
 
urTag :: Maybe Text
 

Instances

Eq UserRef 
Ord UserRef 
Show UserRef 
Typeable UserRef 
ToJSON UserRef

to json as per MangoPay format

FromJSON UserRef

from json as per MangoPay format

data PersonType Source

Type of user.

Constructors

Natural 
Legal 

Instances

Bounded PersonType 
Enum PersonType 
Eq PersonType 
Ord PersonType 
Read PersonType 
Show PersonType 
Typeable PersonType 
ToJSON PersonType

to json as per MangoPay format

FromJSON PersonType

from json as per MangoPay format

type AnyUserId = TextSource

Id for any kind of user

fetchNaturalUser :: MPUsableMonad m => NaturalUserId -> AccessToken -> MangoPayT m NaturalUserSource

fetch a natural user from her Id

fetchLegalUser :: MPUsableMonad m => LegalUserId -> AccessToken -> MangoPayT m LegalUserSource

fetch a natural user from her Id

getUser :: MPUsableMonad m => AnyUserId -> AccessToken -> MangoPayT m (Either NaturalUser LegalUser)Source

get a user, natural or legal

listUsers :: MPUsableMonad m => Maybe Pagination -> AccessToken -> MangoPayT m (PagedList UserRef)Source

list all user references

getExistingUserId :: Either NaturalUser LegalUser -> AnyUserIdSource

Convenience function to extract the user Id of an EXISTING user (one with an id).

data Wallet Source

a wallet

Constructors

Wallet 

Fields

wId :: Maybe WalletId

The Id of the wallet

wCreationDate :: Maybe POSIXTime

The creation date of the object

wTag :: Maybe Text

Custom data

wOwners :: [Text]

The owner of the wallet

wDescription :: Text

A description of the wallet

wCurrency :: Currency

Currency of the wallet

wBalance :: Maybe Amount

The amount held on the wallet

Instances

Eq Wallet 
Ord Wallet 
Show Wallet 
Typeable Wallet 
ToJSON Wallet

to json as per MangoPay format

FromJSON Wallet

from json as per MangoPay format

data Amount Source

currency amount

Constructors

Amount 

Fields

aCurrency :: Currency
 
aAmount :: Integer

all amounts should be in cents!

Instances

Eq Amount 
Ord Amount 
Read Amount 
Show Amount 
Typeable Amount 
ToJSON Amount

to json as per MangoPay format

FromJSON Amount

from json as per MangoPay format

type WalletId = TextSource

Id of a wallet

type Currency = TextSource

alias for Currency

fetchWallet :: MPUsableMonad m => WalletId -> AccessToken -> MangoPayT m WalletSource

fetch a wallet from its Id

listWallets :: MPUsableMonad m => AnyUserId -> Maybe Pagination -> AccessToken -> MangoPayT m (PagedList Wallet)Source

list all wallets for a given user

data Transfer Source

transfer between wallets

Constructors

Transfer 

Fields

tId :: Maybe TransferId

Id of the transfer

tCreationDate :: Maybe POSIXTime

The creation date of the object

tTag :: Maybe Text

Custom data

tAuthorId :: AnyUserId

The Id of the author

tCreditedUserId :: Maybe AnyUserId

The Id of the user owner of the credited wallet

tDebitedFunds :: Amount

The funds debited from the

tFees :: Amount

The fees taken on the transfer.DebitedFunds – Fees = CreditedFunds (amount received on wallet)

tDebitedWalletId :: WalletId

The debited wallet (where the funds are held before the transfer)

tCreditedWalletId :: WalletId

The credited wallet (where the funds will be held after the transfer)

tCreditedFunds :: Maybe Amount

The funds credited on the

tStatus :: Maybe TransferStatus

The status of the transfer:

tResultCode :: Maybe Text

The transaction result code

tResultMessage :: Maybe Text

The transaction result message

tExecutionDate :: Maybe POSIXTime

The execution date of the transfer

Instances

Eq Transfer 
Ord Transfer 
Show Transfer 
Typeable Transfer 
ToJSON Transfer

to json as per MangoPay format

FromJSON Transfer

from json as per MangoPay format

type TransferId = TextSource

Id of a transfer

data TransferStatus Source

status of a transfer

Constructors

Created 
Succeeded 
Failed 

Instances

Bounded TransferStatus 
Enum TransferStatus 
Eq TransferStatus 
Ord TransferStatus 
Read TransferStatus 
Show TransferStatus 
Typeable TransferStatus 
ToJSON TransferStatus

to json as per MangoPay format

FromJSON TransferStatus

from json as per MangoPay format

data Transaction Source

any transaction

Constructors

Transaction 

Fields

txId :: Maybe TransactionId

Id of the transfer

txCreationDate :: Maybe POSIXTime

The creation date of the object

txTag :: Maybe Text

Custom data

txAuthorId :: AnyUserId

The Id of the author

txCreditedUserId :: Maybe AnyUserId

The Id of the user owner of the credited wallet

txDebitedFunds :: Amount

The funds debited from the

txFees :: Amount

The fees taken on the transfer.DebitedFunds – Fees = CreditedFunds (amount received on wallet)

txDebitedWalletId :: Maybe WalletId

The debited wallet (where the funds are held before the transfer)

txCreditedWalletId :: Maybe WalletId

The credited wallet (where the funds will be held after the transfer)

txCreditedFunds :: Maybe Amount

The funds credited on the

txStatus :: Maybe TransferStatus

The status of the transfer:

txResultCode :: Maybe Text

The transaction result code

txResultMessage :: Maybe Text

The transaction result message

txExecutionDate :: Maybe POSIXTime

The execution date of the transfer

txType :: TransactionType

The type of the transaction

txNature :: TransactionNature

The nature of the transaction:

Instances

Eq Transaction 
Ord Transaction 
Show Transaction 
Typeable Transaction 
ToJSON Transaction

to json as per MangoPay format

FromJSON Transaction

from json as per MangoPay format

data TransactionType Source

type of transaction

Constructors

PAYIN 
PAYOUT 
TRANSFER 

Instances

Bounded TransactionType 
Enum TransactionType 
Eq TransactionType 
Ord TransactionType 
Read TransactionType 
Show TransactionType 
Typeable TransactionType 
ToJSON TransactionType

to json as per MangoPay format

FromJSON TransactionType

from json as per MangoPay format

data TransactionNature Source

Constructors

REGULAR

just as you created the object

REFUND

the transaction has been refunded

REPUDIATION

the transaction has been repudiated

Instances

Bounded TransactionNature 
Enum TransactionNature 
Eq TransactionNature 
Ord TransactionNature 
Read TransactionNature 
Show TransactionNature 
Typeable TransactionNature 
ToJSON TransactionNature

to json as per MangoPay format

FromJSON TransactionNature

from json as per MangoPay format

createTransfer :: MPUsableMonad m => Transfer -> AccessToken -> MangoPayT m TransferSource

create a new fund transfer

fetchTransfer :: MPUsableMonad m => TransferId -> AccessToken -> MangoPayT m TransferSource

fetch a transfer from its Id

listTransactions :: MPUsableMonad m => WalletId -> Maybe Pagination -> AccessToken -> MangoPayT m (PagedList Transaction)Source

list transfers for a given wallet

data Event Source

a event

Constructors

Event 

Fields

eResourceId :: Text
 
eEventType :: EventType
 
eDate :: POSIXTime
 

Instances

Eq Event 
Ord Event 
Show Event 
Typeable Event 
ToJSON Event

to json as per MangoPay format

FromJSON Event

from json as per MangoPay format

data EventSearchParams Source

search parameters for events

Constructors

EventSearchParams 

Fields

espEventType :: Maybe EventType
 
espBeforeDate :: Maybe POSIXTime
 
espAfterDate :: Maybe POSIXTime
 
espPagination :: Maybe Pagination
 

searchEvents :: MPUsableMonad m => EventSearchParams -> AccessToken -> MangoPayT m (PagedList Event)Source

search events, returns a paginated list

searchAllEvents :: MPUsableMonad m => EventSearchParams -> AccessToken -> MangoPayT m [Event]Source

search events, returns the full result

checkEvent :: MPUsableMonad m => Event -> AccessToken -> MangoPayT m BoolSource

Check if an event came from MangoPay. Since notifications are not authenticated, you're advised to always check if the event really comes from MangoPay (cf. https://mangopay.desk.com/customer/portal/questions/6493147).

data HookStatus Source

status of notification hook

Constructors

Enabled 
Disabled 

Instances

Bounded HookStatus 
Enum HookStatus 
Eq HookStatus 
Ord HookStatus 
Read HookStatus 
Show HookStatus 
Typeable HookStatus 
ToJSON HookStatus

to json as per MangoPay format

FromJSON HookStatus

from json as per MangoPay format

data HookValidity Source

validity of notification hook

Constructors

Valid 
Invalid 

Instances

Bounded HookValidity 
Enum HookValidity 
Eq HookValidity 
Ord HookValidity 
Read HookValidity 
Show HookValidity 
Typeable HookValidity 
ToJSON HookValidity

to json as per MangoPay format

FromJSON HookValidity

from json as per MangoPay format

type HookId = TextSource

id for hook

data Hook Source

a notification hook

Constructors

Hook 

Fields

hId :: Maybe HookId

The Id of the hook details

hCreationDate :: Maybe POSIXTime
 
hTag :: Maybe Text

Custom data

hUrl :: Text

This is the URL where you receive notification for each EventType

hStatus :: HookStatus
 
hValidity :: Maybe HookValidity
 
hEventType :: EventType
 

Instances

Eq Hook 
Ord Hook 
Show Hook 
Typeable Hook 
ToJSON Hook

to json as per MangoPay format

FromJSON Hook

from json as per MangoPay format

fetchHook :: MPUsableMonad m => HookId -> AccessToken -> MangoPayT m HookSource

fetch a wallet from its Id

listHooks :: MPUsableMonad m => Maybe Pagination -> AccessToken -> MangoPayT m (PagedList Hook)Source

list all wallets for a given user

eventFromQueryString :: Query -> Maybe EventSource

parse an event from the query string the MangoPay is not very clear on notifications, but see v1 http://docs.mangopay.com/v1-api-references/notifications/ v2 works the same, the event is passed via parameters of the query string

eventFromQueryStringT :: [(Text, Text)] -> Maybe EventSource

parse an event from the query string represented as Text the MangoPay is not very clear on notifications, but see v1 http://docs.mangopay.com/v1-api-references/notifications/ v2 works the same, the event is passed via parameters of the query string

data Document Source

a document

Constructors

Document 

Fields

dId :: Maybe DocumentId
 
dCreationDate :: Maybe POSIXTime
 
dTag :: Maybe Text

custom data for client

dType :: DocumentType
 
dStatus :: Maybe DocumentStatus
 
dRefusedReasonType :: Maybe Text
 
dRefusedReasonMessage :: Maybe Text
 

Instances

Eq Document 
Ord Document 
Show Document 
Typeable Document 
ToJSON Document

to json as per MangoPay format

FromJSON Document

from json as per MangoPay format

type DocumentId = TextSource

Id of a document

data DocumentType Source

type of the document

Constructors

IDENTITY_PROOF

For legal and natural users

REGISTRATION_PROOF

Only for legal users

ARTICLES_OF_ASSOCIATION

Only for legal users

SHAREHOLDER_DECLARATION

Only for legal users

ADDRESS_PROOF

For legal and natural users

Instances

Bounded DocumentType 
Enum DocumentType 
Eq DocumentType 
Ord DocumentType 
Read DocumentType 
Show DocumentType 
Typeable DocumentType 
ToJSON DocumentType

to json as per MangoPay format

FromJSON DocumentType

from json as per MangoPay format

data DocumentStatus Source

status of a document

Instances

Bounded DocumentStatus 
Enum DocumentStatus 
Eq DocumentStatus 
Ord DocumentStatus 
Read DocumentStatus 
Show DocumentStatus 
Typeable DocumentStatus 
ToJSON DocumentStatus

to json as per MangoPay format

FromJSON DocumentStatus

from json as per MangoPay format

fetchDocument :: MPUsableMonad m => AnyUserId -> DocumentId -> AccessToken -> MangoPayT m DocumentSource

fetch a document from its Id

createPage :: MPUsableMonad m => AnyUserId -> DocumentId -> ByteString -> AccessToken -> MangoPayT m ()Source

create a page note that per the MangoPay API the document HAS to be in CREATED status should we check it here? Since MangoPay returns a 500 Internal Server Error if the document is in another status...

getRequiredDocumentTypesSource

Arguments

:: Either NaturalUser LegalUser

The MangoPay user.

-> [DocumentType] 

Get the document types that may be required from the given user to enhance authorization level.

data BankAccount Source

bank account details

Constructors

BankAccount 

Fields

baId :: Maybe BankAccountId
 
baCreationDate :: Maybe POSIXTime
 
baUserId :: Maybe AnyUserId
 
baTag :: Maybe Text
 
baDetails :: BankAccountDetails
 
baOwnerName :: Text
 
baOwnerAddress :: Maybe Text
 

Instances

Eq BankAccount 
Ord BankAccount 
Show BankAccount 
Typeable BankAccount 
ToJSON BankAccount

to json as per MangoPay format

FromJSON BankAccount

from json as per MangoPay format

type BankAccountId = TextSource

Id of a bank account

data BankAccountDetails Source

account details, depending on the type

Instances

data PaymentType Source

type of payment

Instances

Bounded PaymentType 
Enum PaymentType 
Eq PaymentType 
Ord PaymentType 
Read PaymentType 
Show PaymentType 
Typeable PaymentType 
ToJSON PaymentType

to json as per MangoPay format

FromJSON PaymentType

from json as per MangoPay format

listAccounts :: MPUsableMonad m => AnyUserId -> Maybe Pagination -> AccessToken -> MangoPayT m (PagedList BankAccount)Source

list all accounts for a given user

data PaymentExecution Source

Constructors

WEB

through a web interface

DIRECT

with a tokenized card

Instances

Bounded PaymentExecution 
Enum PaymentExecution 
Eq PaymentExecution 
Ord PaymentExecution 
Read PaymentExecution 
Show PaymentExecution 
Typeable PaymentExecution 
ToJSON PaymentExecution

to json as per MangoPay format

FromJSON PaymentExecution

from json as per MangoPay format

type BankWireId = TextSource

id of a bankwire

data BankWire Source

a bank wire there are a lot of common fields between all kinds of payments so this could probably become a Payment type

Constructors

BankWire 

Fields

bwId :: Maybe BankWireId
 
bwCreationDate :: Maybe POSIXTime
 
bwTag :: Maybe Text

custom data

bwAuthorId :: AnyUserId

The user Id of the author

bwCreditedUserId :: AnyUserId

It represents the amount credited on the targeted e-wallet.

bwFees :: Maybe Amount

It represents your fees taken on the DebitedFundsDebitedFunds – Fees = CreditedFunds (amount received on wallet)

bwCreditedWalletId :: WalletId

The Id of the credited wallet

bwDebitedWalletId :: Maybe WalletId

The Id of the debited wallet

bwDebitedFunds :: Maybe Amount

It represents the amount debited from the bank account.

bwCreditedFunds :: Maybe Amount

It represents the amount credited on the targeted e-wallet.

bwDeclaredDebitedFunds :: Amount

It represents the expected amount by the platform before that the user makes the payment.

bwDeclaredFees :: Amount

It represents the expected fees amount by the platform before that the user makes the payment.

bwWireReference :: Maybe Text

It is a reference generated by MANGOPAY and displayed to the user by the platform. The user have to indicate it into the bank wire.

bwBankAccount :: Maybe BankAccount

The bank account is generated by MANGOPAY and displayed to the user.

bwStatus :: Maybe TransferStatus

The status of the payment

bwResultCode :: Maybe Text

The transaction result code

bwResultMessage :: Maybe Text

The transaction result Message

bwExecutionDate :: Maybe POSIXTime

The date when the payment is processed

bwType :: Maybe TransactionType

The type of the transaction

bwNature :: Maybe TransactionNature

The nature of the transaction:

bwPaymentType :: Maybe PaymentType

The type of the payment (which type of mean of payment is used).

bwExecutionType :: Maybe PaymentExecution

How the payment has been executed:

Instances

Eq BankWire 
Ord BankWire 
Show BankWire 
Typeable BankWire 
ToJSON BankWire

to json as per MangoPay format

FromJSON BankWire

from json as per MangoPay format

fetchBankWirePayIn :: MPUsableMonad m => BankWireId -> AccessToken -> MangoPayT m BankWireSource

fetch a bank wire pay-in from its Id

mkBankWire :: AnyUserId -> AnyUserId -> WalletId -> Amount -> Amount -> BankWireSource

helper function to create a new bank wire with the needed information

type CardPayinId = TextSource

Id of a direct pay in

data CardPayin Source

direct pay in via registered card

Constructors

CardPayin 

Fields

cpId :: Maybe CardPayinId
 
cpCreationDate :: Maybe POSIXTime
 
cpTag :: Maybe Text

custom data

cpAuthorId :: AnyUserId

The user Id of the author

cpCreditedUserId :: AnyUserId

The user Id of the owner of the credited wallet

cpFees :: Amount

It represents your fees taken on the DebitedFundsDebitedFunds – Fees = CreditedFunds (amount received on wallet)

cpCreditedWalletId :: WalletId

The Id of the credited wallet

cpDebitedWalletId :: Maybe WalletId

The Id of the debited wallet

cpDebitedFunds :: Amount

It represents the amount debited from the bank account.

cpCreditedFunds :: Maybe Amount

It represents the amount credited on the targeted e-wallet.

cpSecureModeReturnURL :: Maybe Text

This URL will be used in case the SecureMode is activated.

cpSecureMode :: Maybe Text

The SecureMode correspond to

cpSecureModeRedirectURL :: Maybe Text

This URL will be used in case the SecureMode is activated.

cpCardId :: CardId

The Id of the registered card (Got through CardRegistration object)

cpStatus :: Maybe TransferStatus

The status of the payment

cpResultCode :: Maybe Text

The transaction result code

cpResultMessage :: Maybe Text

The transaction result Message

cpExecutionDate :: Maybe POSIXTime
 
cpType :: Maybe TransactionType

The type of the transaction

cpNature :: Maybe TransactionNature

The nature of the transaction:

cpPaymentType :: Maybe Text

The type of the payment (which type of mean of payment is used).

cpExecutionType :: Maybe PaymentExecution

How the payment has been executed:

Instances

Eq CardPayin 
Ord CardPayin 
Show CardPayin 
Typeable CardPayin 
ToJSON CardPayin

to json as per MangoPay format

FromJSON CardPayin

from json as per MangoPay format

createCardPayin :: MPUsableMonad m => CardPayin -> AccessToken -> MangoPayT m CardPayinSource

create a direct card pay in

fetchCardPayin :: MPUsableMonad m => CardPayinId -> AccessToken -> MangoPayT m CardPayinSource

fetch a direct card pay in from its Id

mkCardPayin :: AnyUserId -> AnyUserId -> WalletId -> Amount -> Amount -> Text -> CardId -> CardPayinSource

helper function to create a new direct payin with the needed information | the url is only used in secure mode but is REQUIRED by MangoPay

type PayoutId = TextSource

id of payout

data Payout Source

payout

Constructors

Payout 

Fields

ptId :: Maybe PayoutId
 
ptCreationDate :: Maybe POSIXTime
 
ptTag :: Maybe Text

custom data for client

ptAuthorId :: AnyUserId

The user Id of the author

ptDebitedWalletId :: WalletId
 
ptDebitedFunds :: Amount
 
ptFees :: Amount
 
ptBankAccountId :: BankAccountId
 
ptCreditedUserId :: Maybe AnyUserId
 
ptCreditedFunds :: Maybe Amount
 
ptStatus :: Maybe TransferStatus
 
ptResultCode :: Maybe Text

The transaction result code

ptResultMessage :: Maybe Text

The transaction result code

ptExecutionDate :: Maybe POSIXTime
 
ptType :: Maybe TransactionType
 
ptNature :: Maybe TransactionNature
 
ptPaymentType :: Maybe PaymentType
 
ptMeanOfPaymentType :: Maybe PaymentType
 

Instances

Eq Payout 
Ord Payout 
Show Payout 
Typeable Payout 
ToJSON Payout

to json as per MangoPay format

FromJSON Payout

from json as per MangoPay format

mkPayout :: AnyUserId -> WalletId -> Amount -> Amount -> BankAccountId -> PayoutSource

make a simplep payout for creation

fetchPayout :: MPUsableMonad m => PayoutId -> AccessToken -> MangoPayT m PayoutSource

fetch an payout from its Id

data CardRegistration Source

a card registration

Constructors

CardRegistration 

Fields

crId :: Maybe CardRegistrationId

The Id of the object

crCreationDate :: Maybe POSIXTime

The creation date of the object

crTag :: Maybe Text

Custom data

crUserId :: AnyUserId

The Id of the author

crCurrency :: Currency

The currency of the card registrated

crAccessKey :: Maybe Text

This key has to be sent with the card details and the PreregistrationData

crPreregistrationData :: Maybe Text

This passphrase has to be sent with the card details and the AccessKey

crCardRegistrationURL :: Maybe Text

The URL where to POST the card details, the AccessKey and PreregistrationData

crRegistrationData :: Maybe Text

You get the CardRegistrationData once you posted the card details, the AccessKey and PreregistrationData

crCardType :: Maybe Text
 
crCardId :: Maybe CardId

You get the CardId (to process payments) once you edited the CardRegistration Object with the RegistrationData

crResultCode :: Maybe Text

The result code of the object

crResultMessage :: Maybe Text

The message explaining the result code

crStatus :: Maybe DocumentStatus

The status of the object.

Instances

Eq CardRegistration 
Ord CardRegistration 
Show CardRegistration 
Typeable CardRegistration 
ToJSON CardRegistration

to json as per MangoPay format

FromJSON CardRegistration

from json as per MangoPay format

type CardRegistrationId = TextSource

card registration Id

type CardId = TextSource

Id of a card

data CardInfo Source

credit card information

Constructors

CardInfo 

Instances

Eq CardInfo 
Ord CardInfo 
Read CardInfo 
Show CardInfo 
Typeable CardInfo 

data Card Source

a registered card

Constructors

Card 

Fields

cId :: CardId
 
cCreationDate :: POSIXTime
 
cTag :: Maybe Text
 
cExpirationDate :: CardExpiration

MMYY

cAlias :: Text

Example: 497010XXXXXX4414

cCardProvider :: Text

The card provider, it could be

cCardType :: Text
 
cProduct :: Maybe Text
 
cBankCode :: Maybe Text
 
cActive :: Bool
 
cCurrency :: Currency
 
cValidity :: CardValidity

Once we proceed (or attempted to process) a payment with the card we are able to indicate if it is

cCountry :: Text
 
cUserId :: AnyUserId
 

Instances

Eq Card 
Ord Card 
Show Card 
Typeable Card 
ToJSON Card

to json as per MangoPay format

FromJSON Card

from json as per MangoPay format

data CardValidity Source

validity of a card

Constructors

UNKNOWN 
VALID 
INVALID 

Instances

Bounded CardValidity 
Enum CardValidity 
Eq CardValidity 
Ord CardValidity 
Read CardValidity 
Show CardValidity 
Typeable CardValidity 
ToJSON CardValidity

to json as per MangoPay format

FromJSON CardValidity

from json as per MangoPay format

mkCardRegistration :: AnyUserId -> Currency -> CardRegistrationSource

helper function to create a new card registration

fetchCard :: MPUsableMonad m => CardId -> AccessToken -> MangoPayT m CardSource

fetch a card from its Id

listCards :: MPUsableMonad m => AnyUserId -> Maybe Pagination -> AccessToken -> MangoPayT m (PagedList Card)Source

list all cards for a given user

type RefundId = TextSource

id of a refund

data Refund Source

refund of a transfer

Constructors

Refund 

Fields

rId :: RefundId

Id of the refund

rCreationDate :: POSIXTime
 
rTag :: Maybe Text

Custom data

rAuthorId :: AnyUserId

The user Id of the author

rDebitedFunds :: Amount

Strictly positive amount. In cents.

rFees :: Amount

In cents

rCreditedFunds :: Amount

In cents

rStatus :: TransferStatus
 
rResultCode :: Text

The transaction result code

rResultMessage :: Maybe Text

The transaction result Message

rExecutionDate :: POSIXTime
 
rType :: TransactionType
 
rNature :: TransactionNature
 
rCreditedUserId :: Maybe AnyUserId

Id of the user owner of the credited wallet

rInitialTransactionId :: TransactionId

Id of the transaction being refunded

rInitialTransactionType :: TransactionType

The type of the transaction before being refunded (PayIn, Refund)

rDebitedWalletId :: WalletId

The Id of the debited Wallet

rCreditedWalletId :: Maybe WalletId

The Id of the credited Wallet

Instances

Eq Refund 
Ord Refund 
Show Refund 
Typeable Refund 
FromJSON Refund

from json as per MangoPay format

data RefundRequest Source

refund request

Constructors

RefundRequest 

Fields

rrAuthorId :: AnyUserId

The user Id of the author

rrDebitedFunds :: Maybe Amount

Strictly positive amount. In cents.

rrFees :: Maybe Amount

In cents

Instances

Eq RefundRequest 
Ord RefundRequest 
Show RefundRequest 
Typeable RefundRequest 
ToJSON RefundRequest

to json as per MangoPay format

refundPayin :: MPUsableMonad m => AnyPayinId -> RefundRequest -> AccessToken -> MangoPayT m RefundSource

refund a pay-in

fetchRefund :: MPUsableMonad m => RefundId -> AccessToken -> MangoPayT m RefundSource

fetch a refund from its Id