[Haskell-beginners] Problem with catching error

David McBride dmcbride at neondsl.com
Sun Jul 31 23:59:18 CEST 2011


The problem is it can't be sure that the a in readIOWith is the same
as the a in errHandler based on how it is used because the errHandler
version is ignored entirely in this case.

There are two options:

Remove the type signature of errHandler, and the compiler will infer
it for you.  Unfortunately that won't work in this case because the
exception type is ambiguous, so you need the signature to make things
works.

The second option is add the ScopedTypeVariables extension to your
code, then add a forall a. to the signature of readIOWith.  The code
will look like this:

{-# LANGUAGE ScopedTypeVariables #-}
import Control.Exception as E

readIOWith :: forall a. Read a => a -> String -> IO a
readIOWith d x = E.catch tryRead errHandler
  where errHandler :: SomeException -> IO a
        errHandler _ = return d
        tryRead        = readIO x

What this does is you are telling it that it should assume that all
a's in any part of the function as the same type.  The forall is
normally implied but for some reason this extension requires that you
specify it.  Remember that if your function has several type variables
in it, like a, b, and c, the forall needs to cover them all (forall a
b c.).

On Sun, Jul 31, 2011 at 5:24 PM, Alexey G <kreed131 at gmail.com> wrote:
> Hello. I have some problem with catching error.
> My function try to read value from string and if it's fails - return default
> (d).
> With this:
>>import Control.Exception
>>readIOWith :: Read a => a -> String -> IO a
>>readIOWith d x = catch tryRead errHandler
>>    where errHandler :: SomeException -> IO a
>>              errHandler _ = return d
>>              tryRead        = readIO x
> I have error:
>
> Could not deduce (a ~ a1)
>     from the context (Read a)
>       bound by the type signature for
>                  readIOWith :: Read a => a -> String -> IO a
>       at BWClub/Common/Helpers/Packets.hs:(19,1)-(22,33)
>       `a' is a rigid type variable bound by
>           the type signature for readIOWith :: Read a => a -> String -> IO a
>           at BWClub/Common/Helpers/Packets.hs:19:1
>       `a1' is a rigid type variable bound by
>            the type signature for errHandler :: SomeException -> IO a1
>            at BWClub/Common/Helpers/Packets.hs:21:11
>     In the first argument of `return', namely `d'
>     In the expression: return d
>     In an equation for `errHandler': errHandler _ = return d
>
> But this code works:
>>readIOWith d x = catch tryRead (\e -> print (e :: SomeException) >> return
>> d)
>>    where tryRead      = readIO x
> Sorry for my english.
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>



More information about the Beginners mailing list