[commit: ghc] wip/erikd/heapview: heapview: Rename `tipe` to `cltype` (eb6cf2a)

git at git.haskell.org git at git.haskell.org
Sun Jan 29 09:53:20 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/erikd/heapview
Link       : http://ghc.haskell.org/trac/ghc/changeset/eb6cf2a5f8119976f490a8641182bf24dd5ec837/ghc

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

commit eb6cf2a5f8119976f490a8641182bf24dd5ec837
Author: Erik de Castro Lopo <erikd at mega-nerd.com>
Date:   Sun Jan 29 20:22:06 2017 +1100

    heapview: Rename `tipe` to `cltype`


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

eb6cf2a5f8119976f490a8641182bf24dd5ec837
 libraries/heapview/GHC/HeapView.hs       | 8 ++++----
 libraries/heapview/tests/heapview_all.hs | 8 ++++----
 2 files changed, 8 insertions(+), 8 deletions(-)

diff --git a/libraries/heapview/GHC/HeapView.hs b/libraries/heapview/GHC/HeapView.hs
index b8ceeab..ca16852 100644
--- a/libraries/heapview/GHC/HeapView.hs
+++ b/libraries/heapview/GHC/HeapView.hs
@@ -115,7 +115,7 @@ asBox x = Box (unsafeCoerce# x)
 data StgInfoTable = StgInfoTable {
    ptrs   :: HalfWord,
    nptrs  :: HalfWord,
-   tipe   :: ClosureType,
+   cltype :: ClosureType,
    srtlen :: HalfWord
   }
   deriving (Show)
@@ -142,13 +142,13 @@ instance Storable StgInfoTable where
       $ do
            ptrs'   <- load
            nptrs'  <- load
-           tipe'   <- load
+           cltype' <- load
            srtlen' <- load
            return
               StgInfoTable {
                  ptrs   = ptrs',
                  nptrs  = nptrs',
-                 tipe   = toEnum (fromIntegral (tipe'::HalfWord)),
+                 cltype = toEnum (fromIntegral (cltype'::HalfWord)),
                  srtlen = srtlen'
               }
 
@@ -493,7 +493,7 @@ getClosureData :: a -> IO Closure
 getClosureData x = do
     (iptr, wds, ptrs) <- getClosureRaw x
     itbl <- peek iptr
-    case tipe itbl of
+    case cltype itbl of
         t | t >= CONSTR && t <= CONSTR_NOCAF -> do
             (pkg, modl, name) <- dataConInfoPtrToNames iptr
             if modl == "ByteCodeInstr" && name == "BreakInfo"
diff --git a/libraries/heapview/tests/heapview_all.hs b/libraries/heapview/tests/heapview_all.hs
index 7e4b773..645aa4d 100644
--- a/libraries/heapview/tests/heapview_all.hs
+++ b/libraries/heapview/tests/heapview_all.hs
@@ -26,11 +26,11 @@ main = do
         unless eq $ fail "Doesn't reference list"
 
     getClosureData args >>= \ cl ->
-        unless (tipe (info cl) == CONSTR_0_1) $
+        unless (cltype (info cl) == CONSTR_0_1) $
             fail $ "Not a CONSTR_0_1"
 
     getClosureData x >>= \ cl ->
-        unless (tipe (info cl) == THUNK_2_0) $ do
+        unless (cltype (info cl) == THUNK_2_0) $ do
             fail "Not a THUNK_2_0"
 
 
@@ -40,13 +40,13 @@ main = do
         t = f m' list2
 
     getClosureData f >>= \ cl -> do
-        unless (tipe (info cl) == FUN_1_1) $ do
+        unless (cltype (info cl) == FUN_1_1) $ do
             fail "Not a FUN_1_1"
         unless (dataArgs cl == [42]) $ do
             fail "Wrong data arg"
 
     getClosureData t >>= \ cl -> do
-        unless (tipe (info cl) == THUNK) $ do
+        unless (cltype (info cl) == THUNK) $ do
             fail "Not a THUNK"
         unless (dataArgs cl == [23]) $ do
             fail "Wrong data arg"



More information about the ghc-commits mailing list