pop3-client-0.1.4: POP3 Client Library

Portabilityportable
Stabilityprovisional
Maintainertmrudick@gmail.com

Network.POP3.Client

Contents

Description

This module contains function to connect to a POP3 server and retrieve messages and other information from it.

This library is designed to be safe to use: connections are guaranteed to be closed after the POP3 commands have been executed.

Example of downloading the latest email message:

module Main where 

import Network.POP3.Client

main :: IO ()
main = do
    let account = POP3Account "pop3.example.org" defaultPort "my_username" "my_password"
    message <- withPOP3 account $ do
        total <- getNumberOfMessages
        getMessage total
    putStrLn $ show message

Example using the hsemail package to parse the message headers and body:

module Main where 

import Network.POP3.Client
import Control.Monad.Error
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Error
import qualified Text.ParserCombinators.Parsec.Rfc2822 as MP

parseMessage s = case parse MP.message "" s of
    Left err -> throwError $ concatMap messageString (errorMessages err)
    Right m  -> return m

main :: IO ()
main = do
    -- retrieve 5 latest messages and parse them using hsemail
    let account = POP3Account "pop3.example.org" defaultPort "my_username" "my_password"
    messages <- withPOP3 account $ do
        total <- getNumberOfMessages
        messages <- mapM getMessage $ take 5 (reverse [1..total])
        mapM parseMessage messages
    putStrLn $ show messages

Synopsis

Types

type POP3 = ErrorT String (ReaderT Connection IO)Source

The POP3 action. Encapsulates the network connection handle and provides error handling.

data POP3Account Source

A record which contains all settings needed to connect to a POP3 server and to authenticate.

Constructors

POP3Account 

Fields

accHostname :: String

The hostname of the server to connect to

accPort :: Int

The port to connect to (use defaultPort if you want to use the default POP3 port)

accUsername :: String

The username to login with

accPassword :: String

The password to login with

type MessageID = IntegerSource

The message ID as the position in the list of messages on the server, from [1..getNumberOfMessages]. Note that this type does NOT represent the unique IDs (UIDL) of messages as returned by getUniqueID.

Constants

defaultPort :: IntSource

Default POP3 port (110)

Connecting and authenticating

withPOP3 :: POP3Account -> POP3 a -> IO (Either String a)Source

Connects to the given host and port, executes the given POP3 action(s), closes the connection, and finally returns the result op the (last) POP3 action.

If an error occurs, the action is aborted and an error message is returned.

The connection is guaranteed to be closed before returning from this function, even when an exception occurs during the session.

Retrieving mailbox size

getNumberOfMessages :: POP3 IntegerSource

Returns the number of messages stored in the POP3 mailbox.

getMailboxBytes :: POP3 IntegerSource

Returns the size of the POP3 mailbox in bytes.

Retrieving messages

getUniqueID :: MessageID -> POP3 StringSource

Returns the unique ID (UIDL) of a message on the server. The message ID should be in the range [1..getNumberOfMessages].

getSize :: MessageID -> POP3 IntegerSource

Returns the size of a message on the server in bytes. Note that this may not correspond exactly to the size of the message as it is downloaded, because of newline and escape values. The message ID should be in the range [1..getNumberOfMessages].

getMessage :: MessageID -> POP3 StringSource

Retrieves a POP3 message from the server and returns it parsed as a Message. The message ID should be in the range [1..getNumberOfMessages].

getFirstNLines :: MessageID -> Integer -> POP3 StringSource

Retrieves a the headers and the first n lines of a message from the server and returns it parsed as a Message. The message ID should be in the range [1..getNumberOfMessages].

getHeaders :: MessageID -> POP3 StringSource

Retrieves a the headers of a message from the server and returns it parsed as a Message. The message ID should be in the range [1..getNumberOfMessages].

Deleting messages

deleteMessage :: MessageID -> POP3 StringSource

Marks a message as to be deleted and returns a Bool which indicates a success. The message ID should be in the range [1..getNumberOfMessages]. The message will actually be deleted from the server on QUIT.