
Hello all! This is a simplified example: import Control.Exception testHandle :: Integer -> IO (Maybe Integer) testHandle i = handle (\_ -> return Nothing) (return (Just i)) It gives me an "ambiguous type variable" arising from the use of "handle". Ok, I understand that the type variable is ambiguous. And in fact I can resolve this with either wrapping it in a specialised handler: import Control.Exception handleIO :: (IOException -> IO a) -> IO a -> IO a handleIO ec nc = handle ec nc testHandle :: Integer -> IO (Maybe Integer) testHandle i = handleIO (\_ -> return Nothing) (return (Just i)) or resolving it directly: {-# LANGUAGE ScopedTypeVariables #-} import Control.Exception testHandle :: Integer -> IO (Maybe Integer) testHandle i = handle (\ (_ :: IOException) -> return Nothing) (return (Just i)) However: Why does the ambiguity matter in the first place? The corresponding value is never used (\_ -> return Nothing). And there's another doubt: I got this example from a book (Real World Haskell, chapter 9) where actually the first version is used, without resolving the ambiguity in any way. And it does not show up in the errata list. So there's likely something I'm still missing about this issue?!?! Any hints would be really appreciated! Thanks in advance. Thomas

On 15 June 2010 14:57, Thomas
However: Why does the ambiguity matter in the first place? The corresponding value is never used (\_ -> return Nothing).
Hi Thomas GHC has to resolve all types, even if they are for values that are not used at runtime.
And there's another doubt: I got this example from a book (Real World Haskell, chapter 9) where actually the first version is used, without resolving the ambiguity in any way. And it does not show up in the errata list. So there's likely something I'm still missing about this issue?!?!
The type of handle in Control.Exception has (probably) changed since RWH was written. latest (from ghc-6.10.1 onwards): handle :: Exception e => (e -> IO a) -> IO a -> IO a old (upto ghc-6.8.3, I think, the so called Old.Exception): handle :: (Exception -> IO a) -> IO a -> IO a Best wishes Stephen

On Tuesday 15 June 2010 16:07:38, Stephen Tetley wrote:
On 15 June 2010 14:57, Thomas
wrote: However: Why does the ambiguity matter in the first place? The corresponding value is never used (\_ -> return Nothing).
Hi Thomas
GHC has to resolve all types, even if they are for values that are not used at runtime.
And there's another doubt: I got this example from a book (Real World Haskell, chapter 9) where actually the first version is used, without resolving the ambiguity in any way. And it does not show up in the errata list. So there's likely something I'm still missing about this issue?!?!
The type of handle in Control.Exception has (probably) changed since RWH was written.
Right.
latest (from ghc-6.10.1 onwards): handle :: Exception e => (e -> IO a) -> IO a -> IO a
old (upto ghc-6.8.3, I think, the so called Old.Exception):
Small typo, no dot there, the former Control.Exception still available as Control.OldException
handle :: (Exception -> IO a) -> IO a -> IO a
Best wishes
Stephen
participants (3)
-
Daniel Fischer
-
Stephen Tetley
-
Thomas