Hi folks,

I'm using Text.Regex.Base with the TDFA and PCRE backends. I want to
compile regular expressions first and make sure the patterns were
actually valid, so I used makeRegexOptsM, which indicates a bad regular
expression by calling fail. That allows you to use makeRegexOptsM with
Maybe or with (Either String) (assuming that Either String is an
instance of Monad, which of course is defined in Control.Monad.Error.)

Doing this with Maybe Regex works like it should--bad pattern gives you
a Nothing. But if you want to see the error message by using Either
String, an exception gets thrown with the bad pattern, rather than
getting a Left String.

Why is this? Seems like an odd bug somewhere. I am a Haskell novice, but
I looked at the code for Text.Regex.Base and for the TDFA and PCRE
backends and there's nothing in there to suggest this kind of
behavior--it should work with Either String.

The attached code snippet demonstrates the problem. I'm on GHC 7.0.3
(though I also got the problem with 6.12.3) and regex-base-0.93.2 and
regex-tdfa-1.1.8 and regex-pcre-0.94.2. Thanks very much for any tips or
ideas. --Omari
module Main where

import Text.Regex.Base.RegexLike
import Text.Regex.TDFA.String
import Control.Monad.Error

badPattern = "[unclosed brace"

main = do
  let maybeRegex =
        makeRegexOptsM defaultCompOpt
        defaultExecOpt badPattern :: Maybe Regex

  -- This outputs "Bad, no regex", as expected
  putStrLn $ maybe "Good regex"
    (const "Bad, no regex") maybeRegex

  let eitherRegex =
        makeRegexOptsM defaultCompOpt
        defaultExecOpt badPattern :: Either String Regex
  
  -- This throws an exception, why? The whole point of
  -- using makeRegexOptsM is to not have exceptions.
  putStrLn $ either show (const "Good regex") eitherRegex
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to