domain-auth-0.2.4: Domain authentication library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.DomainAuth.Mail

Description

A library to parse e-mail messages both from a file and Milter(https://www.milter.org/).

Synopsis

Documentation

Types for raw e-mail message

type RawMail = ByteString Source #

Type for raw e-mail message.

type RawFieldKey = ByteString Source #

Field key for raw e-mail message.

type RawFieldValue = ByteString Source #

Field value for raw e-mail message.

type RawBodyChunk = ByteString Source #

Body chunk for raw e-mail message.

Types for parsed e-mail message

data Mail Source #

Type for parsed e-mail message.

Constructors

Mail 

Instances

Instances details
Show Mail Source # 
Instance details

Defined in Network.DomainAuth.Mail.Types

Methods

showsPrec :: Int -> Mail -> ShowS #

show :: Mail -> String #

showList :: [Mail] -> ShowS #

Eq Mail Source # 
Instance details

Defined in Network.DomainAuth.Mail.Types

Methods

(==) :: Mail -> Mail -> Bool #

(/=) :: Mail -> Mail -> Bool #

type Header = [Field] Source #

Header type for parsed e-mail message.

data Field Source #

Field type for parsed e-mail message.

Instances

Instances details
Show Field Source # 
Instance details

Defined in Network.DomainAuth.Mail.Types

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Eq Field Source # 
Instance details

Defined in Network.DomainAuth.Mail.Types

Methods

(==) :: Field -> Field -> Bool #

(/=) :: Field -> Field -> Bool #

type CanonFieldKey = ByteString Source #

Type for canonicalized field key of parsed e-mail message.

type FieldKey = ByteString Source #

Type for field key of parsed e-mail message.

type FieldValue = [ByteString] Source #

Type for field value of parsed e-mail message.

type Body = Seq ByteString Source #

Type for body of parsed e-mail message.

canonicalizeKey :: FieldKey -> CanonFieldKey Source #

Canonicalizing FieldKey for search.

Obtaining Mail

readMail :: FilePath -> IO Mail Source #

Obtain Mail from a file.

getMail :: RawMail -> Mail Source #

Obtain Mail from RawMail.

>>> let out1 = finalizeMail $ pushBody "body" $ pushField "to" "val" $ pushField "from" "val" initialXMail
>>> getMail "from: val\nto: val\n\nbody" == out1
True
>>> let out2 = finalizeMail $ pushBody "body" $ pushField "to" "val" $ pushField "from" "val\tval" initialXMail
>>> getMail "from: val\tval\nto: val\n\nbody" == out2
True
>>> let out3 = finalizeMail $ pushBody "" $ pushField "to" "val" $ pushField "from" "val" initialXMail
>>> getMail "from: val\nto: val\n" == out3
True

Obtaining Mail incrementally.

data XMail Source #

Type for temporary data to parse e-mail message.

Constructors

XMail 

Instances

Instances details
Show XMail Source # 
Instance details

Defined in Network.DomainAuth.Mail.XMail

Methods

showsPrec :: Int -> XMail -> ShowS #

show :: XMail -> String #

showList :: [XMail] -> ShowS #

Eq XMail Source # 
Instance details

Defined in Network.DomainAuth.Mail.XMail

Methods

(==) :: XMail -> XMail -> Bool #

(/=) :: XMail -> XMail -> Bool #

initialXMail :: XMail Source #

Initial value for XMail.

pushField :: RawFieldKey -> RawFieldValue -> XMail -> XMail Source #

Storing field key and field value to the temporary data.

pushBody :: RawBodyChunk -> XMail -> XMail Source #

Storing body chunk to the temporary data.

finalizeMail :: XMail -> Mail Source #

Converting XMail to Mail.

Functions to manipulate Header

fieldsFrom :: FieldKey -> Header -> Header Source #

Obtaining the Field of FieldKey and all fields under FieldKey.

fieldsAfter :: FieldKey -> Header -> Header Source #

Obtaining all fields under FieldKey.

fieldsWith :: [CanonFieldKey] -> Header -> Header Source #

Obtaining all fields with DKIM algorithm.

>>> fieldsWith ["from","to","subject","date","message-id"] [Field "from" "From" ["foo"],Field "to" "To" ["bar"],Field "subject" "Subject" ["baz"],Field "date" "Date" ["qux"],Field "message-id" "Message-Id" ["quux"], Field "received" "Received" ["fiz"], Field "filtered-out" "Filtered-Out" ["buzz"], Field "not-needed" "Not-Needed" ["fizz"]]
[Field {fieldSearchKey = "from", fieldKey = "From", fieldValue = ["foo"]},Field {fieldSearchKey = "to", fieldKey = "To", fieldValue = ["bar"]},Field {fieldSearchKey = "subject", fieldKey = "Subject", fieldValue = ["baz"]},Field {fieldSearchKey = "date", fieldKey = "Date", fieldValue = ["qux"]},Field {fieldSearchKey = "message-id", fieldKey = "Message-Id", fieldValue = ["quux"]}]

Functions to manipulate Field

fieldValueFolded :: Field -> RawFieldValue Source #

Obtaining folded (raw) field value.

fieldValueUnfolded :: Field -> RawFieldValue Source #

Obtaining unfolded (removing CRLF) field value.

Functions to manipulate Body

fromBody :: Body -> Builder Source #

Obtaining body.

fromBodyWith :: (ByteString -> ByteString) -> Body -> Builder Source #

Obtaining body with a canonicalization function.

removeTrailingEmptyLine :: Body -> Body Source #

Removing trailing empty lines.

Special function for DomainKeys and DKIM

parseTaggedValue :: RawFieldValue -> [(ByteString, ByteString)] Source #

Parsing field value of tag=value.

>>> parseTaggedValue " k = rsa ; p= MIGfMA0G; n=A 1024 bit key;"
[("k","rsa"),("p","MIGfMA0G"),("n","A1024bitkey")]
>>> parseTaggedValue " k = \nrsa ;\n p= MIGfMA0G;\n n=A 1024 bit key"
[("k","rsa"),("p","MIGfMA0G"),("n","A1024bitkey")]