{-# LANGUAGE RecordWildCards, DeriveGeneric, GeneralizedNewtypeDeriving,
BangPatterns, CPP #-}
module GHCi.ResolvedBCO
( ResolvedBCO(..)
, ResolvedBCOPtr(..)
, isLittleEndian
) where
import Prelude
import 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 = True
#else
isLittleEndian :: Bool
isLittleEndian = Bool
False
#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. ResolvedBCO -> Rep ResolvedBCO x)
-> (forall x. Rep ResolvedBCO x -> ResolvedBCO)
-> Generic ResolvedBCO
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
(Int -> ResolvedBCO -> ShowS)
-> (ResolvedBCO -> String)
-> ([ResolvedBCO] -> ShowS)
-> Show ResolvedBCO
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
External instance of the constraint type IArray UArray Word64
External instance of the constraint type Show Word64
External instance of the constraint type IArray UArray Word16
External instance of the constraint type Show Word16
External instance of the constraint type Ix Int
Instance of class: Show of the constraint type Show ResolvedBCOPtr
External instance of the constraint type forall a. Show a => Show (SizedSeq a)
External instance of the constraint type IArray UArray Word64
External instance of the constraint type Show Word64
External instance of the constraint type forall ix e.
(Ix ix, Show ix, Show e, IArray UArray e) =>
Show (UArray ix e)
External instance of the constraint type Ix Int
External instance of the constraint type Show Int
External instance of the constraint type Show Word64
External instance of the constraint type IArray UArray Word64
External instance of the constraint type IArray UArray Word16
External instance of the constraint type Show Word16
External instance of the constraint type Ix Int
External instance of the constraint type forall ix e.
(Ix ix, Show ix, Show e, IArray UArray e) =>
Show (UArray ix e)
External instance of the constraint type Show Int
External instance of the constraint type Show Int
External instance of the constraint type Show Bool
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show ResolvedBCOPtr
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
Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
resolvedBCOIsLE
Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
resolvedBCOArity
UArray Int Word16 -> Put
forall i a. Binary i => UArray i a -> Put
External instance of the constraint type Binary Int
putArray UArray Int Word16
resolvedBCOInstrs
UArray Int Word64 -> Put
forall i a. Binary i => UArray i a -> Put
External instance of the constraint type Binary Int
putArray UArray Int Word64
resolvedBCOBitmap
UArray Int Word64 -> Put
forall i a. Binary i => UArray i a -> Put
External instance of the constraint type Binary Int
putArray UArray Int Word64
resolvedBCOLits
SizedSeq ResolvedBCOPtr -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary (SizedSeq a)
Instance of class: Binary of the constraint type Binary ResolvedBCOPtr
put SizedSeq ResolvedBCOPtr
resolvedBCOPtrs
get :: Get ResolvedBCO
get = Bool
-> Int
-> UArray Int Word16
-> UArray Int Word64
-> UArray Int Word64
-> SizedSeq ResolvedBCOPtr
-> ResolvedBCO
ResolvedBCO
(Bool
-> Int
-> UArray Int Word16
-> UArray Int Word64
-> UArray Int Word64
-> SizedSeq ResolvedBCOPtr
-> ResolvedBCO)
-> Get Bool
-> Get
(Int
-> UArray Int Word16
-> UArray Int Word64
-> UArray Int Word64
-> SizedSeq ResolvedBCOPtr
-> ResolvedBCO)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get Get
(Int
-> UArray Int Word16
-> UArray Int Word64
-> UArray Int Word64
-> SizedSeq ResolvedBCOPtr
-> ResolvedBCO)
-> Get Int
-> Get
(UArray Int Word16
-> UArray Int Word64
-> UArray Int Word64
-> SizedSeq ResolvedBCOPtr
-> ResolvedBCO)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get Get
(UArray Int Word16
-> UArray Int Word64
-> UArray Int Word64
-> SizedSeq ResolvedBCOPtr
-> ResolvedBCO)
-> Get (UArray Int Word16)
-> Get
(UArray Int Word64
-> UArray Int Word64 -> SizedSeq ResolvedBCOPtr -> ResolvedBCO)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get (UArray Int Word16)
forall i a.
(Binary i, Ix i, MArray IOUArray a IO) =>
Get (UArray i a)
External instance of the constraint type MArray IOUArray Word16 IO
External instance of the constraint type Ix Int
External instance of the constraint type Binary Int
getArray Get
(UArray Int Word64
-> UArray Int Word64 -> SizedSeq ResolvedBCOPtr -> ResolvedBCO)
-> Get (UArray Int Word64)
-> Get
(UArray Int Word64 -> SizedSeq ResolvedBCOPtr -> ResolvedBCO)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get (UArray Int Word64)
forall i a.
(Binary i, Ix i, MArray IOUArray a IO) =>
Get (UArray i a)
External instance of the constraint type MArray IOUArray Word64 IO
External instance of the constraint type Ix Int
External instance of the constraint type Binary Int
getArray Get (UArray Int Word64 -> SizedSeq ResolvedBCOPtr -> ResolvedBCO)
-> Get (UArray Int Word64)
-> Get (SizedSeq ResolvedBCOPtr -> ResolvedBCO)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get (UArray Int Word64)
forall i a.
(Binary i, Ix i, MArray IOUArray a IO) =>
Get (UArray i a)
External instance of the constraint type MArray IOUArray Word64 IO
External instance of the constraint type Ix Int
External instance of the constraint type Binary Int
getArray Get (SizedSeq ResolvedBCOPtr -> ResolvedBCO)
-> Get (SizedSeq ResolvedBCOPtr) -> Get ResolvedBCO
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get (SizedSeq ResolvedBCOPtr)
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary (SizedSeq a)
Instance of class: Binary of the constraint type Binary ResolvedBCOPtr
get
data ResolvedBCOPtr
= ResolvedBCORef {-# UNPACK #-} !Int
| ResolvedBCOPtr {-# UNPACK #-} !(RemoteRef HValue)
| ResolvedBCOStaticPtr {-# UNPACK #-} !(RemotePtr ())
| ResolvedBCOPtrBCO ResolvedBCO
| ResolvedBCOPtrBreakArray {-# UNPACK #-} !(RemoteRef BreakArray)
deriving ((forall x. ResolvedBCOPtr -> Rep ResolvedBCOPtr x)
-> (forall x. Rep ResolvedBCOPtr x -> ResolvedBCOPtr)
-> Generic ResolvedBCOPtr
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
(Int -> ResolvedBCOPtr -> ShowS)
-> (ResolvedBCOPtr -> String)
-> ([ResolvedBCOPtr] -> ShowS)
-> Show ResolvedBCOPtr
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
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type forall a. Show (RemoteRef a)
External instance of the constraint type Ord Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show ResolvedBCO
Show)
instance Binary ResolvedBCOPtr