Safe Haskell | None |
---|---|
Language | Haskell2010 |
String
versions of Smtp operations.
This module does not validate that your strings satisfy the requirements of the relevant RFCs -- see the note in Network.Mail.Assumpta.MonadSmtp about "permissible characters". In general, unless you are using an SMTP extension, your strings must consist of 7-bit clean ASCII.
Synopsis
- runSmtp :: HostName -> Int -> Smtp a -> IO (Either SmtpError a)
- runSecureSmtp :: HostName -> Int -> Smtp a -> IO (Either SmtpError a)
- runSmtpWithParams :: ConnectionParams -> Smtp a -> IO (Either SmtpError a)
- runSmtpHandle :: Handle -> Smtp a -> IO (Either SmtpError a)
- runSmtp' :: (MonadMask m, MonadIO m, MonadError SmtpError m) => HostName -> Port -> SmtpT m b -> m b
- runSecureSmtp' :: (MonadMask m, MonadIO m, MonadError SmtpError m) => HostName -> Int -> SmtpT m b -> m b
- runSmtpWithParams' :: (MonadMask m, MonadIO m, MonadError SmtpError m) => ConnectionParams -> SmtpT m b -> m b
- runSmtpHandle' :: (MonadError SmtpError m, MonadIO m) => Handle -> SmtpT m a -> m a
- helo :: MonadSmtp m => String -> m ()
- ehlo :: MonadSmtp m => String -> m ()
- mailFrom :: MonadSmtp m => String -> m ()
- rcptTo :: MonadSmtp m => String -> m ()
- data_ :: MonadSmtp m => String -> m ()
- noop :: MonadSmtp m => m ()
- quit :: MonadSmtp m => m ()
- rset :: MonadSmtp m => m ()
- startTLS :: MonadSmtp m => m ()
- expn :: MonadSmtp m => String -> m Reply
- vrfy :: MonadSmtp m => String -> m Reply
- help :: MonadSmtp m => Maybe String -> m Reply
- sendRawMail :: (MonadSmtp m, Foldable t) => String -> t String -> String -> m ()
- expect :: (MonadSmtp m, MonadError SmtpError m) => (ReplyCode -> Bool) -> String -> m Reply
- expectGreeting :: MonadSmtp m => m ()
- command :: MonadSmtp m => SmtpCommand -> m ()
- type Reply = [ReplyLine]
- data ReplyLine = ReplyLine {
- replyCode :: !ReplyCode
- replyText :: !ByteString
- type ReplyCode = Int
- data SmtpError
- = UnexpectedResponse { }
- | ParseError String
- type SmtpT = SmtpT Handle
- type Smtp = SmtpT IO
- liftSmtpT :: Monad m => m a -> SmtpT conn m a
- mapSmtpT :: (m1 (Either SmtpError a1) -> m2 (Either SmtpError a2)) -> SmtpT conn m1 a1 -> SmtpT conn m2 a2
- open :: MonadIO m => HostName -> Port -> m Handle
- openTls :: MonadIO m => HostName -> Port -> m Handle
- openParams :: MonadIO m => ConnectionParams -> m Handle
- close :: MonadIO m => Handle -> m ()
- withHandle :: (MonadMask m, MonadIO m) => HostName -> Port -> (Handle -> m b) -> m b
- withSecureHandle :: (MonadMask m, MonadIO m) => HostName -> Port -> (Handle -> m b) -> m b
- withHandleParams :: (MonadMask m, MonadIO m) => ConnectionParams -> (Handle -> m b) -> m b
- type HostName = String
- type Port = Int
- data Handle = Handle {
- hConn :: !Connection
- hContext :: !ConnectionContext
- defaultTLSSettings :: TLSSettings
- send :: MonadSmtp m => String -> m ()
- sendLine :: MonadSmtp m => String -> m ()
- toCrLf :: String -> String
- rethrow :: Either SmtpError a -> IO a
- mkParams :: HostName -> Int -> ConnectionParams
- toIOError :: SmtpError -> IOError
- crlf :: IsString p => p
- escapePeriods :: String -> String
Run Smtp actions
Run actions in the MonadSmtp
monad.
runSecureSmtp :: HostName -> Int -> Smtp a -> IO (Either SmtpError a) Source #
runSecureSmtp hostname port a
Open a secure TLS connection to the specified hostname
and port
,
run some Smtp
action a
with it, then
close, returning the result as an Either
.
Uses the default TLS settings, defaultTLSSettings
. For
more control, use runSmtpWithParams
.
runSmtpWithParams :: ConnectionParams -> Smtp a -> IO (Either SmtpError a) Source #
runSmtpWithParams params a
Like runSmtp
, but providing more control --
the actions are run using the specified connection
parameters (hostname, port, TLS settings, etc.).
MonadError variants
Instead of returning an Either, these run in MonadError --
thus the caller can specialize them to a Maybe
, Either
,
or some other MonadError
instance as desired.
runSmtp' :: (MonadMask m, MonadIO m, MonadError SmtpError m) => HostName -> Port -> SmtpT m b -> m b Source #
runSmtp' host port a
Like runSmtp
, but generalized to MonadError
.
runSecureSmtp' :: (MonadMask m, MonadIO m, MonadError SmtpError m) => HostName -> Int -> SmtpT m b -> m b Source #
runSecureSmtp' host port a
Like runSecureSmtp
, but generalized to MonadError
.
runSmtpWithParams' :: (MonadMask m, MonadIO m, MonadError SmtpError m) => ConnectionParams -> SmtpT m b -> m b Source #
runSmtpWithParams' params a
Like runSmtpWithParams
, but generalized to MonadError
.
runSmtpHandle' :: (MonadError SmtpError m, MonadIO m) => Handle -> SmtpT m a -> m a Source #
runSmtpHandle h a
Run some Smtp
action a
on a Handle
h
,
and return the result as a MonadError
.
Like runSmtpHandle
but generalized to MonadError
.
SMTP commands
Functions for sending commands
to an SMTP server. In general, these are wrappers around
command
and expect
-- they send some command,
and try to parse a response (throwing an SmtpError
on failure).
See the Network.Mail.Assumpta.ByteString module for
documentation of each function.
Convenience func. Send NOOP, expect 250.
See RFC 5321, p. 39, sec 4.1.1.9 ("NOOP (NOOP)")
Convenience func. Send QUIT, expect 221.
See RFC 5321, p. 39, sec 4.1.1.10 ("QUIT (QUIT)").
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 () #
Try to get TLS going on an SMTP connection.
After this, you should send an EHLO.
RFC reference: ???
sendRawMail :: (MonadSmtp m, Foldable t) => String -> t String -> String -> m () Source #
see sendRawMail
.
Server responses
expect :: (MonadSmtp m, MonadError SmtpError m) => (ReplyCode -> Bool) -> String -> m Reply #
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 () #
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 operations and types
command :: MonadSmtp m => SmtpCommand -> m () #
Send a command, without waiting for the reply.
One line of a reply from a server, consisting of a ReplyCode
and US-ASCII message.
ReplyLine | |
|
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.
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. |
ParseError String | We couldn't parse the server's
response; the parser gave the
error message contained in the |
Instances
Show SmtpError | |
Monad m => MonadError SmtpError (SmtpT conn m) | |
Defined in Network.Mail.Assumpta.Trans.Smtp throwError :: SmtpError -> SmtpT conn m a # catchError :: SmtpT conn m a -> (SmtpError -> SmtpT conn m a) -> SmtpT conn m a # |
Monad transformer
A monad transformer, SmtpT
, which provides the ability to
send SMTP commands and parse replies, together with operations
on the transformer.
type SmtpT = SmtpT Handle Source #
Smtp monad transformer. A specialization to Handle
of the more general SmtpT type in the
assumpta-core
package.
mapSmtpT :: (m1 (Either SmtpError a1) -> m2 (Either SmtpError a2)) -> SmtpT conn m1 a1 -> SmtpT conn m2 a2 #
Lifted mapExceptT
.
Network operations
open :: MonadIO m => HostName -> Port -> m Handle Source #
Open a network Handle
to the specified hostname and port
openTls :: MonadIO m => HostName -> Port -> m Handle Source #
Open a secure network Handle
to the specified hostname and port
using the default TLS settings (defaultTLSSettings
)
openParams :: MonadIO m => ConnectionParams -> m Handle Source #
Open a network Handle
with the specified ConnectionParams
withHandle :: (MonadMask m, MonadIO m) => HostName -> Port -> (Handle -> m b) -> m b Source #
withHandle hostname port a
Open a Handle
to the specified hostname
and port
,
run some action a
with it, then
close.
withSecureHandle :: (MonadMask m, MonadIO m) => HostName -> Port -> (Handle -> m b) -> m b Source #
withSecureHandle hostname port a
Open a secure Handle
to the specified hostname
and port
,
run some action a
with it, then
close.
withHandleParams :: (MonadMask m, MonadIO m) => ConnectionParams -> (Handle -> m b) -> m b Source #
withHandleParams p a
Given some parameters p
(hostname, port etc) for opening a Handle
:
open a handle, run some action a
with it, then
close.
Network handle, containing enough information to both communicate a connection, and upgrade to TLS.
Handle | |
|
Instances
Connection Handle Source # | |
Defined in Network.Mail.Assumpta.Internal.Net | |
type Params Handle Source # | |
Defined in Network.Mail.Assumpta.Internal.Net | |
type Cstrt Handle Source # | |
Defined in Network.Mail.Assumpta.Internal.Net |
defaultTLSSettings :: TLSSettings Source #
default TLS settings
Utility functions
A "\r\n"
sequence, indicated <CRLF>
in the RFC,
used to terminate all lines sent.