{-# OPTIONS_GHC -fno-warn-orphans #-}
module Addy.Internal.Render
( Mode (..),
render,
renderToText,
renderAddrSpec,
renderDisplayName,
renderComments,
)
where
import Addy.Internal.Char
import Addy.Internal.Types
import qualified Data.Text as Text
import qualified Data.Text.Lazy.Builder as TB
import qualified Net.IP as IP
import Text.Show (Show (..), showParen, showString)
import Prelude hiding (show)
data Mode
=
Full
|
Short
render :: Mode -> EmailAddr -> TB.Builder
render = \case
Short ->
renderAddrSpec Short
Full -> \addr@EmailAddr {..} ->
case _displayName of
Nothing ->
renderAddrSpec Full addr
<> renderComments Full AfterAddress _comments
Just name ->
mconcat
[ renderComments Full BeforeDisplayName _comments,
renderDisplayName name <> TB.singleton ' ',
renderComments Full AfterDisplayName _comments,
TB.singleton '<' <> renderAddrSpec Full addr <> TB.singleton '>',
renderComments Full AfterAddress _comments
]
renderAddrSpec :: Mode -> EmailAddr -> TB.Builder
renderAddrSpec mode EmailAddr {..} =
mconcat
[ renderComments mode BeforeLocalPart _comments,
lp _localPart <> TB.singleton '@' <> dn _domain,
renderComments mode AfterDomain _comments
]
where
lp :: LocalPart -> TB.Builder
lp (LP t)
| mustQuoteLocalPart t = wrap '"' '"' t
| otherwise = TB.fromText t
dn :: Domain -> TB.Builder
dn = \case
Domain (DN t) ->
TB.fromText t
DomainLiteral lit ->
wrap '[' ']' $ case lit of
IpAddressLiteral ip ->
if IP.isIPv6 ip
then "IPv6:" <> IP.encode ip
else IP.encode ip
TaggedAddressLiteral (AT tag) (Lit body) ->
tag <> ":" <> body
AddressLiteral (Lit body) ->
body
renderDisplayName :: DisplayName -> TB.Builder
renderDisplayName (DP t)
| Text.all (\c -> atext c || wsp c) t =
TB.fromText t
| otherwise =
wrap '"' '"' t
renderComments :: Mode -> CommentLoc -> [Comment] -> TB.Builder
renderComments Short _ _ = mempty
renderComments Full loc cs =
case go (== loc) cs of
Nothing -> mempty
Just tb -> case loc of
BeforeDisplayName -> TB.singleton ' ' <> tb
AfterDisplayName -> tb <> TB.singleton ' '
BeforeLocalPart -> tb <> TB.singleton ' '
AfterDomain -> TB.singleton ' ' <> tb
AfterAddress -> TB.singleton ' ' <> tb
where
go :: (CommentLoc -> Bool) -> [Comment] -> Maybe TB.Builder
go f cs =
filter (\(Comment loc (CC t)) -> f loc && not (Text.null t)) cs
& map (\(Comment _ (CC t)) -> t)
& Text.intercalate " "
& \t ->
if Text.null t
then Nothing
else Just $ wrap '(' ')' t
renderToText :: Mode -> EmailAddr -> Text
renderToText m =
render m
>>> TB.toLazyText
>>> toStrict
wrap :: Char -> Char -> Text -> TB.Builder
wrap lh rh t =
mconcat
[ TB.singleton lh,
Text.foldl' escape mempty t,
TB.singleton rh
]
where
escape :: TB.Builder -> Char -> TB.Builder
escape tb c
| c == lh || c == rh || c == '\\' =
tb <> TB.singleton '\\' <> TB.singleton c
| otherwise =
tb <> TB.singleton c
mustQuoteLocalPart :: Text -> Bool
mustQuoteLocalPart name =
Text.any
( \c ->
c == '"'
|| c == '\\'
|| c == ')'
|| c == '('
|| c == '@'
|| wsp c
)
name
|| Text.isPrefixOf "." name
|| Text.isSuffixOf "." name
|| Text.isInfixOf ".." name
|| Text.null name
instance Show EmailAddr where
showsPrec d addr =
showParen (d > 10) $
showString "EmailAddr " . showsPrec d (render Full addr)