[Haskell-cafe] Failing to catch exception

Michael Jones mike at proclivis.com
Thu Oct 8 13:26:09 UTC 2015


I’m having trouble with an exception that won’t catch and looking for suggestions. Basically, a “fail” inside a “catch” inside a unsafeIOToSTM, inside a wx callback, trying to catch SomeException or IOException.

Details:

I’m using Text.Regex.PCRE

and the exception comes from a “fail" in unwrap:

unwrap :: (Show e) => Either e v -> IO v
unwrap x = case x of Left err -> fail ("Text.Regex.PCRE.String died: "++ show err)
                    Right v -> return v

The catch is in this function, catching SomeException:

 filterTableRow _ record fils = do
   s <- showRecord record
   vs <- Control.Exception.catch (
             return $ map (\(fil,col) -> let fil' = if fil == "" then "^" else fil in
                                                    ((splitOn "," s)!!(fromIntegral (col+1))) =~ fil') (elems fils)
             )
             ((\e -> do return $ replicate (length $ elems fils) False) :: SomeException -> IO [Bool])
   return $ foldl (.&.) True vs

filterTableRow is called from an unsafeIOToSTM:

unsafeIOToSTM $ filterTableRow gridData row’ fil

which is called from a wx callback from a button press

Before I added the catch, the application was working for over a year, so there is no general problem, All I added was the catch.

Adding -xc to the ghc runtime shows the error:

*** Exception (reporting due to +RTS -xc): (THUNK_1_0), stack trace: 
 Text.Regex.PCRE.String.matchTest,
 called from Text.Regex.PCRE.String.unwrap,
…
user error (Text.Regex.PCRE.String died: (4,"unmatched parentheses"))


Which indicates the text in unwrap, as if the exception is not caught. I have tried to catch it as IOException, and SomeException.

Any ideas why it is not caught or some way to debug it?


More information about the Haskell-Cafe mailing list