Report more errors thanks to tryMaybe and try.

This commit is contained in:
Philippe Pittoli 2024-01-18 08:18:51 +01:00
parent e134f55daa
commit f9923bab55
2 changed files with 38 additions and 23 deletions

View File

@ -1,7 +1,7 @@
-- | `DomainParser` is a simple parser for domain names as described in RFC 1035. -- | `DomainParser` is a simple parser for domain names as described in RFC 1035.
module DomainParser where module DomainParser where
import Prelude (bind, not, pure, ($), (&&), (*>), (<<<), (<>), (>)) import Prelude (bind, not, pure, ($), (&&), (*>), (<<<), (<>), (>), (-))
import Control.Lazy (defer) import Control.Lazy (defer)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
@ -10,18 +10,18 @@ import Data.Array as A
import Data.String as S import Data.String as S
import Data.String.CodeUnits as CU import Data.String.CodeUnits as CU
import Control.Alt ((<|>)) import Control.Alt ((<|>))
import Control.Plus (empty) -- import Control.Plus (empty)
import Parser (Parser(..), Position import Parser (Parser(..)
, success, failError , success, failError
, current_position , current_position
, alphanum, char, letter, many1, parse, string) , alphanum, char, letter, many1, parse, string)
type Size = Int type Size = Int
data DomainError data DomainError
= SubdomainTooLarge Position Size = SubdomainTooLarge Size
| DomainTooLarge Size | DomainTooLarge Size
| InvalidCharacter Position | InvalidCharacter
| EOFExpected | EOFExpected
-- | From RFC 1035: <let-dig> ::= <letter> | <digit> -- | From RFC 1035: <let-dig> ::= <letter> | <digit>
@ -55,28 +55,43 @@ parse_last_char s p = case last_char s of
Left _ -> false Left _ -> false
_ -> true _ -> true
-- | `try` provides a way to accept a faulty parser and -- | `tryMaybe` provides a way to accept a faulty parser and
-- | just rewinds back to previous input state if an error occurs. -- | just rewinds back to previous input state if an error occurs.
try :: forall e a. Parser e a -> Parser e (Maybe a) tryMaybe :: forall e a. Parser e a -> Parser e (Maybe a)
try p = Parser p' tryMaybe p = Parser p'
where p' input = case parse p input of where p' input = case parse p input of
Left _ -> Right { suffix: input, result: Nothing } Left _ -> Right { suffix: input, result: Nothing }
Right { suffix, result } -> Right { suffix, result: Just result } Right { suffix, result } -> Right { suffix, result: Just result }
-- | `try` provides a way to accept a faulty parser and
-- | just rewinds back to previous input state if a non-specific error occurs.
try :: forall e a. Parser e a -> Parser e (Maybe a)
try p = Parser p'
where p' input = case parse p input of
Left { position, error } -> case error of
Nothing -> Right { suffix: input, result: Nothing }
_ -> Left { position, error }
Right { suffix, result } -> Right { suffix, result: Just result }
-- | From RFC 1035: <label> ::= <letter> [ [ <ldh-str> ] <let-dig> ] -- | From RFC 1035: <label> ::= <letter> [ [ <ldh-str> ] <let-dig> ]
label :: forall e. Parser e String label :: Parser DomainError String
label = do label = do
l <- letter pos <- current_position
s <- try ldh_str maybel <- tryMaybe letter
let labelstr = CU.singleton l <> maybe "" (\v -> CU.fromCharArray v) s case maybel of
if (S.length labelstr > label_maxsize) Nothing -> Parser \_ -> failError pos (Just InvalidCharacter)
then empty Just l -> do
else if (S.length labelstr > 1 && not (parse_last_char labelstr let_dig)) s <- tryMaybe ldh_str
then empty -- TODO: error management. lastpos <- current_position
else pure labelstr let labelstr = CU.singleton l <> maybe "" (\v -> CU.fromCharArray v) s
if (S.length labelstr > label_maxsize)
then Parser \_ -> failError pos (Just <<< SubdomainTooLarge $ S.length labelstr)
else if (S.length labelstr > 1 && not (parse_last_char labelstr let_dig))
then Parser \_ -> failError (lastpos - 1) (Just InvalidCharacter)
else pure labelstr
-- | From RFC 1035: <subdomain> ::= <label> | <subdomain> "." <label> -- | From RFC 1035: <subdomain> ::= <label> | <subdomain> "." <label>
subdomain :: forall e. Parser e String subdomain :: Parser DomainError String
subdomain = do subdomain = do
-- First: read a label. This is bare minimum for a subdomain. -- First: read a label. This is bare minimum for a subdomain.
lab <- label lab <- label
@ -100,7 +115,7 @@ eof = Parser \input -> case S.length input.string of
sub_eof :: Parser DomainError String sub_eof :: Parser DomainError String
sub_eof = do sub_eof = do
sub <- subdomain sub <- subdomain
maybe_final_point <- try $ char '.' maybe_final_point <- tryMaybe $ char '.'
_ <- eof -- In case there is still some input, it fails. _ <- eof -- In case there is still some input, it fails.
pos <- current_position pos <- current_position
let parsed_domain = did_we_parsed_the_final_point maybe_final_point sub let parsed_domain = did_we_parsed_the_final_point maybe_final_point sub

View File

@ -52,10 +52,10 @@ id :: forall a. a -> a
id a = a id a = a
showerror :: DomainError -> String showerror :: DomainError -> String
showerror (SubdomainTooLarge position size) = "SubdomainTooLarge (position: " <> show position <> ", size: " <> show size <> ")" showerror (SubdomainTooLarge size) = "SubdomainTooLarge (size: " <> show size <> ")"
showerror (DomainTooLarge size) = "DomainTooLarge (size: " <> show size <> ")" showerror (DomainTooLarge size) = "DomainTooLarge (size: " <> show size <> ")"
showerror (InvalidCharacter position) = "InvalidCharacter (position: " <> show position <> ")" showerror (InvalidCharacter) = "InvalidCharacter"
showerror (EOFExpected) = "EOFExpected" showerror (EOFExpected) = "EOFExpected"
main :: Effect Unit main :: Effect Unit
main = do main = do