{-# LINE 1 "libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc" #-}
{-# LANGUAGE DeriveGeneric #-}
module GHC.Exts.Heap.InfoTable.Types
( StgInfoTable(..)
, EntryFunPtr
, HalfWord
, ItblCodes
) where
import Prelude
import GHC.Generics
import GHC.Exts.Heap.ClosureTypes
import Foreign
type ItblCodes = Either [Word8] [Word32]
{-# LINE 21 "libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc" #-}
type HalfWord = Word32
{-# LINE 27 "libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc" #-}
type EntryFunPtr = FunPtr (Ptr () -> IO (Ptr ()))
data StgInfoTable = StgInfoTable {
StgInfoTable -> Maybe EntryFunPtr
entry :: Maybe EntryFunPtr,
StgInfoTable -> HalfWord
ptrs :: HalfWord,
StgInfoTable -> HalfWord
nptrs :: HalfWord,
StgInfoTable -> ClosureType
tipe :: ClosureType,
StgInfoTable -> HalfWord
srtlen :: HalfWord,
StgInfoTable -> Maybe ItblCodes
code :: Maybe ItblCodes
} deriving (Int -> StgInfoTable -> ShowS
[StgInfoTable] -> ShowS
StgInfoTable -> String
(Int -> StgInfoTable -> ShowS)
-> (StgInfoTable -> String)
-> ([StgInfoTable] -> ShowS)
-> Show StgInfoTable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StgInfoTable -> ShowS
showsPrec :: Int -> StgInfoTable -> ShowS
$cshow :: StgInfoTable -> String
show :: StgInfoTable -> String
$cshowList :: [StgInfoTable] -> ShowS
showList :: [StgInfoTable] -> ShowS
Show, (forall x. StgInfoTable -> Rep StgInfoTable x)
-> (forall x. Rep StgInfoTable x -> StgInfoTable)
-> Generic StgInfoTable
forall x. Rep StgInfoTable x -> StgInfoTable
forall x. StgInfoTable -> Rep StgInfoTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StgInfoTable -> Rep StgInfoTable x
from :: forall x. StgInfoTable -> Rep StgInfoTable x
$cto :: forall x. Rep StgInfoTable x -> StgInfoTable
to :: forall x. Rep StgInfoTable x -> StgInfoTable
Generic)