Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
SMTP is s an incredibly stable and well supported protocol. Using this rather then API's prevents vendorlocking.
This module provides a ready to go connection pool for SMTP. Which has been used in various deployments already.
Synopsis
- sendEmail :: MonadIO m => Pool SMTPConnection -> Mail -> m ()
- smtpPool :: PoolSettings -> IO (Pool SMTPConnection)
- defSettings :: SmtpCred -> PoolSettings
- data SmtpCred = SmtpCred {}
- data PoolSettings = PoolSettings {}
- openTls :: SmtpCred -> IO SMTPConnection
- openPlain :: SmtpCred -> IO SMTPConnection
- openTls' :: Settings -> SmtpCred -> IO SMTPConnection
- createPoolConfig :: PoolSettings -> PoolConfig SMTPConnection
- emailOptions :: Parser SmtpCred
- poolCred :: Lens' PoolSettings SmtpCred
- poolConnf :: Lens' PoolSettings (SmtpCred -> IO SMTPConnection)
- poolUnused :: Lens' PoolSettings Double
- poolStripeMax :: Lens' PoolSettings Int
- smtpHost :: Lens' SmtpCred String
- smtpLogin :: Lens' SmtpCred String
- smtpPassword :: Lens' SmtpCred String
- smtpPort :: Lens' SmtpCred PortNumber
- data ServiceAuthFailure a
- module Network.HaskellNet.SMTP.SSL
- module Network.HaskellNet.SMTP
- module Data.Pool
Documentation
sendEmail :: MonadIO m => Pool SMTPConnection -> Mail -> m () Source #
Send a Mail
with help of a connection pool.
smtpPool :: PoolSettings -> IO (Pool SMTPConnection) Source #
Construct a connection pool from settings.
defSettings :: SmtpCred -> PoolSettings Source #
Create settings with good defaults from SmtpCred
.
Authentication information for the SMTP connection
SmtpCred | |
|
data PoolSettings Source #
This allows you to override the default settings from defSettings
PoolSettings | |
|
specify connection type
createPoolConfig :: PoolSettings -> PoolConfig SMTPConnection Source #
allows manipulation of the underlying resourcepool config
optparse applicative
lenses
poolConnf :: Lens' PoolSettings (SmtpCred -> IO SMTPConnection) Source #
Exceptions
data ServiceAuthFailure a Source #
Failed to authetnicate with some upstream service (smtp for example)
Instances
(Typeable a, Show a) => Exception (ServiceAuthFailure a) Source # | |
Defined in Network.Mail.Pool toException :: ServiceAuthFailure a -> SomeException # fromException :: SomeException -> Maybe (ServiceAuthFailure a) # displayException :: ServiceAuthFailure a -> String # | |
Show a => Show (ServiceAuthFailure a) Source # | |
Defined in Network.Mail.Pool showsPrec :: Int -> ServiceAuthFailure a -> ShowS # show :: ServiceAuthFailure a -> String # showList :: [ServiceAuthFailure a] -> ShowS # |
re exports
module Network.HaskellNet.SMTP.SSL
module Network.HaskellNet.SMTP
module Data.Pool