summaryrefslogtreecommitdiff
path: root/ghc/GHCi/Leak.hs
diff options
context:
space:
mode:
authorMichael Sloan <mgsloan@gmail.com>2019-03-14 16:12:09 -0700
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-03-17 22:23:19 -0400
commitc01d5af31c8feb634fc3dffc84e6e7ece61ba190 (patch)
treebe3c878fdd2e1249a536f49baaa563e2ff8de8ac /ghc/GHCi/Leak.hs
parentcb61371e3260e07be724a04b72a935133f66b514 (diff)
downloadhaskell-c01d5af31c8feb634fc3dffc84e6e7ece61ba190.tar.gz
Extract out use of UnboxedTuples from GHCi.Leak
See #13101 + #15454 for motivation. This change reduces the number of modules that need to be compiled to object code when loading GHC into GHCi.
Diffstat (limited to 'ghc/GHCi/Leak.hs')
-rw-r--r--ghc/GHCi/Leak.hs8
1 files changed, 3 insertions, 5 deletions
diff --git a/ghc/GHCi/Leak.hs b/ghc/GHCi/Leak.hs
index 8135c3731e..874d9e2cdc 100644
--- a/ghc/GHCi/Leak.hs
+++ b/ghc/GHCi/Leak.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE RecordWildCards, LambdaCase, MagicHash, UnboxedTuples #-}
+{-# LANGUAGE RecordWildCards, LambdaCase #-}
module GHCi.Leak
( LeakIndicators
, getLeakIndicators
@@ -10,9 +10,8 @@ import Data.Bits
import DynFlags ( sTargetPlatform )
import Foreign.Ptr (ptrToIntPtr, intPtrToPtr)
import GHC
-import GHC.Exts (anyToAddr#)
import GHC.Ptr (Ptr (..))
-import GHC.Types (IO (..))
+import GHCi.Util
import HscTypes
import Outputable
import Platform (target32Bit)
@@ -64,8 +63,7 @@ checkLeakIndicators dflags (LeakIndicators leakmods) = do
report :: String -> Maybe a -> IO ()
report _ Nothing = return ()
report msg (Just a) = do
- addr <- IO (\s -> case anyToAddr# a s of
- (# s', addr #) -> (# s', Ptr addr #)) :: IO (Ptr ())
+ addr <- anyToPtr a
putStrLn ("-fghci-leak-check: " ++ msg ++ " is still alive at " ++
show (maskTagBits addr))