Problems with Language.Haskell.Interpreter and errors

Hi, The API of Language.Haskell.Interpreter says, that 'runInterpreter' runInterpreter :: (MonadCatchIO m, Functor m) => InterpreterT m a -> m (Either InterpreterError a) returns 'Left' in case of errors and 'GhcExceptions from the underlying GHC API are caught and rethrown as this'. What kind of errors do a generate here, why are they not caught by runInterpreter and how can I catch them? I assumed to get a 'Left InterpreterError' from the first and an error in MonadCatchIO in the second.
:m +Language.Haskell.Interpreter let estr1 = "let lst [a] = a; lst _ = error \"foo\" in lst []" let estr1 = "let lst [a] = a; in lst []" runInterpreter (setImportsQ [("Prelude", Nothing)] >> eval estr1 ) Right "*** Exception: foo runInterpreter ( eval estr2) Right "*** Exception: <interactive>:1:101-111: Non-exhaustive patterns in function lst
Thanks a lot

On Sep 29, 2009, at 8:56 AM, Martin Hofmann wrote:
Hi,
The API of Language.Haskell.Interpreter says, that 'runInterpreter'
runInterpreter :: (MonadCatchIO m, Functor m) => InterpreterT m a -> m (Either InterpreterError a)
returns 'Left' in case of errors and 'GhcExceptions from the underlying GHC API are caught and rethrown as this'.
What kind of errors do a generate here, why are they not caught by runInterpreter and how can I catch them? I assumed to get a 'Left InterpreterError' from the first and an error in MonadCatchIO in the second.
:m +Language.Haskell.Interpreter let estr1 = "let lst [a] = a; lst _ = error \"foo\" in lst []" let estr1 = "let lst [a] = a; in lst []" runInterpreter (setImportsQ [("Prelude", Nothing)] >> eval estr1 ) Right "*** Exception: foo runInterpreter ( eval estr2) Right "*** Exception: <interactive>:1:101-111: Non-exhaustive patterns in function lst
Thanks a lot
InterpreterErrors are those that prevent your to-be-interpreted code from "compiling/typechecking". In this case, estr1 is interpreted just fine; but the interpreted value is an exception. So I think Ritght... is ok. You ought to be able to add a Control.Monad.CatchIO.catch clause to your interpreter to catch this kind of errors, if you want. I just tried it and failed, though, so this is probably a bug. I'll try to track it down in more detail. Thanks for the report! Daniel

Thanks a lot.
You ought to be able to add a Control.Monad.CatchIO.catch clause to your interpreter to catch this kind of errors, if you want.
I forgot to mention that this didn't work for me either.
Thanks for the report!
You are welcome. If you come up with a work around or a fix, I would appreciate if you let me know. Cheers, Martin

On Sep 30, 2009, at 2:20 AM, Martin Hofmann wrote:
Thanks a lot.
You ought to be able to add a Control.Monad.CatchIO.catch clause to your interpreter to catch this kind of errors, if you want.
I forgot to mention that this didn't work for me either.
Thanks for the report!
You are welcome. If you come up with a work around or a fix, I would appreciate if you let me know.
Cheers,
Martin
Apologies for a very very very late follow-up on this thread (http://thread.gmane.org/gmane.comp.lang.haskell.cafe/64013 ). It turns out that Control.Monad.CatchIO.catch was the right thing to use; you were probably bitten, just like me, by the fact that "eval" builds a thunk and returns it, but does not execute it. The following works fine for me: import Prelude hiding ( catch ) import Language.Haskell.Interpreter import Control.Monad.CatchIO ( catch ) import Control.Exception.Extensible hiding ( catch ) main :: IO () main = print =<< (runInterpreter (code `catch` handler)) where s = "let lst [a] = a in lst []" code = do setImports ["Prelude"] forceM $ eval s handler (PatternMatchFail _) = return "catched!" forceM :: Monad m => m a -> m a forceM a = a >>= (\x -> return $! x) When run, it prints 'Right "catched!"'. Notice that if you change the line 'forceM $ eval s' by an 'eval s', then the offending thunk is reduced by the print statement and the exception is thrown outside the catch. Hope this helps Daniel

Although late, still very much appreciated. Thanks a lot! Cheers, Martin

I still have problems and your code won't typecheck on my machine printing the following error: Test.hs:9:34: No instance for (Control.Monad.CatchIO.MonadCatchIO (InterpreterT IO)) arising from a use of `catch' at Test.hs:9:34-53 Possible fix: add an instance declaration for (Control.Monad.CatchIO.MonadCatchIO (InterpreterT IO)) In the first argument of `runInterpreter', namely `(code `catch` handler)' In the second argument of `(=<<)', namely `(runInterpreter (code `catch` handler))' In the expression: print =<< (runInterpreter (code `catch` handler)) I assume we are using different versions of some packages. Could you please send me the output of your 'ghc-pkg list'. Thanks, Martin

On Nov 11, 2009, at 5:39 AM, Martin Hofmann wrote:
I still have problems and your code won't typecheck on my machine printing the following error:
[...]
I assume we are using different versions of some packages. Could you please send me the output of your 'ghc-pkg list'.
Thanks,
Martin
Sure. Global: Cabal-1.6.0.3, GLUT-2.1.1.2, HTTP-4000.0.6, HUnit-1.2.0.3, OpenGL-2.2.1.1, QuickCheck-1.2.0.0, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4, cgi-3001.1.7.1, containers-0.2.0.1, directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3), (dph-seq-0.3), editline-0.2.1.0, extensible-exceptions-0.1.1.0, fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3, haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.2, network-2.2.1.4, old-locale-1.0.0.1, old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4, time-1.1.4, unix-2.3.2.0, xhtml-3000.2.0.1, zlib-0.5.0.0 User: MonadCatchIO-mtl-0.2.0.0, ghc-mtl-1.0.1.0, ghc-paths-0.1.0.5, hint-0.3.2.0, utf8-string-0.3.5. Hope that helps Daniel

Thanks, using MonadCatchIO-mtl-0.2.0.0 and hint-0.3.2.0 did it.
participants (2)
-
Daniel Gorín
-
Martin Hofmann