ghc-9.11: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.ByteCode.Types

Description

Bytecode assembler types

Synopsis

Documentation

data CompiledByteCode Source #

Constructors

CompiledByteCode 

Fields

Instances

Instances details
Outputable CompiledByteCode Source # 
Instance details

Defined in GHC.ByteCode.Types

data BCOByteArray a Source #

Wrapper for a ByteArray#. The phantom type tells what elements are stored in the ByteArray#. Creating a ByteArray# can be achieved using UArray's API, where the underlying ByteArray# can be unpacked.

Constructors

BCOByteArray 

Instances

Instances details
Binary (BCOByteArray a) Source # 
Instance details

Defined in GHCi.ResolvedBCO

Show (BCOByteArray Word16) Source # 
Instance details

Defined in GHCi.ResolvedBCO

Show (BCOByteArray Word) Source # 
Instance details

Defined in GHCi.ResolvedBCO

newtype FFIInfo Source #

Constructors

FFIInfo (RemotePtr C_ffi_cif) 

Instances

Instances details
NFData FFIInfo Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

rnf :: FFIInfo -> () Source #

Show FFIInfo Source # 
Instance details

Defined in GHC.ByteCode.Types

newtype RegBitmap Source #

Constructors

RegBitmap 

Fields

Instances

Instances details
Outputable RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: RegBitmap -> SDoc Source #

Bits RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

FiniteBits RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Enum RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Num RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Integral RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Real RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Show RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Eq RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

Ord RegBitmap Source # 
Instance details

Defined in GHC.ByteCode.Types

data NativeCallType Source #

Instances

Instances details
Eq NativeCallType Source # 
Instance details

Defined in GHC.ByteCode.Types

newtype ByteOff Source #

Constructors

ByteOff Int 

Instances

Instances details
Outputable ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: ByteOff -> SDoc Source #

Enum ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Num ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Integral ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Real ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Show ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Eq ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

(==) :: ByteOff -> ByteOff -> Bool #

(/=) :: ByteOff -> ByteOff -> Bool #

Ord ByteOff Source # 
Instance details

Defined in GHC.ByteCode.Types

newtype WordOff Source #

Constructors

WordOff Int 

Instances

Instances details
Outputable WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: WordOff -> SDoc Source #

Enum WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Num WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Integral WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Real WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Show WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Eq WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

(==) :: WordOff -> WordOff -> Bool #

(/=) :: WordOff -> WordOff -> Bool #

Ord WordOff Source # 
Instance details

Defined in GHC.ByteCode.Types

newtype HalfWord Source #

Constructors

HalfWord Word 

Instances

Instances details
Outputable HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: HalfWord -> SDoc Source #

Enum HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

Num HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

Integral HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

Real HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

Show HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

Eq HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

Ord HalfWord Source # 
Instance details

Defined in GHC.ByteCode.Types

data BCOPtr Source #

Constructors

BCOPtrName !Name 
BCOPtrPrimOp !PrimOp 
BCOPtrBCO !UnlinkedBCO 
BCOPtrBreakArray (ForeignRef BreakArray)

a pointer to a breakpoint's module's BreakArray in GHCi's memory

Instances

Instances details
NFData BCOPtr Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

rnf :: BCOPtr -> () Source #

data BCONPtr Source #

Constructors

BCONPtrWord !Word 
BCONPtrLbl !FastString 
BCONPtrItbl !Name 
BCONPtrAddr !Name

A reference to a top-level string literal; see Note [Generating code for top-level string literal bindings] in GHC.StgToByteCode.

BCONPtrStr !ByteString

Only used internally in the assembler in an intermediate representation; should never appear in a fully-assembled UnlinkedBCO. Also see Note [Allocating string literals] in GHC.ByteCode.Asm.

Instances

Instances details
NFData BCONPtr Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

rnf :: BCONPtr -> () Source #

newtype ItblPtr Source #

Instances

Instances details
NFData ItblPtr Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

rnf :: ItblPtr -> () Source #

Show ItblPtr Source # 
Instance details

Defined in GHC.ByteCode.Types

newtype AddrPtr Source #

Constructors

AddrPtr (RemotePtr ()) 

Instances

Instances details
NFData AddrPtr Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

rnf :: AddrPtr -> () Source #

data CgBreakInfo Source #

Information about a breakpoint that we know at code-generation time In order to be used, this needs to be hydrated relative to the current HscEnv by hydrateCgBreakInfo. Everything here can be fully forced and that's critical for preventing space leaks (see #22530)

Constructors

CgBreakInfo 

Fields

Instances

Instances details
Outputable CgBreakInfo Source # 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: CgBreakInfo -> SDoc Source #

data ModBreaks Source #

All the information about the breakpoints for a module

Constructors

ModBreaks 

Fields

type BreakIndex = Int Source #

Breakpoint index

emptyModBreaks :: ModBreaks Source #

Construct an empty ModBreaks

data CCostCentre Source #

C CostCentre type

data FlatBag a Source #

Store elements in a flattened representation.

A FlatBag is a data structure that stores an ordered list of elements in a flat structure, avoiding the overhead of a linked list. Use this data structure, if the code requires the following properties:

  • Elements are stored in a long-lived object, and benefit from a flattened representation.
  • The FlatBag will be traversed but not extended or filtered.
  • The number of elements should be known.
  • Sharing of the empty case improves memory behaviour.

A FlagBag aims to have as little overhead as possible to store its elements. To achieve that, it distinguishes between the empty case, singleton, tuple and general case. Thus, we only pay for the additional three words of an Array if we have at least three elements.

Instances

Instances details
Functor FlatBag Source # 
Instance details

Defined in GHC.Data.FlatBag

Methods

fmap :: (a -> b) -> FlatBag a -> FlatBag b #

(<$) :: a -> FlatBag b -> FlatBag a #

Foldable FlatBag Source # 
Instance details

Defined in GHC.Data.FlatBag

Methods

fold :: Monoid m => FlatBag m -> m #

foldMap :: Monoid m => (a -> m) -> FlatBag a -> m #

foldMap' :: Monoid m => (a -> m) -> FlatBag a -> m #

foldr :: (a -> b -> b) -> b -> FlatBag a -> b #

foldr' :: (a -> b -> b) -> b -> FlatBag a -> b #

foldl :: (b -> a -> b) -> b -> FlatBag a -> b #

foldl' :: (b -> a -> b) -> b -> FlatBag a -> b #

foldr1 :: (a -> a -> a) -> FlatBag a -> a #

foldl1 :: (a -> a -> a) -> FlatBag a -> a #

toList :: FlatBag a -> [a] #

null :: FlatBag a -> Bool #

length :: FlatBag a -> Int #

elem :: Eq a => a -> FlatBag a -> Bool #

maximum :: Ord a => FlatBag a -> a #

minimum :: Ord a => FlatBag a -> a #

sum :: Num a => FlatBag a -> a #

product :: Num a => FlatBag a -> a #

Traversable FlatBag Source # 
Instance details

Defined in GHC.Data.FlatBag

Methods

traverse :: Applicative f => (a -> f b) -> FlatBag a -> f (FlatBag b) #

sequenceA :: Applicative f => FlatBag (f a) -> f (FlatBag a) #

mapM :: Monad m => (a -> m b) -> FlatBag a -> m (FlatBag b) #

sequence :: Monad m => FlatBag (m a) -> m (FlatBag a) #

NFData a => NFData (FlatBag a) Source # 
Instance details

Defined in GHC.Data.FlatBag

Methods

rnf :: FlatBag a -> () Source #

sizeFlatBag :: FlatBag a -> Word Source #

Calculate the size of

fromSizedSeq :: SizedSeq a -> FlatBag a Source #

Convert a SizedSeq into its flattened representation. A 'FlatBag a' is more memory efficient than '[a]', if no further modification is necessary.

elemsFlatBag :: FlatBag a -> [a] Source #

Get all elements that are stored in the FlatBag.