mailtrap-0.1.2.1: Mailtrap API library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.Mail.Mailtrap

Description

Mailtrap API.

Synopsis

Tokens

newtype Token Source #

Authorization token.

Constructors

Token Text 

Instances

Instances details
FromJSON Token Source # 
Instance details

Defined in Network.Mail.Mailtrap

ToJSON Token Source # 
Instance details

Defined in Network.Mail.Mailtrap

Show Token Source # 
Instance details

Defined in Network.Mail.Mailtrap

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in Network.Mail.Mailtrap

Methods

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

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

data Exception Source #

Exceptions thrown by functions from this module.

Constructors

MultipleErrors Int [Text]

API request returned list of errors. HTTP status code and error messages.

SingleError Int Text

API request returned a single error message. HTTP status code and error message.

ParsingError ByteString String

Parsing failed. Input that failed to parse plus error message.

Accounts

newtype AccountID Source #

Mailtrap account ID.

Constructors

AccountID Int 

Instances

Instances details
FromJSON AccountID Source # 
Instance details

Defined in Network.Mail.Mailtrap

Show AccountID Source # 
Instance details

Defined in Network.Mail.Mailtrap

Eq AccountID Source # 
Instance details

Defined in Network.Mail.Mailtrap

data Account Source #

Mailtrap account.

Constructors

Account 

Instances

Instances details
FromJSON Account Source # 
Instance details

Defined in Network.Mail.Mailtrap

Show Account Source # 
Instance details

Defined in Network.Mail.Mailtrap

getAllAccounts :: Token -> IO [Account] Source #

Get all the accounts the given token has access to.

Attachments

data Disposition Source #

Attachment disposition.

Constructors

Inline Text

Inline with identifier.

Attached 

Instances

Instances details
Show Disposition Source # 
Instance details

Defined in Network.Mail.Mailtrap

setDisposition :: Disposition -> Attachment -> Attachment Source #

Set an attachment's disposition.

data Attachment Source #

File that can be attached to an e-mail.

Constructors

Attachment 

Fields

attachmentFromFile :: FilePath -> IO Attachment Source #

Create an attachment from a file. It guesses the mime type from the file extension. Disposition is set to Attached. The file is read strictly.

Templates

data Template Source #

Template that can be used when sending e-mails.

Constructors

Template 

Fields

Instances

Instances details
Show Template Source # 
Instance details

Defined in Network.Mail.Mailtrap

template :: UUID -> Template Source #

Template with no variable set.

setTemplateVariable :: ToJSON a => Text -> a -> Template -> Template Source #

Set template variable.

Testing inboxes

newtype InboxID Source #

Testing inbox identifier.

Constructors

InboxID Int 

Instances

Instances details
FromJSON InboxID Source # 
Instance details

Defined in Network.Mail.Mailtrap

Show InboxID Source # 
Instance details

Defined in Network.Mail.Mailtrap

Eq InboxID Source # 
Instance details

Defined in Network.Mail.Mailtrap

Methods

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

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

data Inbox Source #

Testing inbox.

Constructors

Inbox 

Fields

Instances

Instances details
FromJSON Inbox Source # 
Instance details

Defined in Network.Mail.Mailtrap

Show Inbox Source # 
Instance details

Defined in Network.Mail.Mailtrap

Methods

showsPrec :: Int -> Inbox -> ShowS #

show :: Inbox -> String #

showList :: [Inbox] -> ShowS #

getInboxes :: Token -> AccountID -> IO [Inbox] Source #

Get all inboxes from an account.

getInboxMessages :: Token -> AccountID -> InboxID -> IO [InboxMessage] Source #

Get all inbox messages from an testing inbox.

downloadMessageRaw :: Token -> AccountID -> InboxID -> InboxMessageID -> IO Text Source #

Download inbox message raw email body.

downloadMessageEML :: Token -> AccountID -> InboxID -> InboxMessageID -> IO Text Source #

Download inbox message in EML format.

downloadMessageText :: Token -> AccountID -> InboxID -> InboxMessageID -> IO Text Source #

Download inbox message text part.

downloadMessageHTML :: Token -> AccountID -> InboxID -> InboxMessageID -> IO Text Source #

Download inbox message HTML part.

Sending e-mails

data EmailAddress #

Represents an email address.

Instances

Instances details
Data EmailAddress 
Instance details

Defined in Text.Email.Parser

Methods

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

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

toConstr :: EmailAddress -> Constr #

dataTypeOf :: EmailAddress -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic EmailAddress 
Instance details

Defined in Text.Email.Parser

Associated Types

type Rep EmailAddress :: Type -> Type #

Read EmailAddress 
Instance details

Defined in Text.Email.Parser

Show EmailAddress 
Instance details

Defined in Text.Email.Parser

Eq EmailAddress 
Instance details

Defined in Text.Email.Parser

Ord EmailAddress 
Instance details

Defined in Text.Email.Parser

type Rep EmailAddress 
Instance details

Defined in Text.Email.Parser

type Rep EmailAddress = D1 ('MetaData "EmailAddress" "Text.Email.Parser" "email-validate-2.3.2.20-1Vy9fpOYeovBfF4uThfL4t" 'False) (C1 ('MetaCons "EmailAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

parseEmailAddress :: ByteString -> Either String EmailAddress Source #

Attempt to parse an e-mail address

newtype MessageID Source #

Production message identifier.

Constructors

MessageID UUID 

Instances

Instances details
FromJSON MessageID Source # 
Instance details

Defined in Network.Mail.Mailtrap

Show MessageID Source # 
Instance details

Defined in Network.Mail.Mailtrap

Eq MessageID Source # 
Instance details

Defined in Network.Mail.Mailtrap

data Message Source #

E-mail message, including subject and body.

Constructors

Message 

data EmailBody Source #

An e-mail body.

Constructors

PlainTextBody Text

Plain-text body.

HTMLOnlyBody Html

HTML-only body.

HTMLBody Html Text

HTML body with text fallback.

data Email Source #

E-mail that can be sent using sendEmail.

Constructors

Email 

Fields

Instances

Instances details
ToJSON Email Source # 
Instance details

Defined in Network.Mail.Mailtrap

sendEmail :: Token -> Email -> IO [MessageID] Source #

Send an e-mail and return the list of IDs of the messages sent (one per recipient).

sendTestEmail :: Token -> InboxID -> Email -> IO [InboxMessageID] Source #

Send a testing e-mail to the given inbox and return the list of IDs of the messages sent (one per recipient).