[Haskell-cafe] Control.Exception Funny

2008-11-29 Thread Dominic Steinitz
I'm probably doing something wrong but this example doesn't compile for
me under ghc 6.10.1
(http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html#4):

catch (openFile f ReadMode)
(\e - hPutStr stderr (Couldn't open ++f++:  ++ show e))

 Run.hs:77:24:
 Couldn't match expected type `Handle' against inferred type `()'
   Expected type: IO Handle
   Inferred type: IO ()
 In the expression:
 hPutStr stderr (Couldn't open  ++ d ++ :  ++ show e)
 In the second argument of `CE.catch', namely
 `(\ e - hPutStr stderr (Couldn't open  ++ d ++ :  ++ show e))'

Fair enough because openFile returns a Handle and hPutStr returns () so
they don't match as the compiler says.

 CE.catch :: (CE.Exception e) = IO a - (e - IO a) - IO a

So if I fix the example thus:

 foo d = CE.catch (openFile d ReadMode  return ())
  (\e - hPutStr stderr (Couldn't open ++ d ++:  ++ show 
 e))

I get

 Run.hs:70:8:
 Ambiguous type variable `e' in the constraint:
   `CE.Exception e'
 arising from a use of `CE.catch' at Run.hs:(70,8)-(71,78)
 Probable fix: add a type signature that fixes these type variable(s)

Now I think I never used to get this under 6.8.2 but I don't easily have
a 6.8.2 to try it out on.

Doing what the compiler suggests doesn't work for obvious reasons:

 foo :: CE.Exception e = FilePath - IO ()
 foo d = CE.catch (openFile d ReadMode  return ())
  (\e - hPutStr stderr (Couldn't open ++ d ++:  ++ show 
 e))

 Run.hs:69:0:
 Ambiguous constraint `CE.Exception e'
 At least one of the forall'd type variables mentioned by the 
 constraint
 must be reachable from the type after the '='
 In the type signature for `foo':
   foo :: (CE.Exception e) = FilePath - IO ()

There seems to be a ticket for it
(http://hackage.haskell.org/trac/ghc/ticket/2819) but this doesn't give
a suggested example that compiles.

Dominic.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Control.Exception Funny

2008-11-29 Thread Claus Reinke

CE.catch :: (CE.Exception e) = IO a - (e - IO a) - IO a



foo d = CE.catch (openFile d ReadMode  return ())
 (\e - hPutStr stderr (Couldn't open ++ d ++:  ++ show e))


btw, if your handler cannot return the same type as your action, is this
the right place to catch the exceptions?


Run.hs:70:8:
Ambiguous type variable `e' in the constraint:
  `CE.Exception e'
arising from a use of `CE.catch' at Run.hs:(70,8)-(71,78)
Probable fix: add a type signature that fixes these type variable(s)


Now I think I never used to get this under 6.8.2 but I don't easily have
a 6.8.2 to try it out on.


That would be the new extensible exceptions - instead of a single 
non-extendable exception type (no ambiguities), there's now an

extendable class of exceptions.


Doing what the compiler suggests doesn't work for obvious reasons:


foo :: CE.Exception e = FilePath - IO ()
foo d = CE.catch (openFile d ReadMode  return ())
 (\e - hPutStr stderr (Couldn't open ++ d ++:  ++ show e))



Run.hs:69:0:
Ambiguous constraint `CE.Exception e'
At least one of the forall'd type variables mentioned by the constraint
must be reachable from the type after the '='
In the type signature for `foo':
  foo :: (CE.Exception e) = FilePath - IO ()


The suggestion was to fix the type 'e'. Neither your signature, nor your
exception handler do that. I found the documentation less than helpful
for this recent switch, but if you look at the instances of the Exception
class:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html#1

you'll see 'IOException' listed, so 'show (e::IOException)' might do
what you want.


There seems to be a ticket for it
(http://hackage.haskell.org/trac/ghc/ticket/2819) but this doesn't give
a suggested example that compiles.


I've annotated the ticket. Please check whether the suggested 
explanation would be helpful, and report any other places that

have not been updated to the new exception system.

Claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Control.Exception Funny

2008-11-29 Thread Dominic Steinitz
Claus Reinke wrote:
 btw, if your handler cannot return the same type as your action, is this
 the right place to catch the exceptions?
 

That was an example, the real code looks something like this:

do d - getCurrentDirectory
   t - getCurrentTime
   let u = asn1c. ++ show (utctDay t) ++ . ++ show (utctDayTime t)
   createDirectory u
   setCurrentDirectory u
   CE.catch (do writeASN1AndC (genFile . asn1) (genFile . c) ty val
runCommands [(asn1c ++   ++ asn1cOptions ++   ++ 
 skeletons ++   ++ (genFile . asn1), Failure in asn1c)]
d - getCurrentDirectory
fs - getDirectoryContents d
let cFiles = 
   case os of
  mingw32 - 
 (genFile . c):(name . c):(cFiles' 
 [converter-sample.c] .c.lnk fs)
  _ -
 (genFile . c):(name . c):(cFiles' 
 [genFile . c, name . c, converter-sample . c] .c fs)
putStrLn (show cFiles)
putStrLn (show (map compile cFiles))
runCommands (map compile cFiles)
putStrLn (linker ++   ++ linkerOut genFile ++   ++ 
 (* . objectSuffix))
runCommands [
   (linker ++   ++ linkerOut genFile ++   ++ (* . 
 objectSuffix), Failure linking),
   ((executable genFile) ++   ++ (genFile . per), 
 Failure executing)
   ]
readGen (genFile . per) ty)
(\e - hPutStrLn stderr (Problem with generating / 
 compiling\n ++ show e))
   setCurrentDirectory d

Your suggestion:

 you'll see 'IOException' listed, so 'show (e::IOException)' might do
 what you want.

works perfectly.

Thanks very much, Dominic.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe