[Haskell-cafe] regex problem with ghc-8.6 and older

Melanie Brown brown.m at pm.me
Sun May 28 15:22:25 UTC 2023


Things work best when the packages you need, actually have the things you’re testing. ;)

Cheers
Melanie Brown

On Sun, May 28, 2023 at 10:42, Brandon Allbery <[allbery.b at gmail.com](mailto:On Sun, May 28, 2023 at 10:42, Brandon Allbery <<a href=)> wrote:

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


More information about the Haskell-Cafe mailing list