regex problem with ghc-8.6 and older

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

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
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@gmail.com

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@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
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@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.

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
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

The `fail` method was part of the `Monad` type class from GHC 8.0 (`base` `4.9.0.0`) until GHC 8.6 (`base` `4.12.0.0`). https://hackage.haskell.org/package/base-4.12.0.0/docs/Control-Monad.html#v:... It was removed from GHC 8.8 (`base` `4.13.0.0`). https://hackage.haskell.org/package/base-4.13.0.0/docs/Control-Monad.html#t:... There is information about this in the MonadFail Proposal (MFP): https://gitlab.haskell.org/haskell/prime/-/wikis/libraries/proposals/monad-f... Cheers, Travis

Thanks, this is helpful. It should have made me suspicious that I had to hide the fail from Prelude. What happens here is that for ghc-8.6 and earlier the fail that is called by regex-tdfa is not the one from class MonadFail but the one from class Monad, even though the MonadFail class exists. And apparently newtype deriving will create an instance that calls error (either because the instance Monad for Either String does or because of a default definition). So for ghc-8.6 and older I will have to write a bogus instance MonadFail (since makeRegexM requires it) and have to write out the Monad instance manually. Cheers Ben Am 28.05.23 um 22:53 schrieb Travis Cardwell via Haskell-Cafe:
The `fail` method was part of the `Monad` type class from GHC 8.0 (`base` `4.9.0.0`) until GHC 8.6 (`base` `4.12.0.0`).
https://hackage.haskell.org/package/base-4.12.0.0/docs/Control-Monad.html#v:...
It was removed from GHC 8.8 (`base` `4.13.0.0`).
https://hackage.haskell.org/package/base-4.13.0.0/docs/Control-Monad.html#t:...
There is information about this in the MonadFail Proposal (MFP):
https://gitlab.haskell.org/haskell/prime/-/wikis/libraries/proposals/monad-f...
Cheers,
Travis _______________________________________________ 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
participants (4)
-
Ben Franksen
-
Brandon Allbery
-
Melanie Brown
-
Travis Cardwell