{-# LINE 1 "libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc" #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
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 24 "libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc" #-}
type HalfWord' = Word32
{-# LINE 30 "libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc" #-}
newtype HalfWord = HalfWord HalfWord'
deriving newtype (Int -> HalfWord
HalfWord -> Int
HalfWord -> [HalfWord]
HalfWord -> HalfWord
HalfWord -> HalfWord -> [HalfWord]
HalfWord -> HalfWord -> HalfWord -> [HalfWord]
(HalfWord -> HalfWord)
-> (HalfWord -> HalfWord)
-> (Int -> HalfWord)
-> (HalfWord -> Int)
-> (HalfWord -> [HalfWord])
-> (HalfWord -> HalfWord -> [HalfWord])
-> (HalfWord -> HalfWord -> [HalfWord])
-> (HalfWord -> HalfWord -> HalfWord -> [HalfWord])
-> Enum HalfWord
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: HalfWord -> HalfWord
succ :: HalfWord -> HalfWord
$cpred :: HalfWord -> HalfWord
pred :: HalfWord -> HalfWord
$ctoEnum :: Int -> HalfWord
toEnum :: Int -> HalfWord
$cfromEnum :: HalfWord -> Int
fromEnum :: HalfWord -> Int
$cenumFrom :: HalfWord -> [HalfWord]
enumFrom :: HalfWord -> [HalfWord]
$cenumFromThen :: HalfWord -> HalfWord -> [HalfWord]
enumFromThen :: HalfWord -> HalfWord -> [HalfWord]
$cenumFromTo :: HalfWord -> HalfWord -> [HalfWord]
enumFromTo :: HalfWord -> HalfWord -> [HalfWord]
$cenumFromThenTo :: HalfWord -> HalfWord -> HalfWord -> [HalfWord]
enumFromThenTo :: HalfWord -> HalfWord -> HalfWord -> [HalfWord]
Enum, HalfWord -> HalfWord -> Bool
(HalfWord -> HalfWord -> Bool)
-> (HalfWord -> HalfWord -> Bool) -> Eq HalfWord
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HalfWord -> HalfWord -> Bool
== :: HalfWord -> HalfWord -> Bool
$c/= :: HalfWord -> HalfWord -> Bool
/= :: HalfWord -> HalfWord -> Bool
Eq, Enum HalfWord
Real HalfWord
(Real HalfWord, Enum HalfWord) =>
(HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord -> (HalfWord, HalfWord))
-> (HalfWord -> HalfWord -> (HalfWord, HalfWord))
-> (HalfWord -> Integer)
-> Integral HalfWord
HalfWord -> Integer
HalfWord -> HalfWord -> (HalfWord, HalfWord)
HalfWord -> HalfWord -> HalfWord
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: HalfWord -> HalfWord -> HalfWord
quot :: HalfWord -> HalfWord -> HalfWord
$crem :: HalfWord -> HalfWord -> HalfWord
rem :: HalfWord -> HalfWord -> HalfWord
$cdiv :: HalfWord -> HalfWord -> HalfWord
div :: HalfWord -> HalfWord -> HalfWord
$cmod :: HalfWord -> HalfWord -> HalfWord
mod :: HalfWord -> HalfWord -> HalfWord
$cquotRem :: HalfWord -> HalfWord -> (HalfWord, HalfWord)
quotRem :: HalfWord -> HalfWord -> (HalfWord, HalfWord)
$cdivMod :: HalfWord -> HalfWord -> (HalfWord, HalfWord)
divMod :: HalfWord -> HalfWord -> (HalfWord, HalfWord)
$ctoInteger :: HalfWord -> Integer
toInteger :: HalfWord -> Integer
Integral, Integer -> HalfWord
HalfWord -> HalfWord
HalfWord -> HalfWord -> HalfWord
(HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord)
-> (HalfWord -> HalfWord)
-> (HalfWord -> HalfWord)
-> (Integer -> HalfWord)
-> Num HalfWord
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: HalfWord -> HalfWord -> HalfWord
+ :: HalfWord -> HalfWord -> HalfWord
$c- :: HalfWord -> HalfWord -> HalfWord
- :: HalfWord -> HalfWord -> HalfWord
$c* :: HalfWord -> HalfWord -> HalfWord
* :: HalfWord -> HalfWord -> HalfWord
$cnegate :: HalfWord -> HalfWord
negate :: HalfWord -> HalfWord
$cabs :: HalfWord -> HalfWord
abs :: HalfWord -> HalfWord
$csignum :: HalfWord -> HalfWord
signum :: HalfWord -> HalfWord
$cfromInteger :: Integer -> HalfWord
fromInteger :: Integer -> HalfWord
Num, Eq HalfWord
Eq HalfWord =>
(HalfWord -> HalfWord -> Ordering)
-> (HalfWord -> HalfWord -> Bool)
-> (HalfWord -> HalfWord -> Bool)
-> (HalfWord -> HalfWord -> Bool)
-> (HalfWord -> HalfWord -> Bool)
-> (HalfWord -> HalfWord -> HalfWord)
-> (HalfWord -> HalfWord -> HalfWord)
-> Ord HalfWord
HalfWord -> HalfWord -> Bool
HalfWord -> HalfWord -> Ordering
HalfWord -> HalfWord -> HalfWord
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 :: HalfWord -> HalfWord -> Ordering
compare :: HalfWord -> HalfWord -> Ordering
$c< :: HalfWord -> HalfWord -> Bool
< :: HalfWord -> HalfWord -> Bool
$c<= :: HalfWord -> HalfWord -> Bool
<= :: HalfWord -> HalfWord -> Bool
$c> :: HalfWord -> HalfWord -> Bool
> :: HalfWord -> HalfWord -> Bool
$c>= :: HalfWord -> HalfWord -> Bool
>= :: HalfWord -> HalfWord -> Bool
$cmax :: HalfWord -> HalfWord -> HalfWord
max :: HalfWord -> HalfWord -> HalfWord
$cmin :: HalfWord -> HalfWord -> HalfWord
min :: HalfWord -> HalfWord -> HalfWord
Ord, Num HalfWord
Ord HalfWord
(Num HalfWord, Ord HalfWord) =>
(HalfWord -> Rational) -> Real HalfWord
HalfWord -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: HalfWord -> Rational
toRational :: HalfWord -> Rational
Real, Int -> HalfWord -> ShowS
[HalfWord] -> ShowS
HalfWord -> String
(Int -> HalfWord -> ShowS)
-> (HalfWord -> String) -> ([HalfWord] -> ShowS) -> Show HalfWord
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HalfWord -> ShowS
showsPrec :: Int -> HalfWord -> ShowS
$cshow :: HalfWord -> String
show :: HalfWord -> String
$cshowList :: [HalfWord] -> ShowS
showList :: [HalfWord] -> ShowS
Show, Ptr HalfWord -> IO HalfWord
Ptr HalfWord -> Int -> IO HalfWord
Ptr HalfWord -> Int -> HalfWord -> IO ()
Ptr HalfWord -> HalfWord -> IO ()
HalfWord -> Int
(HalfWord -> Int)
-> (HalfWord -> Int)
-> (Ptr HalfWord -> Int -> IO HalfWord)
-> (Ptr HalfWord -> Int -> HalfWord -> IO ())
-> (forall b. Ptr b -> Int -> IO HalfWord)
-> (forall b. Ptr b -> Int -> HalfWord -> IO ())
-> (Ptr HalfWord -> IO HalfWord)
-> (Ptr HalfWord -> HalfWord -> IO ())
-> Storable HalfWord
forall b. Ptr b -> Int -> IO HalfWord
forall b. Ptr b -> Int -> HalfWord -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: HalfWord -> Int
sizeOf :: HalfWord -> Int
$calignment :: HalfWord -> Int
alignment :: HalfWord -> Int
$cpeekElemOff :: Ptr HalfWord -> Int -> IO HalfWord
peekElemOff :: Ptr HalfWord -> Int -> IO HalfWord
$cpokeElemOff :: Ptr HalfWord -> Int -> HalfWord -> IO ()
pokeElemOff :: Ptr HalfWord -> Int -> HalfWord -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO HalfWord
peekByteOff :: forall b. Ptr b -> Int -> IO HalfWord
$cpokeByteOff :: forall b. Ptr b -> Int -> HalfWord -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> HalfWord -> IO ()
$cpeek :: Ptr HalfWord -> IO HalfWord
peek :: Ptr HalfWord -> IO HalfWord
$cpoke :: Ptr HalfWord -> HalfWord -> IO ()
poke :: Ptr HalfWord -> HalfWord -> IO ()
Storable)
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 (StgInfoTable -> StgInfoTable -> Bool
(StgInfoTable -> StgInfoTable -> Bool)
-> (StgInfoTable -> StgInfoTable -> Bool) -> Eq StgInfoTable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StgInfoTable -> StgInfoTable -> Bool
== :: StgInfoTable -> StgInfoTable -> Bool
$c/= :: StgInfoTable -> StgInfoTable -> Bool
/= :: StgInfoTable -> StgInfoTable -> Bool
Eq, 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)