assumpta-core-0.1.0.2: Core functionality for an SMTP client

Safe HaskellSafe
LanguageHaskell2010

Network.Mail.Assumpta.MonadSmtp

Contents

Description

A monad for sending SMTP commands and checking for expected responses.

Permissible characters

This module accepts ByteStrings as parameters, but it is the responsibility of the caller to ensure that the bytestrings meet the requirements of the appropriate RFC; we do not validate them.

In general, RFC 5321 commands and replies must be composed of composed of characters from the ASCII character set (with the possible exception of content supplied after a 'DATA' command); see sec 2.4 of the RFC. That is, they must be '7-bit clean'.

RFC 5321 notes that although various SMTP extensions (such as "8BITMIME", RFC 1652) may relax this restriction for the content body, content header fields are always encoded using US-ASCII. See also RFC 3030, "SMTP Service Extensions", for details of suppling DATA in non-ASCII format.

Note also that unless increased using some SMTP extension, RFC 5321 imposes maximum sizes on the length of (<CRLF>-terminated) lines sent to the server (see sec. 4.5.3, "Sizes and Timeouts"). Again, we don't enforce these requirements, it's up to the caller to check that they're satisfied.

Constructing email messages

This package does not provide facilities for constructing email messages, but only sending them via SMTP. See the mime-mail package to construct and properly render email messages.

Synopsis

SMTP monad

class Monad m => MonadSmtp m where Source #

Monad for sending SMTP commands and checking for expected responses.

Minimal complete definition

send, getReply, tlsUpgrade

Methods

send :: ByteString -> m () Source #

Send some bytes.

getReply :: m Reply Source #

Attempt to read a response from the server, parsing it as a Reply.

expectCode :: ReplyCode -> m () Source #

Attempt to read and parse a server response, indicating that we expect it to be the given ReplyCode.

In some MonadSmtp instances, failure of the expectation will result in an exception being thrown. If you are writing an instance of MonadSmtp m where MonadError SmtpError m holds, we can supply a default implementation for you.

expectCode :: MonadError SmtpError m => ReplyCode -> m () Source #

Attempt to read and parse a server response, indicating that we expect it to be the given ReplyCode.

In some MonadSmtp instances, failure of the expectation will result in an exception being thrown. If you are writing an instance of MonadSmtp m where MonadError SmtpError m holds, we can supply a default implementation for you.

tlsUpgrade :: m () Source #

Upgrade from plain STMP to SMTPS using default TLS settings

Instances
MonadSmtp m => MonadSmtp (MaybeT m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

Monad m => MonadSmtp (MockSmtpT m) Source #

In this mock monad, send writes to the underlying Writer; expectCode and tlsUpgrade are no-ops; and getReply returns an empty list. (In breach of the req. that a reply always contains at least one line.)

Instance details

Defined in Network.Mail.Assumpta.Mock

MonadSmtp m => MonadSmtp (ExceptT e m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

MonadSmtp m => MonadSmtp (IdentityT m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

MonadSmtp m => MonadSmtp (StateT s m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

MonadSmtp m => MonadSmtp (StateT s m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

(Monoid w, MonadSmtp m) => MonadSmtp (WriterT w m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

(Monoid w, MonadSmtp m) => MonadSmtp (WriterT w m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

(Connection conn, cstr ~ Cstrt conn, Monad m, cstr (SmtpT conn m)) => MonadSmtp (SmtpT conn m) Source #

An instance of MonadSmtp communicating over some Connection type, conn.

Instance details

Defined in Network.Mail.Assumpta.Trans.Smtp

Methods

send :: ByteString -> SmtpT conn m () Source #

getReply :: SmtpT conn m Reply Source #

expectCode :: ReplyCode -> SmtpT conn m () Source #

tlsUpgrade :: SmtpT conn m () Source #

MonadSmtp m => MonadSmtp (ReaderT r m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

(Monoid w, MonadSmtp m) => MonadSmtp (RWST r w s m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

Methods

send :: ByteString -> RWST r w s m () Source #

getReply :: RWST r w s m Reply Source #

expectCode :: ReplyCode -> RWST r w s m () Source #

tlsUpgrade :: RWST r w s m () Source #

(Monoid w, MonadSmtp m) => MonadSmtp (RWST r w s m) Source # 
Instance details

Defined in Network.Mail.Assumpta.MonadSmtp

Methods

send :: ByteString -> RWST r w s m () Source #

getReply :: RWST r w s m Reply Source #

expectCode :: ReplyCode -> RWST r w s m () Source #

tlsUpgrade :: RWST r w s m () Source #

SMTP commands

helo :: MonadSmtp m => ByteString -> m () Source #

Convenience func.

helo myhostname will send 'HELO myhostname', expect 250.

ehlo :: MonadSmtp m => ByteString -> m () Source #

Convenience func.

ehlo myhostname will send 'EHLO myhostname', expect 250.

mailFrom :: MonadSmtp m => ByteString -> m () Source #

Convenience func.

mailFrom sender will send 'MAIL FROM:<sender>', expect 250.

rcptTo :: MonadSmtp m => ByteString -> m () Source #

Convenience func.

rcptTo recipient will send 'RCPT TO:<recipient>', expect 250.

data_ :: MonadSmtp m => ByteString -> m () Source #

convenience func. Send a 'DATA' command, expect 354, send bytestring content (which should be terminated by the sequence <CRLF.CRLF>), expect 354.

See RFC 5321 for details of the DATA command.

Prerequisites:

  • "The mail data may contain any of the 128 ASCII character codes, although experience has indicated that use of control characters other than SP, HT, CR, and LF may cause problems and SHOULD be avoided when possible." [RFC 5321, p. 35]

    We don't check that the bytestring being sent is indeed 7-bit clean; that's up to the caller.

  • Any periods at the start of a line SHOULD be escaped. (See RFC 5321, p. 61, "Transparency".) It is up to the caller to ensure this has been done.
  • The content passed should end in '<CRLF.CRLF>' (i.e., a <CRLF>, then a full stop on a line by itself, then <CRLF>. We don't check that this is the case.

noop :: MonadSmtp m => m () Source #

Convenience func. Send NOOP, expect 250.

See RFC 5321, p. 39, sec 4.1.1.9 ("NOOP (NOOP)")

quit :: MonadSmtp m => m () Source #

Convenience func. Send QUIT, expect 221.

See RFC 5321, p. 39, sec 4.1.1.10 ("QUIT (QUIT)").

rset :: MonadSmtp m => m () Source #

Convenience func. Send RSET (used to abort transaction), expect 250.

See RFC 5321, p. 37, sec 4.1.1.5 ("RESET (RSET)").

startTLS :: MonadSmtp m => m () Source #

Try to get TLS going on an SMTP connection.

After this, you should send an EHLO.

RFC reference: ???

expn :: MonadSmtp m => ByteString -> m Reply Source #

Convenience func.

expn recipient will send 'EXPN recipient' and attempt to parse a Reply. The EXPN command asks the server to verify that the recipient is a mailing list, and return the members of the list. Many servers restrict access to this command.

vrfy :: MonadSmtp m => ByteString -> m Reply Source #

Convenience func.

vrfy recipient will send 'VRFY recipient' and attempt to parse a Reply. The VRFY command asks the server to confirm that the argument identifies a user or mailbox. Many servers restrict access to this command

help :: MonadSmtp m => Maybe ByteString -> m Reply Source #

Convenience func.

help myhostname will send 'HELP myhostname' and attempt to parse a Reply.

Server responses

expect :: (MonadSmtp m, MonadError SmtpError m) => (ReplyCode -> Bool) -> String -> m Reply Source #

expect pred expectDescrip

Fetch a reply, and validate that its reply code meets predicate pred; on failure, an UnexpectedResponse is thrown into the MonadError monad. (So a caller can easily convert it to a Maybe or Either or any other instance.)

Takes a human-readable description of what was expected, which is included in the exception.

Useful for implementing expectCode.

expectGreeting :: MonadSmtp m => m () Source #

Expect code 220, a "Service ready" message (or "greeting").

Every client session should start by waiting for the server to send a "Service ready" message.

Low-level MonadSmtp operations

sendLine :: MonadSmtp m => ByteString -> m () Source #

Send some bytes, with a crlf inserted at the end.

command :: MonadSmtp m => SmtpCommand -> m () Source #

Send a command, without waiting for the reply.

Send an email message

sendRawMail :: (MonadSmtp m, Foldable t) => ByteString -> t ByteString -> ByteString -> m () Source #

sendRawMail sender recipients message

convenience func. Expects a raw ByteString that can be sent after a data command.

Just a sequence of mailFrom the sender, rcptTo calls for each recipient, then data_ of the message.

We don't alter the content of message, except insofar as specified by RFC, p. 36, namely: If the body content passed does not end in <CRLF>, a client must either reject the message as invalid or add <CRLF> to the end; we do the latter. (We are not permitted to alter the content in any other case.)

We then append the '<.CRLF>' used to terminate the data (this is not considered part of the message).

Other than that, the same requirements apply as for the data_ function.

Types

data SmtpCommand Source #

SMTP commands. This type does not include the 'AUTH' command, which has a flexible form.

type Reply = [ReplyLine] Source #

Response from a serve

data ReplyLine Source #

One line of a reply from a server, consisting of a ReplyCode and US-ASCII message.

Constructors

ReplyLine 
Instances
Show ReplyLine Source # 
Instance details

Defined in Network.Mail.Assumpta.Types

type ReplyCode = Int Source #

Reply code from a server

data SmtpError Source #

Errors that can occur during SMTP operations.

These don't include connectivity and other IO errors which might occur in the underlying transport mechanism; those should be handled elsewhere (if necessary).

The possible errors are that either (a) we couldn't parse the server's response at all, or (b) we could, but it wasn't what we expected.

Constructors

UnexpectedResponse

We received a response contrary to what we expected. The first field is a description of what we expected, the second of what we got.

Fields

ParseError String

We couldn't parse the server's response; the parser gave the error message contained in the ParseError.

Instances
Show SmtpError Source # 
Instance details

Defined in Network.Mail.Assumpta.Types

Monad m => MonadError SmtpError (SmtpT conn m) # 
Instance details

Defined in Network.Mail.Assumpta.Trans.Smtp

Methods

throwError :: SmtpError -> SmtpT conn m a #

catchError :: SmtpT conn m a -> (SmtpError -> SmtpT conn m a) -> SmtpT conn m a #

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances
Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

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

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

IsString ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString :: * #

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

ByteArray ByteString 
Instance details

Defined in Data.ByteArray.Types

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, ByteString) #

ByteArrayAccess ByteString 
Instance details

Defined in Data.ByteArray.Types

Methods

length :: ByteString -> Int #

withByteArray :: ByteString -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: ByteString -> Ptr p -> IO () #

Monad m => MonadWriter ByteString (MockSmtpT m) # 
Instance details

Defined in Network.Mail.Assumpta.Mock

type State ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString = Buffer
type ChunkElem ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Utility functions

crlf :: IsString p => p Source #

A "\r\n" sequence, indicated <CRLF> in the RFC, used to terminate all lines sent.