assumpta-0.1.0.0: An SMTP client library

Safe HaskellNone
LanguageHaskell2010

Network.Mail.Assumpta.Text

Contents

Description

Text versions of Smtp operations.

This module does not validate that your text satisfies 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 text must consist of 7-bit clean ASCII.

Example code

Short example (which will work if you have an SMTP server running on local port 2025): (see the examples directory for a copy of the code):


-- Program that runs a short SMTP session
-- with a server running on local port 2025.

module Main where

import           Data.Monoid
import qualified Data.Text as T
import Network.BSD (getHostName) -- requires 'network' package
import Network.Mail.Assumpta.Text

sampleMesg :: T.Text
sampleMesg = T.intercalate crlf [
    "Date: Tue, 21 Jan 2020 02:28:37 +0800"
  , "To: neddie.seagoon@gmail.com"
  , "From: jim.moriarty@gmail.com"
  , "Subject: test Tue, 21 Jan 2020 02:28:37 +0800"
  , ""
  , "Sapristi nyuckoes!"
  ]

-- The sender and recipient supplied to the
-- SMTP server are what is used to route the
-- message; any 'To:' and 'From:' fields
-- in the message are completely ignored for this
-- purpose.
sender, recipient :: T.Text
sender = "somesender@mycorp.com"
recipient = "somerecipient@mozilla.org"

main :: IO ()
main = do
  let  
      port = 2025
  hostname <- getHostName
  print =<< runSmtp "localhost" port (do
          expectGreeting
          ehlo $ T.pack hostname
          -- Properly, we should escape periods at the start of a
          -- line. But we know there aren't any
          sendRawMail sender [recipient] sampleMesg
          quit)

Alternatives to "connection"

If you want to use other network libraries besides connection, it should be pretty straightforward to adapt the code here.

If you want to use stream-like IO, one possibility is the conduit-connection package, which provides Conduit-based sources and sinks on top of Network.Connection.

Synopsis

Run Smtp actions

Run actions in the MonadSmtp monad.

runSmtp :: HostName -> Int -> Smtp a -> IO (Either SmtpError a) Source #

runSmtp hostname port a

Open a connection to the specified hostname and port, run some Smtp action a with it, then close, returning the result as an Either.

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.).

runSmtpHandle :: Handle -> Smtp a -> IO (Either SmtpError a) Source #

runSmtpHandle h a

Run some Smtp action a on a Handle h, and return the result as an Either.

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.

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

See helo

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

See ehlo

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

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

See rcptTo

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

See data_

noop :: MonadSmtp m => m () #

Convenience func. Send NOOP, expect 250.

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

quit :: MonadSmtp m => m () #

Convenience func. Send QUIT, expect 221.

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

rset :: MonadSmtp m => m () #

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: ???

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

See expn

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

See vrfy

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

simpleMail Source #

Arguments

:: Address

to

-> Address

from

-> Text

subject

-> Text

plain body

-> Text

HTML body

-> [(Text, FilePath)]

content type and path of attachments

-> String

qualified name of local host

-> String

SMTP server to connect to

-> Int

Port of SMTP server

-> IO (Text, Either SmtpError ()) 

Warning: experimental, likely to change

A simple interface for generating an email with HTML and plain-text alternatives and some file attachments and sending it via an SMTP server.

Uses lazy IO for reading in the attachment contents. Simple wrapper around renderMail'. Caution: Not tested, use with care. Likely to change.

sample use:

> import qualified Network.Mail.Mime as MM
> :set -XOverloadedStrings
> :{
  let addr =  MM.Address (Just "joe") "joe@nowhere"
      subj = "a test subject"
      body = "a test body"
> :}
> simpleMail addr addr subj body "" [] "myserver.mydomain.com" "mail.yourserver.org" 2025

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.

type Reply = [ReplyLine] #

Response from a serve

data ReplyLine #

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

Constructors

ReplyLine 
Instances
Show ReplyLine 
Instance details

Defined in Network.Mail.Assumpta.Types

type ReplyCode = Int #

Reply code from a server

data SmtpError #

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 
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 #

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.

type Smtp = SmtpT IO Source #

Smtp actions in the IO monad.

liftSmtpT :: Monad m => m a -> SmtpT conn m a #

lift, specialised to the SmtpT transformer.

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

close :: MonadIO m => Handle -> m () Source #

Close a network Handle

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.

type Port = Int Source #

data Handle Source #

Network handle, containing enough information to both communicate a connection, and upgrade to TLS.

Constructors

Handle 
Instances
Connection Handle Source # 
Instance details

Defined in Network.Mail.Assumpta.Internal.Net

Associated Types

type Cstrt Handle :: (* -> *) -> Constraint #

type Params Handle :: * #

Methods

open :: Cstrt Handle m => Params Handle -> m Handle #

close :: Cstrt Handle m => Handle -> m () #

send :: Cstrt Handle m => Handle -> ByteString -> m () #

recv :: Cstrt Handle m => Handle -> m ByteString #

upgrade :: Cstrt Handle m => Handle -> m () #

type Params Handle Source # 
Instance details

Defined in Network.Mail.Assumpta.Internal.Net

type Cstrt Handle Source # 
Instance details

Defined in Network.Mail.Assumpta.Internal.Net

defaultTLSSettings :: TLSSettings Source #

default TLS settings

send :: MonadSmtp m => Text -> m () Source #

See send

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

Utility functions

toCrLf :: Text -> Text Source #

replace newlines ('\n') with crlf sequence ('\r\n').

rethrow :: Either SmtpError a -> IO a Source #

convenience function: re-throw an SmtpError as an exception in IO.

toIOError :: SmtpError -> IOError Source #

Convenience function: convert an SmtpError into an IOError.

crlf :: IsString p => p #

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

escapePeriods :: Text -> Text Source #

Where a period (.) character starts a (crlf-delimited) line, replace it with two periods.