Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/c84ddf85ed52609d5468101d38958503b092c269

>---------------------------------------------------------------

commit c84ddf85ed52609d5468101d38958503b092c269
Author: David Terei <[email protected]>
Date:   Thu May 19 00:57:12 2011 -0700

    SafeHaskell: Update to work with safe base

>---------------------------------------------------------------

 compiler/basicTypes/UniqSupply.lhs |    3 ++-
 compiler/ghc.cabal.in              |    1 +
 compiler/ghci/ByteCodeLink.lhs     |    9 ++++-----
 compiler/ghci/RtClosureInspect.hs  |    4 ++--
 compiler/main/BreakArray.hs        |    2 +-
 compiler/prelude/PrelNames.lhs     |    4 ++--
 compiler/utils/Binary.hs           |    3 ++-
 compiler/utils/Encoding.hs         |    4 ++++
 compiler/utils/FastFunctions.lhs   |    3 ++-
 compiler/utils/FastMutInt.lhs      |    6 +++++-
 compiler/utils/FastString.lhs      |    2 +-
 compiler/utils/GhcIO.hs            |   16 ++++++++++++++++
 12 files changed, 42 insertions(+), 15 deletions(-)

diff --git a/compiler/basicTypes/UniqSupply.lhs 
b/compiler/basicTypes/UniqSupply.lhs
index 493bfbe..4e1de6a 100644
--- a/compiler/basicTypes/UniqSupply.lhs
+++ b/compiler/basicTypes/UniqSupply.lhs
@@ -29,9 +29,10 @@ module UniqSupply (
 import Unique
 import FastTypes
 
+import GhcIO (unsafeDupableInterleaveIO)
+
 import MonadUtils
 import Control.Monad
-import GHC.IO (unsafeDupableInterleaveIO)
 
 \end{code}
 
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 2711c1b..7fffe83 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -435,6 +435,7 @@ Library
         FastTypes
         Fingerprint
         FiniteMap
+        GhcIO
         GraphBase
         GraphColor
         GraphOps
diff --git a/compiler/ghci/ByteCodeLink.lhs b/compiler/ghci/ByteCodeLink.lhs
index b1f7e39..7fdc274 100644
--- a/compiler/ghci/ByteCodeLink.lhs
+++ b/compiler/ghci/ByteCodeLink.lhs
@@ -38,19 +38,18 @@ import Panic
 import Outputable
 
 -- Standard libraries
-import GHC.Word                ( Word(..) )
 
 import Data.Array.Base
-import GHC.Arr         ( STArray(..) )
 
 import Control.Monad   ( zipWithM )
 import Control.Monad.ST ( stToIO )
 
-import GHC.Exts
-import GHC.Arr         ( Array(..) )
+import GHC.Arr.Unsafe   ( Array(..), STArray(..) )
+import GHC.Base                ( writeArray#, RealWorld, Int(..), Word# )  
 import GHC.IOBase      ( IO(..) )
+import GHC.Exts
 import GHC.Ptr         ( Ptr(..), castPtr )
-import GHC.Base                ( writeArray#, RealWorld, Int(..), Word# )  
+import GHC.Word                ( Word(..) )
 
 import Data.Word
 \end{code}
diff --git a/compiler/ghci/RtClosureInspect.hs 
b/compiler/ghci/RtClosureInspect.hs
index b6c97c3..0b4d031 100644
--- a/compiler/ghci/RtClosureInspect.hs
+++ b/compiler/ghci/RtClosureInspect.hs
@@ -53,9 +53,9 @@ import DynFlags
 import Outputable as Ppr
 import FastString
 import Constants        ( wORD_SIZE )
-import GHC.Arr          ( Array(..) )
+import GHC.Arr.Unsafe   ( Array(..) )
 import GHC.Exts
-import GHC.IO ( IO(..) )
+import GhcIO ( IO(..) )
 
 import StaticFlags( opt_PprStyle_Debug )
 import Control.Monad
diff --git a/compiler/main/BreakArray.hs b/compiler/main/BreakArray.hs
index 4d2c07b..29d7d77 100644
--- a/compiler/main/BreakArray.hs
+++ b/compiler/main/BreakArray.hs
@@ -26,7 +26,7 @@ module BreakArray
   ) where
 #ifdef GHCI
 import GHC.Exts
-import GHC.IO ( IO(..) )
+import GhcIO ( IO(..) )
 import Constants
 
 data BreakArray = BA (MutableByteArray# RealWorld)
diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs
index 4fd23ee..0c06336 100644
--- a/compiler/prelude/PrelNames.lhs
+++ b/compiler/prelude/PrelNames.lhs
@@ -314,9 +314,9 @@ gHC_CONC    = mkBaseModule (fsLit "GHC.Conc")
 gHC_IO         = mkBaseModule (fsLit "GHC.IO")
 gHC_IO_Exception = mkBaseModule (fsLit "GHC.IO.Exception")
 gHC_ST         = mkBaseModule (fsLit "GHC.ST")
-gHC_ARR                = mkBaseModule (fsLit "GHC.Arr")
+gHC_ARR                = mkBaseModule (fsLit "GHC.Arr.Imp")
 gHC_STABLE     = mkBaseModule (fsLit "GHC.Stable")
-gHC_PTR                = mkBaseModule (fsLit "GHC.Ptr")
+gHC_PTR                = mkBaseModule (fsLit "GHC.Ptr.Imp")
 gHC_ERR                = mkBaseModule (fsLit "GHC.Err")
 gHC_REAL       = mkBaseModule (fsLit "GHC.Real")
 gHC_FLOAT      = mkBaseModule (fsLit "GHC.Float")
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index 1981dc8..80e9171 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -81,7 +81,8 @@ import System.IO.Error          ( mkIOError, eofErrorType )
 import GHC.Real                 ( Ratio(..) )
 import GHC.Exts
 import GHC.Word                 ( Word8(..) )
-import GHC.IO ( IO(..) )
+
+import GhcIO ( IO(..) )
 
 type BinArray = ForeignPtr Word8
 
diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs
index 84b4e09..4351538 100644
--- a/compiler/utils/Encoding.hs
+++ b/compiler/utils/Encoding.hs
@@ -32,7 +32,11 @@ module Encoding (
 import Foreign
 import Data.Char
 import Numeric
+#if __GLASGOW_HASKELL__ >= 701
+import GHC.Ptr.Unsafe   ( Ptr(..) )
+#else
 import GHC.Ptr          ( Ptr(..) )
+#endif
 import GHC.Base
 
 -- 
-----------------------------------------------------------------------------
diff --git a/compiler/utils/FastFunctions.lhs b/compiler/utils/FastFunctions.lhs
index 5496ed0..0734240 100644
--- a/compiler/utils/FastFunctions.lhs
+++ b/compiler/utils/FastFunctions.lhs
@@ -22,9 +22,10 @@ import System.IO.Unsafe
 
 import GHC.Exts
 import GHC.Word
-import GHC.IO (IO(..), unsafeDupableInterleaveIO)
 import GHC.Base (unsafeChr)
 
+import GhcIO        (IO(..), unsafeDupableInterleaveIO)
+
 -- Just like unsafePerformIO, but we inline it.
 {-# INLINE inlinePerformIO #-}
 inlinePerformIO :: IO a -> a
diff --git a/compiler/utils/FastMutInt.lhs b/compiler/utils/FastMutInt.lhs
index 2618307..8f7de90 100644
--- a/compiler/utils/FastMutInt.lhs
+++ b/compiler/utils/FastMutInt.lhs
@@ -26,7 +26,11 @@ module FastMutInt(
 #endif
 
 import GHC.Base
-import GHC.Ptr
+#if __GLASGOW_HASKELL__ >= 701
+import GHC.Ptr.Unsafe   ( Ptr(..) )
+#else
+import GHC.Ptr          ( Ptr(..) )
+#endif
 
 #else /* ! __GLASGOW_HASKELL__ */
 
diff --git a/compiler/utils/FastString.lhs b/compiler/utils/FastString.lhs
index c6dac8f..55b115c 100644
--- a/compiler/utils/FastString.lhs
+++ b/compiler/utils/FastString.lhs
@@ -106,7 +106,7 @@ import Data.IORef       ( IORef, newIORef, readIORef, 
writeIORef )
 import Data.Maybe       ( isJust )
 import Data.Char        ( ord )
 
-import GHC.IO ( IO(..) )
+import GhcIO ( IO(..) )
 
 import GHC.Ptr          ( Ptr(..) )
 #if defined(__GLASGOW_HASKELL__)
diff --git a/compiler/utils/GhcIO.hs b/compiler/utils/GhcIO.hs
new file mode 100644
index 0000000..9d6734e
--- /dev/null
+++ b/compiler/utils/GhcIO.hs
@@ -0,0 +1,16 @@
+-- | A simple version compatability wrapper around GHC.IO.
+-- This module exports both the safe and Unsafe version of GHC.IO
+-- after that SafeHaskell change over occured.
+module GhcIO (
+#if __GLASGOW_HASKELL__ >= 701
+        module GHC.IO.Unsafe,
+#endif
+        module GHC.IO
+    ) where
+
+#if __GLASGOW_HASKELL__ >= 701
+import GHC.IO.Unsafe
+#endif
+
+import GHC.IO
+



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to