Let ReadP carry a failure message
Isaac Elliott
isaace71295 at gmail.com
Fri Nov 20 03:12:38 UTC 2020
Looks like `MonadError String` to me.
On Fri, 20 Nov 2020, 1:08 pm Dannyu NDos, <ndospark320 at gmail.com> wrote:
> 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 at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20201120/beac7e83/attachment.html>
More information about the Libraries
mailing list