EmailAddress: WIP.
This commit is contained in:
parent
140c7e128c
commit
29eddd715b
@ -2,7 +2,7 @@
|
|||||||
-- | This module is experimental and doesn't follow every rule for an email address, yet.
|
-- | This module is experimental and doesn't follow every rule for an email address, yet.
|
||||||
module GenericParser.EmailAddress where
|
module GenericParser.EmailAddress where
|
||||||
|
|
||||||
import Prelude (Unit, unit, bind, pure, ($), (<>), (==), (||), between, void)
|
import Prelude (Unit, bind, pure, ($), (<>), (==), (||), between, void)
|
||||||
|
|
||||||
import Control.Alt ((<|>))
|
import Control.Alt ((<|>))
|
||||||
import Data.Array as A
|
import Data.Array as A
|
||||||
@ -24,33 +24,31 @@ data EmailError
|
|||||||
= InvalidCharacter
|
= InvalidCharacter
|
||||||
| InvalidDomain (Maybe DomainError)
|
| InvalidDomain (Maybe DomainError)
|
||||||
|
|
||||||
-- | obs-FWS = 1*WSP *(CRLF 1*WSP)
|
-- | obs-FWS: obsolete folding white space.
|
||||||
-- |
|
-- |
|
||||||
-- | Obsolete FWS.
|
-- | obs-FWS = 1*WSP *(CRLF 1*WSP)
|
||||||
obs_fws :: forall e. Parser e Unit
|
obs_fws :: forall e. Parser e Unit
|
||||||
obs_fws = do _ <- A.many wsp
|
obs_fws = do _ <- A.many wsp
|
||||||
_ <- A.many $ do _ <- crlf
|
void $ A.many $ do _ <- crlf
|
||||||
_ <- many1 wsp
|
void $ many1 wsp
|
||||||
pure unit
|
|
||||||
pure unit
|
|
||||||
|
|
||||||
-- FWS = ([*WSP CRLF] 1*WSP) / obs-FWS
|
-- | FWS: folding white space. This can be described in plain english as:
|
||||||
-- ; Folding white space
|
-- | 1. an OPTIONAL line with potential white spaces followed by at least one white space
|
||||||
-- In english: FWS is described as:
|
-- | 2. or, by the obs-FWS rule (meaning: many empty lines)
|
||||||
-- 1. an OPTIONAL line with potential white spaces followed by at least one white space
|
-- |
|
||||||
-- 2. or, by the obs-FWS rule (meaning: many empty lines)
|
-- | FWS = ([*WSP CRLF] 1*WSP) / obs-FWS
|
||||||
fws :: forall e. Parser e Unit
|
fws :: forall e. Parser e Unit
|
||||||
fws = do _ <- tryMaybe do _ <- A.many wsp
|
fws = do _ <- tryMaybe do _ <- A.many wsp
|
||||||
_ <- crlf
|
crlf
|
||||||
pure unit
|
void $ many1 wsp
|
||||||
_ <- many1 wsp
|
|
||||||
pure unit
|
|
||||||
<|> obs_fws
|
<|> obs_fws
|
||||||
|
|
||||||
-- ctext = %d33-39 / ; Printable US-ASCII
|
-- | ctext: printable US-ASCII characters.
|
||||||
-- %d42-91 / ; characters not including
|
-- |
|
||||||
-- %d93-126 / ; "(", ")", or "\"
|
-- | ctext = %d33-39 / ; Printable US-ASCII
|
||||||
-- obs-ctext
|
-- | %d42-91 / ; characters not including
|
||||||
|
-- | %d93-126 / ; "(", ")", or "\"
|
||||||
|
-- | obs-ctext
|
||||||
ctext :: forall e. Parser e Char
|
ctext :: forall e. Parser e Char
|
||||||
ctext = sat cond <|> obs_ctext
|
ctext = sat cond <|> obs_ctext
|
||||||
where cond x = let charcode = C.toCharCode x
|
where cond x = let charcode = C.toCharCode x
|
||||||
@ -58,30 +56,28 @@ ctext = sat cond <|> obs_ctext
|
|||||||
|| between 42 91 charcode
|
|| between 42 91 charcode
|
||||||
|| between 93 126 charcode
|
|| between 93 126 charcode
|
||||||
|
|
||||||
-- | TODO
|
-- | TODO: `quoted_pair`
|
||||||
quoted_pair :: forall e. Parser e Char
|
quoted_pair :: forall e. Parser e Char
|
||||||
quoted_pair = char ' '
|
quoted_pair = char ' '
|
||||||
|
|
||||||
-- | ccontent = ctext / quoted-pair / comment
|
-- | ccontent = ctext / quoted-pair / comment
|
||||||
-- |
|
-- |
|
||||||
-- | Comment content. TODO
|
-- | Comment content.
|
||||||
ccontent :: forall e. Parser e Unit
|
ccontent :: forall e. Parser e Unit
|
||||||
ccontent = many_ctext <|> a_quoted_pair <|> comment
|
ccontent = a_ctext <|> a_quoted_pair <|> comment
|
||||||
where many_ctext :: Parser e Unit
|
where a_ctext :: Parser e Unit
|
||||||
many_ctext = do void $ A.many ctext
|
a_ctext = void ctext
|
||||||
a_quoted_pair :: Parser e Unit
|
a_quoted_pair :: Parser e Unit
|
||||||
a_quoted_pair = do void quoted_pair
|
a_quoted_pair = void quoted_pair
|
||||||
|
|
||||||
-- | comment = "(" *([FWS] ccontent) [FWS] ")"
|
-- | Comment. Nothing to return since comments aren't to be processed.
|
||||||
-- |
|
-- |
|
||||||
-- | Comment. Nothing to return.
|
-- | comment = "(" *([FWS] ccontent) [FWS] ")"
|
||||||
comment :: forall e. Parser e Unit
|
comment :: forall e. Parser e Unit
|
||||||
comment = do _ <- char '('
|
comment = do _ <- char '('
|
||||||
_ <- A.many (do _ <- A.many fws
|
_ <- A.many (do _ <- A.many fws
|
||||||
_ <- ccontent
|
void ccontent)
|
||||||
pure unit)
|
void $ char ')'
|
||||||
_ <- char ')'
|
|
||||||
pure unit
|
|
||||||
|
|
||||||
-- CFWS = (1*([FWS] comment) [FWS]) / FWS
|
-- CFWS = (1*([FWS] comment) [FWS]) / FWS
|
||||||
--cfws :: forall e. Parser e String
|
--cfws :: forall e. Parser e String
|
||||||
|
Loading…
Reference in New Issue
Block a user