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

Ben Franksen ben.franksen at online.de
Sun May 28 14:35:34 UTC 2023


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



More information about the Haskell-Cafe mailing list