[Haskell-beginners] type ambiguity confusion

Thomas haskell at phirho.com
Tue Jun 15 09:57:50 EDT 2010


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




More information about the Beginners mailing list