addy-0.1.0.0: A full-featured library for parsing, validating, and rendering email addresses

CopyrightThis file is part of the package addy. It is subject to the license
terms in the LICENSE file found in the top-level directory of this
distribution and at:

https://code.devalot.com/open/addy

No part of this package including this file may be copied
modified propagated or distributed except according to the terms
contained in the LICENSE file.
LicenseBSD-2-Clause
Safe HaskellNone
LanguageHaskell2010

Addy

Contents

Description

Email addressed are complicated, really complicated. This library supports all standardized forms of email addresses, including those with UTF-8 encoded Unicode characters. The standards used by this library include:

  • RFC 1123: Requirements for Internet Hosts -- Application and Support
  • RFC 2181: Clarifications to the DNS Specification
  • RFC 3696: Application Techniques for Checking and Transformation of Names
  • RFC 5321: Simple Mail Transfer Protocol
  • RFC 5322: Internet Message Format
  • RFC 6531: SMTP Extension for Internationalized Email
  • RFC 6532: Internationalized Email Headers
Synopsis

How to use this library

Importing

This library is designed to be imported qualified:

import qualified Addy

Decoding addresses

To decode (parse) an email address from text:

>>> Addy.decode "example@example.com"
Right (EmailAddr "example@example.com")
>>> Addy.decode "我買@屋企.香港"
Right (EmailAddr "\25105\36023@\23627\20225.\39321\28207")
>>> Addy.decode "Mary Smith <mary@example.net> (hi there!)"
Right (EmailAddr "Mary Smith <mary@example.net> (hi there!)")
>>> Addy.decode "example@[127.0.0.1]"
Right (EmailAddr "example@[127.0.0.1]")

After decoding, an address is automatically normalized by performing NFC normalization and down-casing the domain name:

>>> Addy.decode "My.Email.Addy@ExAmPlE.COM"
Right (EmailAddr "My.Email.Addy@example.com")

Encoding addresses

Turning an email address back to text is just as easy:

>>> Addy.encode address
"example@example.com"

If an address has an optional display name or comments you can render those with the encodeFull function.

>>> :{
  Addy.decode "Mary Smith <mary@example.net> (hi there!)"
    & second Addy.encodeFull
:}
Right "Mary Smith <mary@example.net> (hi there!)"

Creating addresses

In order to prevent invalid email addresses from being created this library uses newtype wrappers and does not export the data constructors. Therefore you'll need to use the smart constructor approach using the emailAddr function.

If you want to work with the validation functions directly we recommend Applicative syntax:

>>> :{
 Addy.emailAddr
   <$> Addy.validateLocalPart "pjones"
   <*> Addy.validateDomainName "devalot.com"
:}
Success (EmailAddr "pjones@devalot.com")

Prisms for the newtype wrappers are provided if you want to use optics:

>>> :{
 Addy.emailAddr
   <$> "pjones" ^? Addy._LocalPart
   <*> "devalot.com" ^? Addy._DomainName
:}
Just (EmailAddr "pjones@devalot.com")

Optics

Lens and prisms are provided to make working with email addresses easier:

import qualified Addy
import Control.Lens
>>> Addy.decode "example@example.com" ^? _Right . Addy.domain
Just (Domain (DomainName "example.com"))
>>> Addy.decode "example@example.com"
  ^? _Right . Addy.domain . Addy._Domain . Addy._HostNames
Just [HostName "example",HostName "com"]
>>> Addy.decode "example@example.com"
  ^.. _Right . Addy.domain . Addy._Domain
  . Addy._HostNames . traversed . re _HostName
["example","com"]

A word about address literals

Believe it or not, this is a completely valid email address:

>>> Addy.decode "example@[what's my domain name?]"
  ^? _Right . Addy.domain
Just (DomainLiteral (AddressLiteral (Literal "what's my domain name?")))

If you're working with email messages it might be useful to capture these address literals, especially if you know how to interpret them. However, if you're validating user input you probably don't want to allow these.

>>> Addy.decode "e@[127.0.0.1]" ^? _Right
  >>= failover (Addy.domain . Addy._Domain) id
Nothing
>>> Addy.decode "example@example.com" ^? _Right
  >>= failover (Addy.domain . Addy._Domain) id
Just (EmailAddr "example@example.com")

Decoding and encoding

decode :: Text -> Either (NonEmpty Error) EmailAddr Source #

Decode an email address.

Since: 0.1.0.0

decodeLenient :: Text -> Either (NonEmpty Error) EmailAddr Source #

Decode an email address, allowing obsolete characters. The obsolete characters are parsed but not included in the output.

This is useful for exacting email addresses from mail messages but should not be used to validate user input.

>>> Addy.decode "my . email . addy@(WTF)example.com"
Left (ParserFailedError "local part > quoted content > '\"': Failed reading: satisfy" :| [])
>>> Addy.decodeLenient "my . email . addy@(WTF)example.com"
Right (EmailAddr "my.email.addy@example.com (WTF)")

Since: 0.1.0.0

encode :: EmailAddr -> Text Source #

Encode an email address as text. This function produces the short form of an email address. That is, just the LocalPart and the Domain separated by @.

Since: 0.1.0.0

encodeFull :: EmailAddr -> Text Source #

Encode a complete email address to text, including the optional display name and any comments.

Since: 0.1.0.0

Email addresses

data EmailAddr Source #

The representation of a complete email address.

The parser preserves optional components such as the display name and comments. The rendering code can optionally include these optional elements when turning the address back into Text.

Since: 0.1.0.0

Instances
Show EmailAddr Source # 
Instance details

Defined in Addy.Internal.Render

emailAddr :: LocalPart -> DomainName -> EmailAddr Source #

Build an EmailAddr from a LocalPart and DomainName.

Since: 0.1.0.0

displayName :: Lens' EmailAddr (Maybe DisplayName) Source #

Optional display name. Addresses in the name-addr format from RFC 5322 allow descriptive text to precede the address. This is commonly used in email messages to list the name of the address' owner.

Since: 0.1.0.0

localPart :: Lens' EmailAddr LocalPart Source #

The LocalPart of an email address usually references the destination mailbox on the Domain server. However, the content of the LocalPart can only be understood by the receiving Domain.

Since: 0.1.0.0

domain :: Lens' EmailAddr Domain Source #

The Domain refers to the fully-qualified domain name that accepts mail for the associated LocalPart. See the documentation for the Domain type for more details.

Since: 0.1.0.0

comments :: Lens' EmailAddr [Comment] Source #

Addresses in both the name-addr and addr-spec formats support comments.

Since: 0.1.0.0

Display name

data DisplayName Source #

Optional display name. Usually this is the name of the person who receives email at the associated address.

Display Name <example@example.com>

Since: 0.1.0.0

_DisplayName :: Prism' Text DisplayName Source #

Prism for working with display names.

import Control.Lens ((^?), review)

To convert text into a DisplayName with content validation:

>>> "Some Text" ^? _DisplayName
Just (DisplayName "Some Text")
>>> "Some\nText" ^? _DisplayName
Nothing -- Validation failed.

To access the text content of a DisplayName:

>>> review _DisplayName someDisplayName
"Some Text"

Uses validateDisplayName to perform validation.

Since: 0.1.0.0

validateDisplayName :: Text -> Validation (NonEmpty Error) DisplayName Source #

Validate the content of a DisplayName.

There does not appear to be a limit on the length of the display name. For consistency and efficiency we limit it to 64 bytes, the same as the local part.

Since: 0.1.0.0

Local part

data LocalPart Source #

The name of the mailbox on the associated Domain.

Since: 0.1.0.0

Instances
Eq LocalPart Source # 
Instance details

Defined in Addy.Internal.Types

Show LocalPart Source # 
Instance details

Defined in Addy.Internal.Types

Semigroup LocalPart Source # 
Instance details

Defined in Addy.Internal.Types

_LocalPart :: Prism' Text LocalPart Source #

Prism for working with the local part of an email address.

import Control.Lens ((^?), review)

To convert text to a LocalPart with content validation:

>>> "cockroach+mouse" ^? _LocalPart
Just (LocalPart "cockroach+mouse")
>>> "cockroach\nmouse" ^? _LocalPart
Nothing -- Validation failed.

To access the text content of a LocalPart:

>>> review _LocalPart someLocalPart
"cockamouse"

Uses validateLocalPart to perform validation.

Since: 0.1.0.0

validateLocalPart :: Text -> Validation (NonEmpty Error) LocalPart Source #

Validate and normalize the text content of the LocalPart of an email address.

RFC 3696 §3 restricts the length of the local part to a maximum of 64 bytes. RFC 6532 extends the character set to include Unicode characters but maintains the length measurement as bytes and not characters.

Since: 0.1.0.0

Domain part

data Domain Source #

A fully-qualified domain name or an address literal.

Most email addresses use a domain name. However, it's perfectly legal to use an AddressLiteral instead.

Since: 0.1.0.0

Instances
Eq Domain Source # 
Instance details

Defined in Addy.Internal.Types

Methods

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

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

Show Domain Source # 
Instance details

Defined in Addy.Internal.Types

_Domain :: Prism' Domain DomainName Source #

Prism for working with domain names.

Since: 0.1.0.0

_DomainLiteral :: Prism' Domain AddressLiteral Source #

Prism for working with domain literals.

Since: 0.1.0.0

data DomainName Source #

A fully-qualified domain name which is made up of a list of host names (labels) separated by dots.

Since: 0.1.0.0

_DomainName :: Prism' Text DomainName Source #

Prism for working with domain names.

import Control.Lens ((^?), review)

To convert text to a DomainName with validation:

>>> "gmail.com" ^? _DomainName
Just (DomainName "gmail.com")
>>> "too.many.dots." ^? _DomainName
Nothing

To access the text content of a DomainName:

>>> review _DomainName someDomainName
"gmail.com"

Uses validateDomainName to perform validation.

Since: 0.1.0.0

validateDomainName :: Text -> Validation (NonEmpty Error) DomainName Source #

Validate a domain name.

The domain name is split into host names (labels) and each label is validated with validateHostName.

Since: 0.1.0.0

Host names

data HostName Source #

The name of one host component of a domain name.

Since: 0.1.0.0

Instances
Eq HostName Source # 
Instance details

Defined in Addy.Internal.Types

Show HostName Source # 
Instance details

Defined in Addy.Internal.Types

Semigroup HostName Source # 
Instance details

Defined in Addy.Internal.Types

_HostNames :: Iso' DomainName [HostName] Source #

Iso for converting between domain names and a list of host names.

>>> "gmail.uk.co" ^. _DomainName._HostNames & map (review _HostName)
["gmail","uk","co"]

Since: 0.1.0.0

_HostName :: Prism' Text HostName Source #

Prism for working with host names (DNS labels).

import Control.Lens ((^?), review)

To convert text to a host name with validation:

>>> "com" ^? _HostName
Just (HostName "com")
>>> "com." ^? _HostName
Nothing -- Validation failed.

To access the text content of a HostName:

>>> review _HostName someHostName
"com"

Uses validateHostName to perform validation.

Since: 0.1.0.0

validateHostName :: Text -> Validation (NonEmpty Error) HostName Source #

Validate a single host name. Each host name in a domain name (referred to as a label) must validate with this function.

RFC 2181 §11 clearly states that there are no restrictions placed on which characters may appear in a label. However, due to legacy issues we enforce the rule from RFC 952 §1 that disallows hyphens as the first or last character of a label.

RFC 5322 §3.4.1 restricts the characters that may appear in the domain component of an email address. Even though a DNS label does not impose such restrictions, in order to be a valid email address the label must only be composed of so-called atext characters or UTF8-non-ascii characters.

Finally, RFC 2181 §11 restricts the length of a label to 63 bytes and the fully-qualified domain name to 255 bytes. RFC 6532 which extends the email syntax to allow UTF-8 encoded Unicode characters briefly states in §3.4 to continue using bytes, and not characters. It also states that Unicode text should be normalized (which we do).

Since: 0.1.0.0

Address literals

data AddressLiteral Source #

Address literals can be used instead of a domain name to direct mail to a specific IP address or other tagged address type.

Example email addresses with address literals:

example@[127.0.0.1]
example@[IPv6:1111:2222:3333:4444:5555:6666:7777]
example@[Just-some-text]

Since: 0.1.0.0

Constructors

IpAddressLiteral IP

A literal IP address as defined in RFC 5321 §4.1.3. The address can be in many formats so it is presented here in its parsed form.

TaggedAddressLiteral AddressTag Literal

RFC 5321 also defines a general address literal where a standardized tag precedes the address itself. The only information provided about the standardized tag is:

Standardized-tag MUST be specified in a
Standards-Track RFC and registered with IANA
AddressLiteral Literal

RFC 5322 defines a domain-literal as (roughly) a span of characters that are allowed in a domain name. The interpretation of those characters is left to "separate documents" such as RFC 5321.

If an address literal cannot be parsed in one of the proceeding formats it is encoded as a Literal value.

_IpAddressLiteral :: Prism' AddressLiteral IP Source #

Prism for working with IP address literals.

Since: 0.1.0.0

_TaggedAddressLiteral :: Prism' AddressLiteral (AddressTag, Literal) Source #

Prism for working with tagged address literals.

Since: 0.1.0.0

_AddressLiteral :: Prism' AddressLiteral Literal Source #

Prism for working with address literals.

Since: 0.1.0.0

data AddressTag Source #

A tag that can be used with a TaggedAddressLiteral.

Since: 0.1.0.0

_AddressTag :: Prism' Text AddressTag Source #

Prism for working with the AddressTag for an AddressLiteral.

import Control.Lens ((^?), review)

To convert text to an address tag with validation:

>>> "IPv6" ^? _AddressTag
Just (AddressTag "IPv6")
>>> "[IPv6]" ^? _AddressTag
Nothing -- Validation failed.

To access the text content of an AddressTag:

>>> review _AddressTag someTag
"tag"

Uses validateAddressTag to perform validation.

Since: 0.1.0.0

validateAddressTag :: Text -> Validation (NonEmpty Error) AddressTag Source #

Validate the content of an AddressTag. Uses the same rules as validateLiteral.

Since: 0.1.0.0

data Literal Source #

A literal address that can be used with a TaggedAddressLiteral or AddressLiteral.

Since: 0.1.0.0

Instances
Eq Literal Source # 
Instance details

Defined in Addy.Internal.Types

Methods

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

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

Show Literal Source # 
Instance details

Defined in Addy.Internal.Types

Semigroup Literal Source # 
Instance details

Defined in Addy.Internal.Types

_Literal :: Prism' Text Literal Source #

Prism for working with the literal text of an address literal.

import Control.Lens ((^?), review)

To convert text to an address literal with validation:

>>> "127.0.0.1" ^? _Literal
Just (Literal "127.0.0.1")
>>> "[]" ^? _Literal
Nothing -- Validation failed.

To access the text content of a Literal:

>>> review _Literal someLiteral
"127.0.0.1"

Uses validateLiteral to perform validation.

Since: 0.1.0.0

validateLiteral :: Text -> Validation (NonEmpty Error) Literal Source #

Validate the Literal content of a domain literal.

There does not appear to be a limit on the length of an address literal but for consistency with DNS labels we limit them to 63 bytes.

Since: 0.1.0.0

Comments

data Comment Source #

A comment which may appear in an email address in a specific location.

Since: 0.1.0.0

Instances
Eq Comment Source # 
Instance details

Defined in Addy.Internal.Types

Methods

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

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

Show Comment Source # 
Instance details

Defined in Addy.Internal.Types

_Comment :: Prism' Comment (CommentLoc, CommentContent) Source #

Prism for working with a Comment.

Since: 0.1.0.0

commentLoc :: Lens' Comment CommentLoc Source #

Lens for working with comment locations.

Since: 0.1.0.0

commentContent :: Lens' Comment CommentContent Source #

Lens for working with comment contents.

Since: 0.1.0.0

data CommentLoc Source #

The location where a comment was parsed or where it should be rendered.

Since: 0.1.0.0

Constructors

BeforeDisplayName

Just before the DisplayName.

AfterDisplayName

Just after the DisplayName but before the address.

BeforeLocalPart

Before the LocalPart of the address.

AfterDomain

After the Domain.

AfterAddress

After the complete address.

Instances
Eq CommentLoc Source # 
Instance details

Defined in Addy.Internal.Types

Show CommentLoc Source # 
Instance details

Defined in Addy.Internal.Types

_CommentContent :: Prism' Text CommentContent Source #

Prism for working with the text content of a comment.

import Control.Lens ((^?), review)

To convert text to a comment with validation:

>>> "best email ever" ^? _CommentContent
Just (CommentContent "best email ever")
>>> "\n" ^? _CommentContent
Nothing

To access the text content of the comment:

>>> review _CommentContent someComment
"super"

Uses validateCommentContent to perform validation.

Since: 0.1.0.0

validateCommentContent :: Text -> Validation (NonEmpty Error) CommentContent Source #

Validate the content of a comment.

There does not appear to be a limit on the length of a comment. For consistency and efficiency we limit it to 64 bytes, the same as the local part.

Since: 0.1.0.0