emailaddress-0.2.0.0: Wrapper around email-validate library adding instances for common type classes.

Copyright(c) Dennis Gosnell 2016
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Text.EmailAddress

Contents

Description

This module is a wrapper around Text.Email.Validate from email-validate.

This module exports EmailAddress, a newtype wrapper around Text.Email.Validate.EmailAddress. Additional instances are defined for our new EmailAddress, including ToJSON and FromJSON. This is done so that no orphan instances need to be used.

If you would like additional instances to be defined, please send a pull request. Additional instances will be accepted for any typeclass from any package available on stackage.

Synopsis

Data Type

newtype EmailAddress Source #

Type to represent an email address. Newtype wrapper around EmailAddress with additional typeclass instances.

Constructors

EmailAddress 

Instances

Eq EmailAddress Source # 
Data EmailAddress Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EmailAddress -> c EmailAddress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EmailAddress #

toConstr :: EmailAddress -> Constr #

dataTypeOf :: EmailAddress -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EmailAddress) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EmailAddress) #

gmapT :: (forall b. Data b => b -> b) -> EmailAddress -> EmailAddress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EmailAddress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EmailAddress -> r #

gmapQ :: (forall d. Data d => d -> u) -> EmailAddress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EmailAddress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EmailAddress -> m EmailAddress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EmailAddress -> m EmailAddress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EmailAddress -> m EmailAddress #

Ord EmailAddress Source # 
Read EmailAddress Source #
>>> toText $ read "\"[email protected]\""
"[email protected]"
Show EmailAddress Source #
>>> show $ unsafeEmailAddress "foo" "gmail.com"
"\"[email protected]\""
Generic EmailAddress Source # 

Associated Types

type Rep EmailAddress :: * -> * #

ToJSON EmailAddress Source #

Turn EmailAddress into JSON.

>>> toJSON $ unsafeEmailAddress "foo" "gmail.com"
String "[email protected]"
FromJSON EmailAddress Source #

Parse EmailAddress from JSON.

>>> import Data.Aeson (decode)
>>> fmap (fmap toText) (decode "[ \"[email protected] \" ]" :: Maybe [EmailAddress])
Just ["[email protected]"]
>>> decode "[ \"not an email address\" ]" :: Maybe [EmailAddress]
Nothing
ToHttpApiData EmailAddress Source #

This instance assumes EmailAddress is UTF8-encoded. See toText.

>>> toUrlPiece $ unsafeEmailAddress "foo" "gmail.com"
"[email protected]"
FromHttpApiData EmailAddress Source #

This instance assumes EmailAddress is UTF8-encoded. See validateFromText.

>>> import Data.Either (isLeft)
>>> fmap toText $ parseUrlPiece "[email protected]"
Right "[email protected]"
>>> isLeft $ (parseUrlPiece "not an email address" :: Either Text EmailAddress)
True
FromField EmailAddress Source # 
PathPiece EmailAddress Source #

See emailAddressFromText and toText.

>>> fmap toText $ fromPathPiece "[email protected]"
Just "[email protected]"
>>> fmap toText $ fromPathPiece "this is not an email address"
Nothing
>>> toPathPiece $ unsafeEmailAddress "foo" "gmail.com"
"[email protected]"
PersistFieldSql EmailAddress Source #

Treat EmailAddress just like a Text value.

>>> sqlType (Proxy :: Proxy EmailAddress)
SqlString
PersistField EmailAddress Source #

Treat EmailAddress just like a Text value.

>>> import Data.Either (isLeft)
>>> import Database.Persist.Types (PersistValue(PersistBool, PersistText))
>>> toPersistValue $ unsafeEmailAddress "foo" "gmail.com"
PersistText "[email protected]"
>>> fmap toText $ fromPersistValue (PersistText "[email protected]")
Right "[email protected]"
>>> isLeft (fromPersistValue (PersistText "not an email address") :: Either Text EmailAddress)
True
>>> isLeft (fromPersistValue (PersistBool False) :: Either Text EmailAddress)
True
QueryRunnerColumnDefault PGText EmailAddress Source # 
Default Constant EmailAddress (Column PGText) Source # 
type Rep EmailAddress Source # 
type Rep EmailAddress = D1 (MetaData "EmailAddress" "Text.EmailAddress.Internal" "emailaddress-0.2.0.0-BNjAFSfKPfCH8VEYCVQy1G" True) (C1 (MetaCons "EmailAddress" PrefixI True) (S1 (MetaSel (Just Symbol "unEmailAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EmailAddress)))

Create EmailAddress

emailAddress :: ByteString -> Maybe EmailAddress Source #

Wrapper around emailAddress.

Similar to validate, but returns Nothing if the email address fails to parse.

>>> emailAddress "[email protected]"
Just "[email protected]"
>>> emailAddress "not an email address"
Nothing

validate :: ByteString -> Either String EmailAddress Source #

Wrapper around validate.

>>> validate "[email protected]"
Right "[email protected]"
>>> import Data.Either (isLeft)
>>> isLeft $ validate "not an email address"
True

Check validity

isValid :: ByteString -> Bool #

Validates whether a particular string is an email address according to RFC5322.

Convert to Text

toText :: EmailAddress -> Text Source #

Convert an email address to Text.

This assumes the EmailAddress is UTF8-encoded.

>>> let email = unsafeEmailAddress "foo" "gmail.com"
>>> email
"[email protected]"
>>> toText email
"[email protected]"

Convert back to ByteString

toByteString :: EmailAddress -> ByteString Source #

Wrapper around toByteString.

>>> let email = unsafeEmailAddress "foo" "gmail.com"
>>> email
"[email protected]"
>>> toByteString email
"[email protected]"

localPart :: EmailAddress -> ByteString Source #

Wrapper around localPart.

Extracts the local part from an email address.

For example, in the email address [email protected], the local part is foo.

>>> let email = unsafeEmailAddress "foo" "gmail.com"
>>> email
"[email protected]"
>>> localPart email
"foo"

domainPart :: EmailAddress -> ByteString Source #

Wrapper around domainPart.

Extracts the domain part from an email address.

For example, in the email address [email protected], the domain part is gmail.com.

>>> let email = unsafeEmailAddress "foo" "gmail.com"
>>> email
"[email protected]"
>>> domainPart email
"gmail.com"

Helper functions

canonicalizeEmail :: ByteString -> Maybe ByteString #

Checks that an email is valid and returns a version of it where comments and whitespace have been removed.

Unsafe creation

unsafeEmailAddress Source #

Arguments

:: ByteString

Local part

-> ByteString

Domain part

-> EmailAddress 

Wrapper around unsafeEmailAddress.

Unsafely create an EmailAddress from a local part and a domain part. The first argument is the local part, and the second argument is the domain part.

For example, in the email address [email protected], the local part is foo and the domain part is gmail.com.

>>> unsafeEmailAddress "foo" "gmail.com"
"[email protected]"