summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSven Tennie <sven.tennie@gmail.com>2022-02-20 13:28:48 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-02-28 19:16:01 -0500
commitfbf005e973b18674494615bea59d42c54779a814 (patch)
treed200f78f18dad3f17e770878b51c9949ad5ae613
parentd734ef8f78203b856dcfaf19eaebfed6ec623850 (diff)
downloadhaskell-fbf005e973b18674494615bea59d42c54779a814.tar.gz
Fix some hlint issues in ghc-heap
This does not fix all hlint issues as the criticised index and length expressions seem to be fine in context.
-rw-r--r--libraries/ghc-heap/GHC/Exts/Heap.hs9
-rw-r--r--libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs2
2 files changed, 4 insertions, 7 deletions
diff --git a/libraries/ghc-heap/GHC/Exts/Heap.hs b/libraries/ghc-heap/GHC/Exts/Heap.hs
index 2906cf6926..a587739813 100644
--- a/libraries/ghc-heap/GHC/Exts/Heap.hs
+++ b/libraries/ghc-heap/GHC/Exts/Heap.hs
@@ -1,13 +1,10 @@
{-# LANGUAGE CPP #-}
-{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UnliftedFFITypes #-}
@@ -157,7 +154,7 @@ getClosureDataFromHeapObject x = do
let infoTablePtr = Ptr infoTableAddr
ptrList = [case indexArray# pointersArray i of
(# ptr #) -> Box ptr
- | I# i <- [0..(I# (sizeofArray# pointersArray)) - 1]
+ | I# i <- [0..I# (sizeofArray# pointersArray) - 1]
]
infoTable <- peekItbl infoTablePtr
@@ -204,7 +201,7 @@ getClosureDataFromHeapRepPrim getConDesc decodeCCS itbl heapRep pts = do
rawHeapWords :: [Word]
rawHeapWords = [W# (indexWordArray# heapRep i) | I# i <- [0.. end] ]
where
- nelems = (I# (sizeofByteArray# heapRep)) `div` wORD_SIZE
+ nelems = I# (sizeofByteArray# heapRep) `div` wORD_SIZE
end = fromIntegral nelems - 1
-- Just the payload of rawHeapWords (no header).
@@ -236,7 +233,7 @@ getClosureDataFromHeapRepPrim getConDesc decodeCCS itbl heapRep pts = do
fail "Expected at least 1 ptr argument to AP"
-- We expect at least the arity, n_args, and fun fields
unless (length payloadWords >= 2) $
- fail $ "Expected at least 2 raw words to AP"
+ fail "Expected at least 2 raw words to AP"
let splitWord = payloadWords !! 0
pure $ APClosure itbl
#if defined(WORDS_BIGENDIAN)
diff --git a/libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs b/libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs
index 5ff030d923..ced6c5ef46 100644
--- a/libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs
+++ b/libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs
@@ -9,7 +9,7 @@ import GHC.Generics
-- | This is a somewhat faithful representation of StgTSOProfInfo. See
-- <https://gitlab.haskell.org/ghc/ghc/blob/master/rts/include/rts/storage/TSO.h>
-- for more details on this data structure.
-data StgTSOProfInfo = StgTSOProfInfo {
+newtype StgTSOProfInfo = StgTSOProfInfo {
cccs :: Maybe CostCentreStack
} deriving (Show, Generic, Eq, Ord)