{-# LANGUAGE RecordWildCards, DeriveGeneric, GeneralizedNewtypeDeriving,
BangPatterns, CPP #-}
module GHCi.ResolvedBCO
( ResolvedBCO(..)
, ResolvedBCOPtr(..)
, isLittleEndian
) where
import Prelude
import GHC.Data.SizedSeq
import GHCi.RemoteTypes
import GHCi.BreakArray
import Data.Array.Unboxed
import Data.Binary
import GHC.Generics
import GHCi.BinaryArray
#include "MachDeps.h"
isLittleEndian :: Bool
#if defined(WORDS_BIGENDIAN)
isLittleEndian = False
#else
isLittleEndian :: Bool
isLittleEndian = Bool
True
#endif
data ResolvedBCO
= ResolvedBCO {
ResolvedBCO -> Bool
resolvedBCOIsLE :: Bool,
ResolvedBCO -> Int
resolvedBCOArity :: {-# UNPACK #-} !Int,
ResolvedBCO -> UArray Int Word16
resolvedBCOInstrs :: UArray Int Word16,
ResolvedBCO -> UArray Int Word64
resolvedBCOBitmap :: UArray Int Word64,
ResolvedBCO -> UArray Int Word64
resolvedBCOLits :: UArray Int Word64,
ResolvedBCO -> SizedSeq ResolvedBCOPtr
resolvedBCOPtrs :: (SizedSeq ResolvedBCOPtr)
}
deriving (forall x. Rep ResolvedBCO x -> ResolvedBCO
forall x. ResolvedBCO -> Rep ResolvedBCO x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResolvedBCO x -> ResolvedBCO
$cfrom :: forall x. ResolvedBCO -> Rep ResolvedBCO x
Generic, Int -> ResolvedBCO -> ShowS
[ResolvedBCO] -> ShowS
ResolvedBCO -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolvedBCO] -> ShowS
$cshowList :: [ResolvedBCO] -> ShowS
show :: ResolvedBCO -> String
$cshow :: ResolvedBCO -> String
showsPrec :: Int -> ResolvedBCO -> ShowS
$cshowsPrec :: Int -> ResolvedBCO -> ShowS
Show)
instance Binary ResolvedBCO where
put :: ResolvedBCO -> Put
put ResolvedBCO{Bool
Int
UArray Int Word16
UArray Int Word64
SizedSeq ResolvedBCOPtr
resolvedBCOPtrs :: SizedSeq ResolvedBCOPtr
resolvedBCOLits :: UArray Int Word64
resolvedBCOBitmap :: UArray Int Word64
resolvedBCOInstrs :: UArray Int Word16
resolvedBCOArity :: Int
resolvedBCOIsLE :: Bool
resolvedBCOPtrs :: ResolvedBCO -> SizedSeq ResolvedBCOPtr
resolvedBCOLits :: ResolvedBCO -> UArray Int Word64
resolvedBCOBitmap :: ResolvedBCO -> UArray Int Word64
resolvedBCOInstrs :: ResolvedBCO -> UArray Int Word16
resolvedBCOArity :: ResolvedBCO -> Int
resolvedBCOIsLE :: ResolvedBCO -> Bool
..} = do
forall t. Binary t => t -> Put
put Bool
resolvedBCOIsLE
forall t. Binary t => t -> Put
put Int
resolvedBCOArity
forall i a. Binary i => UArray i a -> Put
putArray UArray Int Word16
resolvedBCOInstrs
forall i a. Binary i => UArray i a -> Put
putArray UArray Int Word64
resolvedBCOBitmap
forall i a. Binary i => UArray i a -> Put
putArray UArray Int Word64
resolvedBCOLits
forall t. Binary t => t -> Put
put SizedSeq ResolvedBCOPtr
resolvedBCOPtrs
get :: Get ResolvedBCO
get = Bool
-> Int
-> UArray Int Word16
-> UArray Int Word64
-> UArray Int Word64
-> SizedSeq ResolvedBCOPtr
-> ResolvedBCO
ResolvedBCO
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall i a.
(Binary i, Ix i, MArray IOUArray a IO) =>
Get (UArray i a)
getArray forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall i a.
(Binary i, Ix i, MArray IOUArray a IO) =>
Get (UArray i a)
getArray forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall i a.
(Binary i, Ix i, MArray IOUArray a IO) =>
Get (UArray i a)
getArray forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
data ResolvedBCOPtr
= ResolvedBCORef {-# UNPACK #-} !Int
| ResolvedBCOPtr {-# UNPACK #-} !(RemoteRef HValue)
| ResolvedBCOStaticPtr {-# UNPACK #-} !(RemotePtr ())
| ResolvedBCOPtrBCO ResolvedBCO
| ResolvedBCOPtrBreakArray {-# UNPACK #-} !(RemoteRef BreakArray)
deriving (forall x. Rep ResolvedBCOPtr x -> ResolvedBCOPtr
forall x. ResolvedBCOPtr -> Rep ResolvedBCOPtr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResolvedBCOPtr x -> ResolvedBCOPtr
$cfrom :: forall x. ResolvedBCOPtr -> Rep ResolvedBCOPtr x
Generic, Int -> ResolvedBCOPtr -> ShowS
[ResolvedBCOPtr] -> ShowS
ResolvedBCOPtr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolvedBCOPtr] -> ShowS
$cshowList :: [ResolvedBCOPtr] -> ShowS
show :: ResolvedBCOPtr -> String
$cshow :: ResolvedBCOPtr -> String
showsPrec :: Int -> ResolvedBCOPtr -> ShowS
$cshowsPrec :: Int -> ResolvedBCOPtr -> ShowS
Show)
instance Binary ResolvedBCOPtr