Fix bug in parser
This commit is contained in:
		| @@ -1,4 +1,5 @@ | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| {-# LANGUAGE ApplicativeDo #-} | ||||
| module Data.Email.Header where | ||||
|  | ||||
| import qualified Data.Foldable as F | ||||
| @@ -21,28 +22,39 @@ data Header | ||||
|  | ||||
| decode :: ByteString -> Either String Header | ||||
| decode = parseOnly parseHeader | ||||
|   where | ||||
| {-# INLINE decode #-} | ||||
|  | ||||
| parseHeader :: Parser Header | ||||
| parseHeader = parseFrom <|> parseTo | ||||
| {-# INLINE parseHeader #-} | ||||
|  | ||||
| parseFrom :: Parser Header | ||||
| parseFrom = From <$> (string "From:" *> emptySpace *> (bracketEmail <|> email)) | ||||
|  | ||||
| parseTo :: Parser Header | ||||
| parseTo = To <$> (string "To:" *> emptySpace *> emails) | ||||
|     emptySpace = many' space | ||||
|  | ||||
| emptySpace :: Parser () | ||||
| emptySpace = () <$ many' space | ||||
|  | ||||
| emails :: Parser (Vector ByteString) | ||||
| emails = V.fromList <$> (bracketEmail <|> email) `sepBy` char ',' | ||||
|  | ||||
| bracketEmail :: Parser ByteString | ||||
| bracketEmail = do | ||||
|   _ <- manyTill anyChar (char '<') | ||||
|   email | ||||
| {-# INLINE bracketEmail #-} | ||||
|  | ||||
| email :: Parser ByteString | ||||
| email = do | ||||
|   _ <- many' space | ||||
|   name <- BC.pack <$> many' (satisfy (\c -> not (isSpace c) && c /= '@')) | ||||
|   _ <- char '@' | ||||
|       rest <- BC.pack <$> many' (satisfy (\c -> not (isSpace c) && c /= ',' && c /= '>')) | ||||
|   rest <- BC.pack <$> many' (satisfy (\c -> not (isSpace c) && c /= ',' && c /= '>' && c /= '<')) | ||||
|   _ <- many' (notChar ',') | ||||
|   pure (name <> "@" <> rest) | ||||
| {-# INLINE email #-} | ||||
|  | ||||
|  | ||||
| encode :: Header -> ByteString | ||||
|   | ||||
| @@ -31,4 +31,7 @@ tests = testGroup "Data.Email" | ||||
|   [ testCase "Can parse a sample email" $ do | ||||
|       got <- parseToList sample | ||||
|       got @?= [ From "me@example.com", To ["you@example.com"]] | ||||
|   , testCase "Combined mailto" $ do | ||||
|       let got = decode "To: James Doe<james.doe@example.com<mailto:james.doe@example.com>>" | ||||
|       got @?= Right (To ["james.doe@example.com"]) | ||||
|   ] | ||||
|   | ||||
		Reference in New Issue
	
	Block a user