[commit: base] master: Remove an import loop (4b0addb)
Ian Lynagh
igloo at earth.li
Sun Jun 2 14:12:26 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/packages/base
On branch : master
https://github.com/ghc/packages-base/commit/4b0addbbd931e85c896ed593500d0f2c5ada8b34
>---------------------------------------------------------------
commit 4b0addbbd931e85c896ed593500d0f2c5ada8b34
Author: Ian Lynagh <ian at well-typed.com>
Date: Sun Jun 2 12:43:34 2013 +0100
Remove an import loop
>---------------------------------------------------------------
GHC/Foreign.hs | 4 ++--
System/Posix/Internals.hs-boot | 9 ---------
2 files changed, 2 insertions(+), 11 deletions(-)
diff --git a/GHC/Foreign.hs b/GHC/Foreign.hs
index 3924d40..ceb7447 100644
--- a/GHC/Foreign.hs
+++ b/GHC/Foreign.hs
@@ -49,12 +49,12 @@ import Control.Monad
import Data.Tuple (fst)
import Data.Maybe
-import {-# SOURCE #-} System.Posix.Internals (puts)
import GHC.Show ( show )
import Foreign.Marshal.Alloc
import Foreign.ForeignPtr
+import GHC.Debug
import GHC.Err (undefined)
import GHC.List
import GHC.Num
@@ -70,7 +70,7 @@ c_DEBUG_DUMP :: Bool
c_DEBUG_DUMP = False
putDebugMsg :: String -> IO ()
-putDebugMsg | c_DEBUG_DUMP = puts
+putDebugMsg | c_DEBUG_DUMP = debugLn
| otherwise = const (return ())
diff --git a/System/Posix/Internals.hs-boot b/System/Posix/Internals.hs-boot
deleted file mode 100644
index 612269b..0000000
--- a/System/Posix/Internals.hs-boot
+++ /dev/null
@@ -1,9 +0,0 @@
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude #-}
-module System.Posix.Internals where
-
-import GHC.IO
-import GHC.Base
-
-puts :: String -> IO ()
-
More information about the ghc-commits
mailing list