[Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

Daniel Gorín dgorin at dc.uba.ar
Tue Nov 10 20:42:21 EST 2009


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


More information about the Haskell-Cafe mailing list