<html><head></head><body>  <div dir="auto">Things work best when the packages you need, actually have the things you’re testing. ;)<caret></caret></div><div><br></div><div class="protonmail_signature_block" id="protonmail_signature_block"><div>Cheers<br>Melanie Brown</div></div> <div class="signature_br" contenteditable="false"><br></div><div class="signature_br" contenteditable="false"><br></div>  <div><br></div><div><br></div>On Sun, May 28, 2023 at 10:42, Brandon Allbery <<a class="" href="mailto:On Sun, May 28, 2023 at 10:42, Brandon Allbery <<a href=">allbery.b@gmail.com</a>> wrote:<blockquote type="cite" class="protonmail_quote">  Isn't this just `MonadFail` not existing in older GHC versions? You<br>need to override `fail` in the `Monad` instance instead of using GND.<br><br>On Sun, May 28, 2023 at 10:36 AM Ben Franksen <ben.franksen@online.de> wrote:<br>><br>> Hi Everyone<br>><br>> I was trying to fix a bug in a large program (darcs) and stumbled over a<br>> problem that I cooked down to the minimal test program below. The issue<br>> here is that with ghc-8.6 and earlier, properly handling an invalid<br>> regular expression (here: the empty string) does not work: somehow<br>> something calls "error". With ghc-8.8 and later it works as expected. In<br>> both cases the latest releases of the regex packages are used.<br>><br>> {-# LANGUAGE GeneralizedNewtypeDeriving #-}<br>> import Prelude hiding (fail)<br>> import Control.Monad.Fail<br>> import Control.Exception<br>> import Text.Regex.Base<br>> import Text.Regex.TDFA<br>><br>> newtype RegexFail a = RegexFail { runRegexFail :: Either String a }<br>>    deriving (Functor, Applicative, Monad)<br>><br>> instance MonadFail RegexFail where<br>>    fail = RegexFail . Left<br>><br>> test :: RegexFail Regex<br>> test = makeRegexM ""<br>><br>> main =<br>>    handle (\(ErrorCall _) -> putStrLn "error call") $<br>>      case runRegexFail test of<br>>        Left _ -> putStrLn "clean error handling"<br>>        Right x -> print (matchM x "" :: Maybe Bool)<br>><br>>  > runghc-8.6 test2.hs                                     √<br>> error call<br>>  > runghc-8.8 test2.hs                                     √<br>> clean error handling<br>><br>> (1) Is this a known problem with ghc < 8.8 / base < 4.13?<br>> (2) Is there a work-around for older ghc versions?<br>><br>> Cheers<br>> Ben<br>> --<br>> I would rather have questions that cannot be answered, than answers that<br>> cannot be questioned.  -- Richard Feynman<br>><br>> _______________________________________________<br>> Haskell-Cafe mailing list<br>> To (un)subscribe, modify options or view archives go to:<br>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe<br>> Only members subscribed via the mailman list are allowed to post.<br><br><br><br>--<br>brandon s allbery kf8nh<br>allbery.b@gmail.com<br>_______________________________________________<br>Haskell-Cafe mailing list<br>To (un)subscribe, modify options or view archives go to:<br>http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe<br>Only members subscribed via the mailman list are allowed to post.</blockquote></body></html>