Let ReadP carry a failure message

Firstly, I propose a new class. This class is like MonadFail, but with "error bind" operator: class Monad m => FailMsg m where failMsg :: String -> m a (>?=) :: m a -> (String -> m a) -> m a Laws are: * For every (x :: m a), if (x ≡ fail msg) for some (msg :: String), msg shall be unique. * For (x ≡ fail msg), (x >?= f ≡ f msg). If such msg doesn't exist, (x >?= _ ≡ x). Basic instances are: instance e ~ String => FailMsg (Either e) where failMsg = Left Left msg >?= f = f msg x >?= _ = x instance FailMsg IO where failMsg = throwIO . userError action >?= f = catch action (f . ioeGetErrorString) Now let's focus on ReadP. Let P carry a failure message: data P a = Get (Char -> P a) | Look (String -> P a) | Fail String | Result a (P a) | Final (NonEmpty (a,String)) Then we have: instance FailMsg P where fail = Fail Fail msg >?= f = f msg p >?= _ = p instance FailMsg ReadP where fail msg = R (\_ -> fail msg) R m >?= f = R (\k -> case m k of Fail msg -> let R n = f msg in n k p -> p ) This is incredibly useful. This can be used when there are multiple types of parse error.

Looks like `MonadError String` to me.
On Fri, 20 Nov 2020, 1:08 pm Dannyu NDos,
Firstly, I propose a new class. This class is like MonadFail, but with "error bind" operator:
class Monad m => FailMsg m where failMsg :: String -> m a (>?=) :: m a -> (String -> m a) -> m a
Laws are:
* For every (x :: m a), if (x ≡ fail msg) for some (msg :: String), msg shall be unique. * For (x ≡ fail msg), (x >?= f ≡ f msg). If such msg doesn't exist, (x >?= _ ≡ x).
Basic instances are:
instance e ~ String => FailMsg (Either e) where failMsg = Left Left msg >?= f = f msg x >?= _ = x
instance FailMsg IO where failMsg = throwIO . userError action >?= f = catch action (f . ioeGetErrorString)
Now let's focus on ReadP. Let P carry a failure message:
data P a = Get (Char -> P a) | Look (String -> P a) | Fail String | Result a (P a) | Final (NonEmpty (a,String))
Then we have:
instance FailMsg P where fail = Fail Fail msg >?= f = f msg p >?= _ = p
instance FailMsg ReadP where fail msg = R (\_ -> fail msg) R m >?= f = R (\k -> case m k of Fail msg -> let R n = f msg in n k p -> p )
This is incredibly useful. This can be used when there are multiple types of parse error. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

ReadP was never designed to produce useful error messages. Have you
experimented with your design? Do the messages it produces help find the
problems?
On Thu, Nov 19, 2020, 10:08 PM Dannyu NDos
Firstly, I propose a new class. This class is like MonadFail, but with "error bind" operator:
class Monad m => FailMsg m where failMsg :: String -> m a (>?=) :: m a -> (String -> m a) -> m a
Laws are:
* For every (x :: m a), if (x ≡ fail msg) for some (msg :: String), msg shall be unique. * For (x ≡ fail msg), (x >?= f ≡ f msg). If such msg doesn't exist, (x >?= _ ≡ x).
Basic instances are:
instance e ~ String => FailMsg (Either e) where failMsg = Left Left msg >?= f = f msg x >?= _ = x
instance FailMsg IO where failMsg = throwIO . userError action >?= f = catch action (f . ioeGetErrorString)
Now let's focus on ReadP. Let P carry a failure message:
data P a = Get (Char -> P a) | Look (String -> P a) | Fail String | Result a (P a) | Final (NonEmpty (a,String))
Then we have:
instance FailMsg P where fail = Fail Fail msg >?= f = f msg p >?= _ = p
instance FailMsg ReadP where fail msg = R (\_ -> fail msg) R m >?= f = R (\k -> case m k of Fail msg -> let R n = f msg in n k p -> p )
This is incredibly useful. This can be used when there are multiple types of parse error. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Well, I once tried implementing a parser that evaluates integer addition, multiplication, exponential, tetration, pentation, and so on infinitely. The operators were + with precedence 6, * with precedence 7, ^ with precedence 8, ^^ with precedence 9 (for tetration), ^^^ with precedence 10 (for pentation), ^^^^ with precedence 11 (for hexation), and so on infinitely. I've not succeeded implementing it using ordinary ReadP.

This seems like bloat to me, should probably be in userspace if it exists
at all.
I never use Read et al in actual code, and I doubt most people do. What are
you using it for?
On Thu, Nov 19, 2020, 21:26 Dannyu NDos
Well, I once tried implementing a parser that evaluates integer addition, multiplication, exponential, tetration, pentation, and so on infinitely. The operators were + with precedence 6, * with precedence 7, ^ with precedence 8, ^^ with precedence 9 (for tetration), ^^^ with precedence 10 (for pentation), ^^^^ with precedence 11 (for hexation), and so on infinitely. I've not succeeded implementing it using ordinary ReadP. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Well, I have many heavy usages of ReadP, and this particular problem is really bugging me.

My main concern is that while you'll get error messages from parse
failures, they may not actually do a good job of pointing to the cause of
the failure. I don't know much about parsing, but I gather that a lot of
people have put a lot of work into designing parsing frameworks with decent
error reporting, and you're not likely to get anything near that by
grafting errors onto a more primitive system.
On Thu, Nov 19, 2020, 10:25 PM Dannyu NDos
Well, I once tried implementing a parser that evaluates integer addition, multiplication, exponential, tetration, pentation, and so on infinitely. The operators were + with precedence 6, * with precedence 7, ^ with precedence 8, ^^ with precedence 9 (for tetration), ^^^ with precedence 10 (for pentation), ^^^^ with precedence 11 (for hexation), and so on infinitely. I've not succeeded implementing it using ordinary ReadP.

Excellently said!
Good parser abstractions include a lot of extra info like source span,
context. And or even what the actual expected vs seen token are. And the
proposed extension doesn’t seem to provide for those.
On Thu, Nov 19, 2020 at 10:27 PM David Feuer
My main concern is that while you'll get error messages from parse failures, they may not actually do a good job of pointing to the cause of the failure. I don't know much about parsing, but I gather that a lot of people have put a lot of work into designing parsing frameworks with decent error reporting, and you're not likely to get anything near that by grafting errors onto a more primitive system.
On Thu, Nov 19, 2020, 10:25 PM Dannyu NDos
wrote: Well, I once tried implementing a parser that evaluates integer addition, multiplication, exponential, tetration, pentation, and so on infinitely. The operators were + with precedence 6, * with precedence 7, ^ with precedence 8, ^^ with precedence 9 (for tetration), ^^^ with precedence 10 (for pentation), ^^^^ with precedence 11 (for hexation), and so on infinitely. I've not succeeded implementing it using ordinary ReadP.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (5)
-
Carter Schonwald
-
chessai
-
Dannyu NDos
-
David Feuer
-
Isaac Elliott