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

Ben Franksen ben.franksen at online.de
Sun May 28 20:13:41 UTC 2023


No. If MonadFail did not exist in ghc-8.6.5 then I would get a compiler 
error, right? I have compiled and run it with ghc versions back to 
8.2.2. Furthermore, I did try to define the Monad instance manually, 
along with fail and I do get a compiler error in that case, with every 
ghc since 8.2.2:

test2.hs:15:3: error:
     ‘fail’ is not a (visible) method of class ‘Monad’
    |
15 |   fail = RegexFail . Left

The docs for MonadFail say "Since: base-4.9.0.0" which came with ghc-8.0.

Am 28.05.23 um 16:42 schrieb Brandon Allbery:
> 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.
> 
> 
> 

-- 
I would rather have questions that cannot be answered, than answers that
cannot be questioned.  -- Richard Feynman




More information about the Haskell-Cafe mailing list