base package

Joachim Breitner mail at joachim-breitner.de
Wed Feb 20 16:40:48 CET 2013


Hi,

Am Mittwoch, den 20.02.2013, 14:57 +0100 schrieb Joachim Breitner:
> I’m still stuck at the problem of separating the definition of IO and
> Monad IO from all file related stuff, which is prevented by the "Maybe
> Handle" field in the IOError data type.

re-reading „An Extensible Dynamically-Typed Hierarchy of Exceptions“
helped me to come up with this somewhat neat solution:

The Monad IO instance uses an exception different from IOError:

$ git show HEAD | filterdiff -i \*.cabal -i \*Fail\* -i \*/GHC/IO.hs
--- a/GHC/IO.hs
+++ b/GHC/IO.hs
@@ -46,8 +46,7 @@ import GHC.ST
 import GHC.Exception
 import GHC.Show
 import Data.Maybe
-
-import {-# SOURCE #-} GHC.IO.Exception ( userError )
+import GHC.IO.Fail
 
 -- ---------------------------------------------------------------------------
 -- The IO Monad
@@ -79,7 +78,7 @@ liftIO :: IO a -> State# RealWorld -> STret RealWorld a
 liftIO (IO m) = \s -> case m s of (# s', r #) -> STret s' r
 
 failIO :: String -> IO a
-failIO s = IO (raiseIO# (toException (userError s)))
+failIO s = IO (raiseIO# (toException (IOFail s)))
 
 -- ---------------------------------------------------------------------------
 -- Coercions between IO and ST
--- /dev/null
+++ b/GHC/IO/Fail.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+module GHC.IO.Fail where
+
+import GHC.Base
+import GHC.Exception
+import Data.Typeable
+import GHC.Show
+
+
+-- | This exception is thrown by the 'fail' method of the 'Monad' 'IO' instance.
+--
+--   The Exception instance of IOException will also catch this, converting the
+--   IOFail to a UserError, for compatibility and consistency with the Haskell
+--   report
+data IOFail = IOFail String
+
+instance Typeable IOFail -- deriving does not work without package
+instance Show IOFail     -- name changes to GHC
+instance Exception IOFail
+

After this change, 

    exposed-modules:
        GHC.IO.Fail,
        GHC.IO,
        GHC.IORef,
        GHC.ST,
        GHC.STRef

is possible (and of course ST can be moved away as well).

So far so good, but this breaks user code.  So the solution is to make
sure that to everyone who tries to catch an IOException (which will
likely be part of some base-io-file), an IOFail will look like a IOError
of type UserError:

$ git show HEAD|filterdiff -i \*Exception.hs
--- a/GHC/IO/Exception.hs
+++ b/GHC/IO/Exception.hs
@@ -45,9 +45,10 @@ import GHC.Show
 import GHC.Exception
 import Data.Maybe
 import GHC.IO.Handle.Types
+import GHC.IO.Fail
 import Foreign.C.Types
 
-import Data.Typeable     ( Typeable )
+import Data.Typeable     ( Typeable, cast )
 
 -- ------------------------------------------------------------------------
 -- Exception datatypes and operations
@@ -222,7 +223,11 @@ data IOException
    }
 instance Typeable IOException
 
-instance Exception IOException
+instance Exception IOException where
+    toException = SomeException
+    fromException e = case cast e of
+        Just (IOFail s) -> Just (userError s)
+        Nothing -> cast e
 
 instance Eq IOException where
   (IOError h1 e1 loc1 str1 en1 fn1) == (IOError h2 e2 loc2 str2 en2 fn2) = 


Neat, isn’t it?

Now I can proceed separating some of the Foreign stuff from the IO
stuff.


Greetings,
Joachim
-- 
Joachim "nomeata" Breitner
Debian Developer
  nomeata at debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nomeata at joachim-breitner.de | http://people.debian.org/~nomeata

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20130220/d156da5f/attachment.pgp>


More information about the Glasgow-haskell-users mailing list