module GHC.Cmm.Type
    ( CmmType   
    , b8, b16, b32, b64, b128, b256, b512, f32, f64, bWord, bHalfWord, gcWord
    , cInt
    , cmmBits, cmmFloat
    , typeWidth, setCmmTypeWidth
    , cmmEqType, cmmCompatType
    , isFloatType, isGcPtrType, isBitsType
    , isWordAny, isWord32, isWord64
    , isFloat64, isFloat32
    , Width(..)
    , widthInBits, widthInBytes, widthInLog, widthFromBytes
    , wordWidth, halfWordWidth, cIntWidth
    , halfWordMask
    , narrowU, narrowS
    , rEP_CostCentreStack_mem_alloc
    , rEP_CostCentreStack_scc_count
    , rEP_StgEntCounter_allocs
    , rEP_StgEntCounter_allocd
    , ForeignHint(..)
    , Length
    , vec, vec2, vec4, vec8, vec16
    , vec2f64, vec2b64, vec4f32, vec4b32, vec8b16, vec16b8
    , cmmVec
    , vecLength, vecElemType
    , isVecType
    , DoAlignSanitisation
   )
where
import GHC.Prelude
import GHC.Platform
import GHC.Utils.Outputable
import GHC.Utils.Panic
import Data.Word
import Data.Int
  
  
  
  
  
data CmmType    
  = CmmType CmmCat !Width
  deriving Int -> CmmType -> ShowS
[CmmType] -> ShowS
CmmType -> String
(Int -> CmmType -> ShowS)
-> (CmmType -> String) -> ([CmmType] -> ShowS) -> Show CmmType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CmmType -> ShowS
showsPrec :: Int -> CmmType -> ShowS
$cshow :: CmmType -> String
show :: CmmType -> String
$cshowList :: [CmmType] -> ShowS
showList :: [CmmType] -> ShowS
Show
data CmmCat                
   = GcPtrCat              
   | BitsCat               
   | FloatCat              
   | VecCat Length CmmCat  
   deriving( CmmCat -> CmmCat -> Bool
(CmmCat -> CmmCat -> Bool)
-> (CmmCat -> CmmCat -> Bool) -> Eq CmmCat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CmmCat -> CmmCat -> Bool
== :: CmmCat -> CmmCat -> Bool
$c/= :: CmmCat -> CmmCat -> Bool
/= :: CmmCat -> CmmCat -> Bool
Eq, Int -> CmmCat -> ShowS
[CmmCat] -> ShowS
CmmCat -> String
(Int -> CmmCat -> ShowS)
-> (CmmCat -> String) -> ([CmmCat] -> ShowS) -> Show CmmCat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CmmCat -> ShowS
showsPrec :: Int -> CmmCat -> ShowS
$cshow :: CmmCat -> String
show :: CmmCat -> String
$cshowList :: [CmmCat] -> ShowS
showList :: [CmmCat] -> ShowS
Show )
        
instance Outputable CmmType where
  ppr :: CmmType -> SDoc
ppr (CmmType CmmCat
cat Width
wid) = CmmCat -> SDoc
forall a. Outputable a => a -> SDoc
ppr CmmCat
cat SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Width -> Int
widthInBits Width
wid)
instance Outputable CmmCat where
  ppr :: CmmCat -> SDoc
ppr CmmCat
FloatCat       = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"F"
  ppr CmmCat
GcPtrCat       = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"P"
  ppr CmmCat
BitsCat        = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"I"
  ppr (VecCat Int
n CmmCat
cat) = CmmCat -> SDoc
forall a. Outputable a => a -> SDoc
ppr CmmCat
cat SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"x" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
n SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"V"
cmmEqType :: CmmType -> CmmType -> Bool 
cmmEqType :: CmmType -> CmmType -> Bool
cmmEqType (CmmType CmmCat
c1 Width
w1) (CmmType CmmCat
c2 Width
w2) = CmmCat
c1CmmCat -> CmmCat -> Bool
forall a. Eq a => a -> a -> Bool
==CmmCat
c2 Bool -> Bool -> Bool
&& Width
w1Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
==Width
w2
cmmCompatType :: CmmType -> CmmType -> Bool
cmmCompatType :: CmmType -> CmmType -> Bool
cmmCompatType (CmmType CmmCat
c1 Width
w1) (CmmType CmmCat
c2 Width
w2)
   = CmmCat
c1 CmmCat -> CmmCat -> Bool
`weak_eq` CmmCat
c2 Bool -> Bool -> Bool
&& Width
w1 Width -> Width -> Bool
forall a. Eq a => a -> a -> Bool
== Width
w2
   where
     weak_eq :: CmmCat -> CmmCat -> Bool
     CmmCat
FloatCat    weak_eq :: CmmCat -> CmmCat -> Bool
`weak_eq` CmmCat
FloatCat    = Bool
True
     CmmCat
FloatCat    `weak_eq` CmmCat
_other      = Bool
False
     CmmCat
_other      `weak_eq` CmmCat
FloatCat    = Bool
False
     (VecCat {}) `weak_eq` (VecCat {}) = Bool
True  
     (VecCat {}) `weak_eq` CmmCat
_other      = Bool
False
     CmmCat
_other      `weak_eq` (VecCat {}) = Bool
False
     CmmCat
_word1      `weak_eq` CmmCat
_word2      = Bool
True  
typeWidth :: CmmType -> Width
typeWidth :: CmmType -> Width
typeWidth (CmmType CmmCat
_ Width
w) = Width
w
setCmmTypeWidth :: Width -> CmmType -> CmmType
setCmmTypeWidth :: Width -> CmmType -> CmmType
setCmmTypeWidth Width
w (CmmType CmmCat
c Width
_) = CmmCat -> Width -> CmmType
CmmType CmmCat
c Width
w
cmmBits, cmmFloat :: Width -> CmmType
cmmBits :: Width -> CmmType
cmmBits  = CmmCat -> Width -> CmmType
CmmType CmmCat
BitsCat
cmmFloat :: Width -> CmmType
cmmFloat = CmmCat -> Width -> CmmType
CmmType CmmCat
FloatCat
b8, b16, b32, b64, b128, b256, b512, f32, f64 :: CmmType
b8 :: CmmType
b8     = Width -> CmmType
cmmBits Width
W8
b16 :: CmmType
b16    = Width -> CmmType
cmmBits Width
W16
b32 :: CmmType
b32    = Width -> CmmType
cmmBits Width
W32
b64 :: CmmType
b64    = Width -> CmmType
cmmBits Width
W64
b128 :: CmmType
b128   = Width -> CmmType
cmmBits Width
W128
b256 :: CmmType
b256   = Width -> CmmType
cmmBits Width
W256
b512 :: CmmType
b512   = Width -> CmmType
cmmBits Width
W512
f32 :: CmmType
f32    = Width -> CmmType
cmmFloat Width
W32
f64 :: CmmType
f64    = Width -> CmmType
cmmFloat Width
W64
bWord :: Platform -> CmmType
bWord :: Platform -> CmmType
bWord Platform
platform = Width -> CmmType
cmmBits (Platform -> Width
wordWidth Platform
platform)
bHalfWord :: Platform -> CmmType
bHalfWord :: Platform -> CmmType
bHalfWord Platform
platform = Width -> CmmType
cmmBits (Platform -> Width
halfWordWidth Platform
platform)
gcWord :: Platform -> CmmType
gcWord :: Platform -> CmmType
gcWord Platform
platform = CmmCat -> Width -> CmmType
CmmType CmmCat
GcPtrCat (Platform -> Width
wordWidth Platform
platform)
cInt :: Platform -> CmmType
cInt :: Platform -> CmmType
cInt Platform
platform = Width -> CmmType
cmmBits (Platform -> Width
cIntWidth Platform
platform)
isFloatType, isGcPtrType, isBitsType :: CmmType -> Bool
isFloatType :: CmmType -> Bool
isFloatType (CmmType CmmCat
FloatCat    Width
_) = Bool
True
isFloatType CmmType
_other                  = Bool
False
isGcPtrType :: CmmType -> Bool
isGcPtrType (CmmType CmmCat
GcPtrCat Width
_) = Bool
True
isGcPtrType CmmType
_other               = Bool
False
isBitsType :: CmmType -> Bool
isBitsType (CmmType CmmCat
BitsCat Width
_) = Bool
True
isBitsType CmmType
_                   = Bool
False
isWordAny, isWord32, isWord64,
  isFloat32, isFloat64 :: CmmType -> Bool
isWordAny :: CmmType -> Bool
isWordAny (CmmType CmmCat
BitsCat  Width
_) = Bool
True
isWordAny (CmmType CmmCat
GcPtrCat Width
_) = Bool
True
isWordAny CmmType
_other               = Bool
False
isWord64 :: CmmType -> Bool
isWord64 (CmmType CmmCat
BitsCat  Width
W64) = Bool
True
isWord64 (CmmType CmmCat
GcPtrCat Width
W64) = Bool
True
isWord64 CmmType
_other                 = Bool
False
isWord32 :: CmmType -> Bool
isWord32 (CmmType CmmCat
BitsCat  Width
W32) = Bool
True
isWord32 (CmmType CmmCat
GcPtrCat Width
W32) = Bool
True
isWord32 CmmType
_other                 = Bool
False
isFloat32 :: CmmType -> Bool
isFloat32 (CmmType CmmCat
FloatCat Width
W32) = Bool
True
isFloat32 CmmType
_other                 = Bool
False
isFloat64 :: CmmType -> Bool
isFloat64 (CmmType CmmCat
FloatCat Width
W64) = Bool
True
isFloat64 CmmType
_other                 = Bool
False
data Width
  = W8
  | W16
  | W32
  | W64
  | W128
  | W256
  | W512
  deriving (Width -> Width -> Bool
(Width -> Width -> Bool) -> (Width -> Width -> Bool) -> Eq Width
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Width -> Width -> Bool
== :: Width -> Width -> Bool
$c/= :: Width -> Width -> Bool
/= :: Width -> Width -> Bool
Eq, Eq Width
Eq Width =>
(Width -> Width -> Ordering)
-> (Width -> Width -> Bool)
-> (Width -> Width -> Bool)
-> (Width -> Width -> Bool)
-> (Width -> Width -> Bool)
-> (Width -> Width -> Width)
-> (Width -> Width -> Width)
-> Ord Width
Width -> Width -> Bool
Width -> Width -> Ordering
Width -> Width -> Width
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Width -> Width -> Ordering
compare :: Width -> Width -> Ordering
$c< :: Width -> Width -> Bool
< :: Width -> Width -> Bool
$c<= :: Width -> Width -> Bool
<= :: Width -> Width -> Bool
$c> :: Width -> Width -> Bool
> :: Width -> Width -> Bool
$c>= :: Width -> Width -> Bool
>= :: Width -> Width -> Bool
$cmax :: Width -> Width -> Width
max :: Width -> Width -> Width
$cmin :: Width -> Width -> Width
min :: Width -> Width -> Width
Ord, Int -> Width -> ShowS
[Width] -> ShowS
Width -> String
(Int -> Width -> ShowS)
-> (Width -> String) -> ([Width] -> ShowS) -> Show Width
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Width -> ShowS
showsPrec :: Int -> Width -> ShowS
$cshow :: Width -> String
show :: Width -> String
$cshowList :: [Width] -> ShowS
showList :: [Width] -> ShowS
Show)
instance Outputable Width where
   ppr :: Width -> SDoc
ppr Width
rep = String -> SDoc
forall doc. IsLine doc => String -> doc
text (Width -> String
forall a. Show a => a -> String
show Width
rep)
wordWidth :: Platform -> Width
wordWidth :: Platform -> Width
wordWidth Platform
platform = case Platform -> PlatformWordSize
platformWordSize Platform
platform of
 PlatformWordSize
PW4 -> Width
W32
 PlatformWordSize
PW8 -> Width
W64
halfWordWidth :: Platform -> Width
halfWordWidth :: Platform -> Width
halfWordWidth Platform
platform = case Platform -> PlatformWordSize
platformWordSize Platform
platform of
 PlatformWordSize
PW4 -> Width
W16
 PlatformWordSize
PW8 -> Width
W32
halfWordMask :: Platform -> Integer
halfWordMask :: Platform -> Integer
halfWordMask Platform
platform = case Platform -> PlatformWordSize
platformWordSize Platform
platform of
 PlatformWordSize
PW4 -> Integer
0xFFFF
 PlatformWordSize
PW8 -> Integer
0xFFFFFFFF
cIntWidth :: Platform -> Width
cIntWidth :: Platform -> Width
cIntWidth Platform
platform = case PlatformConstants -> Int
pc_CINT_SIZE (Platform -> PlatformConstants
platformConstants Platform
platform) of
                   Int
4 -> Width
W32
                   Int
8 -> Width
W64
                   Int
s -> String -> Width
forall a. HasCallStack => String -> a
panic (String
"cIntWidth: Unknown cINT_SIZE: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
s)
widthInBits :: Width -> Int
widthInBits :: Width -> Int
widthInBits Width
W8   = Int
8
widthInBits Width
W16  = Int
16
widthInBits Width
W32  = Int
32
widthInBits Width
W64  = Int
64
widthInBits Width
W128 = Int
128
widthInBits Width
W256 = Int
256
widthInBits Width
W512 = Int
512
widthInBytes :: Width -> Int
widthInBytes :: Width -> Int
widthInBytes Width
W8   = Int
1
widthInBytes Width
W16  = Int
2
widthInBytes Width
W32  = Int
4
widthInBytes Width
W64  = Int
8
widthInBytes Width
W128 = Int
16
widthInBytes Width
W256 = Int
32
widthInBytes Width
W512 = Int
64
widthFromBytes :: Int -> Width
widthFromBytes :: Int -> Width
widthFromBytes Int
1  = Width
W8
widthFromBytes Int
2  = Width
W16
widthFromBytes Int
4  = Width
W32
widthFromBytes Int
8  = Width
W64
widthFromBytes Int
16 = Width
W128
widthFromBytes Int
32 = Width
W256
widthFromBytes Int
64 = Width
W512
widthFromBytes Int
n  = String -> SDoc -> Width
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"no width for given number of bytes" (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
n)
widthInLog :: Width -> Int
widthInLog :: Width -> Int
widthInLog Width
W8   = Int
0
widthInLog Width
W16  = Int
1
widthInLog Width
W32  = Int
2
widthInLog Width
W64  = Int
3
widthInLog Width
W128 = Int
4
widthInLog Width
W256 = Int
5
widthInLog Width
W512 = Int
6
narrowU :: Width -> Integer -> Integer
narrowU :: Width -> Integer -> Integer
narrowU Width
W8  Integer
x = Word8 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Word8)
narrowU Width
W16 Integer
x = Word16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Word16)
narrowU Width
W32 Integer
x = Word32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Word32)
narrowU Width
W64 Integer
x = Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Word64)
narrowU Width
_ Integer
_ = String -> Integer
forall a. HasCallStack => String -> a
panic String
"narrowTo"
narrowS :: Width -> Integer -> Integer
narrowS :: Width -> Integer -> Integer
narrowS Width
W8  Integer
x = Int8 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Int8)
narrowS Width
W16 Integer
x = Int16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Int16)
narrowS Width
W32 Integer
x = Int32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Int32)
narrowS Width
W64 Integer
x = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x :: Int64)
narrowS Width
_ Integer
_ = String -> Integer
forall a. HasCallStack => String -> a
panic String
"narrowTo"
type Length = Int
vec :: Length -> CmmType -> CmmType
vec :: Int -> CmmType -> CmmType
vec Int
l (CmmType CmmCat
cat Width
w) = CmmCat -> Width -> CmmType
CmmType (Int -> CmmCat -> CmmCat
VecCat Int
l CmmCat
cat) Width
vecw
  where
    vecw :: Width
    vecw :: Width
vecw = Int -> Width
widthFromBytes (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
*Width -> Int
widthInBytes Width
w)
vec2, vec4, vec8, vec16 :: CmmType -> CmmType
vec2 :: CmmType -> CmmType
vec2  = Int -> CmmType -> CmmType
vec Int
2
vec4 :: CmmType -> CmmType
vec4  = Int -> CmmType -> CmmType
vec Int
4
vec8 :: CmmType -> CmmType
vec8  = Int -> CmmType -> CmmType
vec Int
8
vec16 :: CmmType -> CmmType
vec16 = Int -> CmmType -> CmmType
vec Int
16
vec2f64, vec2b64, vec4f32, vec4b32, vec8b16, vec16b8 :: CmmType
vec2f64 :: CmmType
vec2f64 = Int -> CmmType -> CmmType
vec Int
2 CmmType
f64
vec2b64 :: CmmType
vec2b64 = Int -> CmmType -> CmmType
vec Int
2 CmmType
b64
vec4f32 :: CmmType
vec4f32 = Int -> CmmType -> CmmType
vec Int
4 CmmType
f32
vec4b32 :: CmmType
vec4b32 = Int -> CmmType -> CmmType
vec Int
4 CmmType
b32
vec8b16 :: CmmType
vec8b16 = Int -> CmmType -> CmmType
vec Int
8 CmmType
b16
vec16b8 :: CmmType
vec16b8 = Int -> CmmType -> CmmType
vec Int
16 CmmType
b8
cmmVec :: Int -> CmmType -> CmmType
cmmVec :: Int -> CmmType -> CmmType
cmmVec Int
n (CmmType CmmCat
cat Width
w) =
    CmmCat -> Width -> CmmType
CmmType (Int -> CmmCat -> CmmCat
VecCat Int
n CmmCat
cat) (Int -> Width
widthFromBytes (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*Width -> Int
widthInBytes Width
w))
vecLength :: CmmType -> Length
vecLength :: CmmType -> Int
vecLength (CmmType (VecCat Int
l CmmCat
_) Width
_) = Int
l
vecLength CmmType
_                        = String -> Int
forall a. HasCallStack => String -> a
panic String
"vecLength: not a vector"
vecElemType :: CmmType -> CmmType
vecElemType :: CmmType -> CmmType
vecElemType (CmmType (VecCat Int
l CmmCat
cat) Width
w) = CmmCat -> Width -> CmmType
CmmType CmmCat
cat Width
scalw
  where
    scalw :: Width
    scalw :: Width
scalw = Int -> Width
widthFromBytes (Width -> Int
widthInBytes Width
w Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
l)
vecElemType CmmType
_ = String -> CmmType
forall a. HasCallStack => String -> a
panic String
"vecElemType: not a vector"
isVecType :: CmmType -> Bool
isVecType :: CmmType -> Bool
isVecType (CmmType (VecCat {}) Width
_) = Bool
True
isVecType CmmType
_                       = Bool
False
data ForeignHint
  = NoHint | AddrHint | SignedHint
  deriving( ForeignHint -> ForeignHint -> Bool
(ForeignHint -> ForeignHint -> Bool)
-> (ForeignHint -> ForeignHint -> Bool) -> Eq ForeignHint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ForeignHint -> ForeignHint -> Bool
== :: ForeignHint -> ForeignHint -> Bool
$c/= :: ForeignHint -> ForeignHint -> Bool
/= :: ForeignHint -> ForeignHint -> Bool
Eq )
        
        
instance Outputable ForeignHint where
  ppr :: ForeignHint -> SDoc
ppr ForeignHint
NoHint     = SDoc
forall doc. IsOutput doc => doc
empty
  ppr ForeignHint
SignedHint = SDoc -> SDoc
quotes(String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"signed")
  ppr ForeignHint
AddrHint   = (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"PtrHint")
rEP_CostCentreStack_mem_alloc :: Platform -> CmmType
rEP_CostCentreStack_mem_alloc :: Platform -> CmmType
rEP_CostCentreStack_mem_alloc Platform
platform
    = Width -> CmmType
cmmBits (Int -> Width
widthFromBytes (PlatformConstants -> Int
pc_REP_CostCentreStack_mem_alloc PlatformConstants
pc))
    where pc :: PlatformConstants
pc = Platform -> PlatformConstants
platformConstants Platform
platform
rEP_CostCentreStack_scc_count :: Platform -> CmmType
rEP_CostCentreStack_scc_count :: Platform -> CmmType
rEP_CostCentreStack_scc_count Platform
platform
    = Width -> CmmType
cmmBits (Int -> Width
widthFromBytes (PlatformConstants -> Int
pc_REP_CostCentreStack_scc_count PlatformConstants
pc))
    where pc :: PlatformConstants
pc = Platform -> PlatformConstants
platformConstants Platform
platform
rEP_StgEntCounter_allocs :: Platform -> CmmType
rEP_StgEntCounter_allocs :: Platform -> CmmType
rEP_StgEntCounter_allocs Platform
platform
    = Width -> CmmType
cmmBits (Int -> Width
widthFromBytes (PlatformConstants -> Int
pc_REP_StgEntCounter_allocs PlatformConstants
pc))
    where pc :: PlatformConstants
pc = Platform -> PlatformConstants
platformConstants Platform
platform
rEP_StgEntCounter_allocd :: Platform -> CmmType
rEP_StgEntCounter_allocd :: Platform -> CmmType
rEP_StgEntCounter_allocd Platform
platform
    = Width -> CmmType
cmmBits (Int -> Width
widthFromBytes (PlatformConstants -> Int
pc_REP_StgEntCounter_allocd PlatformConstants
pc))
    where pc :: PlatformConstants
pc = Platform -> PlatformConstants
platformConstants Platform
platform
type DoAlignSanitisation = Bool