{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
module GHC.Exts.Heap.ClosureTypes
( ClosureType(..)
, closureTypeHeaderSize
) where
import Prelude
#if __GLASGOW_HASKELL__ >= 909
import GHC.Internal.ClosureTypes
#else
import GHC.Generics
data ClosureType
= INVALID_OBJECT
| CONSTR
| CONSTR_1_0
| CONSTR_0_1
| CONSTR_2_0
| CONSTR_1_1
| CONSTR_0_2
| CONSTR_NOCAF
| FUN
| FUN_1_0
| FUN_0_1
| FUN_2_0
| FUN_1_1
| FUN_0_2
| FUN_STATIC
| THUNK
| THUNK_1_0
| THUNK_0_1
| THUNK_2_0
| THUNK_1_1
| THUNK_0_2
| THUNK_STATIC
| THUNK_SELECTOR
| BCO
| AP
| PAP
| AP_STACK
| IND
| IND_STATIC
| RET_BCO
| RET_SMALL
| RET_BIG
| RET_FUN
| UPDATE_FRAME
| CATCH_FRAME
| UNDERFLOW_FRAME
| STOP_FRAME
| BLOCKING_QUEUE
| BLACKHOLE
| MVAR_CLEAN
| MVAR_DIRTY
| TVAR
| ARR_WORDS
| MUT_ARR_PTRS_CLEAN
| MUT_ARR_PTRS_DIRTY
| MUT_ARR_PTRS_FROZEN_DIRTY
| MUT_ARR_PTRS_FROZEN_CLEAN
| MUT_VAR_CLEAN
| MUT_VAR_DIRTY
| WEAK
| PRIM
| MUT_PRIM
| TSO
| STACK
| TREC_CHUNK
| ATOMICALLY_FRAME
| CATCH_RETRY_FRAME
| CATCH_STM_FRAME
| WHITEHOLE
| SMALL_MUT_ARR_PTRS_CLEAN
| SMALL_MUT_ARR_PTRS_DIRTY
| SMALL_MUT_ARR_PTRS_FROZEN_DIRTY
| SMALL_MUT_ARR_PTRS_FROZEN_CLEAN
| COMPACT_NFDATA
| CONTINUATION
| N_CLOSURE_TYPES
deriving (Enum, Eq, Ord, Show, Generic)
#endif
closureTypeHeaderSize :: ClosureType -> Int
ClosureType
closType =
case ClosureType
closType of
ClosureType
ct | ClosureType
THUNK ClosureType -> ClosureType -> Bool
forall a. Ord a => a -> a -> Bool
<= ClosureType
ct Bool -> Bool -> Bool
&& ClosureType
ct ClosureType -> ClosureType -> Bool
forall a. Ord a => a -> a -> Bool
<= ClosureType
THUNK_0_2 -> Int
thunkHeader
ClosureType
ct | ClosureType
ct ClosureType -> ClosureType -> Bool
forall a. Eq a => a -> a -> Bool
== ClosureType
THUNK_SELECTOR -> Int
thunkHeader
ClosureType
ct | ClosureType
ct ClosureType -> ClosureType -> Bool
forall a. Eq a => a -> a -> Bool
== ClosureType
AP -> Int
thunkHeader
ClosureType
ct | ClosureType
ct ClosureType -> ClosureType -> Bool
forall a. Eq a => a -> a -> Bool
== ClosureType
AP_STACK -> Int
thunkHeader
ClosureType
_ -> Int
header
where
header :: Int
header = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
prof
thunkHeader :: Int
thunkHeader = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
prof
#if defined(PROFILING)
prof = 2
#else
prof :: Int
prof = Int
0
#endif