IOError vs. Exception vs. IOException

John Meacham john@repetae.net
Thu, 14 Nov 2002 18:09:37 -0800


Just a thought, but what are the ramifications of taking the other
route, relaxing the haskell 98 spec to allow implementations to expand
the set of valid exceptions? a function can be used to determine whether
it is something not covered by the haskell 98 spec (even if we dont know
anything else about it..) and we can at least rethrow it or 'show' it in
logs or whatever. lots of useful little functions can be written which
are haskell 98 but should be general enough to handle random exceptions,
it would be silly to have to keep 2 versions around... some examples are


ioM :: Monad m => IO a -> IO (m a)
ioM action = catch (fmap return action) (\e -> return (fail (show e)))

which turns possibly excepting actions into an arbitrary monad (such as
maybe, or a list). a version with MonadPlus is also useful.

also something like
logEnterExit :: IO a -> IO a
logEnterExit action = ...

which is a useful function which adds an entry to a log upon the start
and finish of action with the added bonus of recording when the action
failed due to an exception as its exit log entry..


	John

On Thu, Nov 14, 2002 at 12:03:44PM +0000, Ross Paterson wrote:
> On Mon, Nov 04, 2002 at 01:00:39PM -0000, Simon Marlow wrote:
> > Ross Paterson wrote:
> > > Two (mostly) independent proposals:
> > > 
> > > 1) Move bracket and bracket_ from System.IO (or GHC.Exception) to
> > >    haskell98/IO.hs.  These two should now never be used anyway (except
> > >    in all-H98 programs), and this would save users of the new 
> > > libraries
> > >    from having to hide them.
> > > 
> > > 2) Define
> > > 
> > > 	type IOError = IOException	-- was Exception
> > >
> > >    (or vice versa), leave the type of Prelude.ioError as IOError -> IO
> > a,
> > >    but add to Control.Exception
> > > 
> > > 	throwIO :: Exception -> IO a
> > > 
> > > If both are done, the only overlap seen by users of the new libraries
> > > is Prelude.catch vs Control.Exception.catch and System.IO.try vs
> > > Control.Exception.try.  In each case there's a type distinction
> > > reflecting the semantic distinction.
> > 
> > Our feeling over here is that this is an unforced change, so in
> > isolation it probably wouldn't be worthwhile.  It'll break some code,
> > and the awkward squad paper will have to be updated to comply (although
> > we just noticed it is already wrong about the behaviour of
> > Prelude.catch).
> > 
> > However, if there's concensus that folk would prefer the alternate
> > definition of IOError, then we're happy to go along with it.
> 
> There have been three responses, all in favour of change.  What's your
> view now?  I would rather see a confusing interface fixed than force
> the other implementations to change their Preludes to implement it,
> but then I have no investment in the old interface.
> _______________________________________________
> Libraries mailing list
> Libraries@haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
> 

-- 
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john@foo.net
---------------------------------------------------------------------------