[Haskell-beginners] Problem with catching error

Daniel Fischer daniel.is.fischer at googlemail.com
Sun Jul 31 23:59:15 CEST 2011


On Sunday 31 July 2011, 23:24:13, Alexey G 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

There's your problem. The type variable 'a' in the local signature is 
completely unrelated to the type variable 'a' in the top-level signature 
(type variables have an implicit forall in Haskell), so the local signature 
says "errHandler can return `IO anything'", but it can of course only 
return `IO (Type of d)'.

If you remove the signature, it should compile.
(Another possibility is to bring the type variable into scope, that would 
require the ScopedTypeVariables language extension and an explicit forall.)

However, this shouldn't need any IO at all,

import Data.Char -- for isSpace

readWithDefault :: Read a => a -> String -> a
readWithDefault d s =
    case reads s of
      [(result,remaining)]
        | all isSpace remaining -> result
      _ -> d

If you really need the IO return type:

readIOWith d = return . readWithDefault d

> >    
> >              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

Here, there's no signature introducing a fresh type variable.

> 
> Sorry for my english.




More information about the Beginners mailing list