| Copyright | (c) The University of Glasgow 2001 |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Jeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Sylvain Henry <sylvain.henry@iohk.io> Josh Meredith <josh.meredith@iohk.io> |
| Stability | experimental |
| Safe Haskell | None |
| Language | GHC2021 |
GHC.StgToJS.Types
Description
Module that holds the Types required for the StgToJS pass
Synopsis
- type G = StateT GenState IO
- data GenState = GenState {
- gsSettings :: !StgToJSConfig
- gsModule :: !Module
- gsId :: !FastMutInt
- gsIdents :: !IdCache
- gsUnfloated :: !(UniqFM Id CgStgExpr)
- gsGroup :: GenGroupState
- gsGlobal :: [JStgStat]
- data GenGroupState = GenGroupState {}
- data StgToJSConfig = StgToJSConfig {
- csInlinePush :: !Bool
- csInlineBlackhole :: !Bool
- csInlineLoadRegs :: !Bool
- csInlineEnter :: !Bool
- csInlineAlloc :: !Bool
- csPrettyRender :: !Bool
- csTraceRts :: !Bool
- csAssertRts :: !Bool
- csBoundsCheck :: !Bool
- csDebugAlloc :: !Bool
- csTraceForeign :: !Bool
- csProf :: !Bool
- csRuntimeAssert :: !Bool
- csContext :: !SDocContext
- csLinkerConfig :: !LinkerConfig
- data ClosureInfo = ClosureInfo {}
- data CIRegs
- = CIRegsUnknown
- | CIRegs {
- ciRegsSkip :: Int
- ciRegsTypes :: [JSRep]
- data CILayout
- = CILayoutVariable
- | CILayoutUnknown {
- layoutSize :: !Int
- | CILayoutFixed {
- layoutSize :: !Int
- layout :: [JSRep]
- data CIType
- = CIFun { }
- | CIThunk
- | CICon {
- citConstructor :: !Int
- | CIPap
- | CIBlackhole
- | CIStackFrame
- newtype CIStatic = CIStaticRefs {
- staticRefs :: [FastString]
- data JSRep
- data IdType
- = IdPlain
- | IdEntry
- | IdConEntry
- data IdKey = IdKey !Word64 !Int !IdType
- data OtherSymb = OtherSymb !Module !FastString
- newtype IdCache = IdCache (Map IdKey Ident)
- newtype GlobalIdCache = GlobalIdCache (UniqFM Ident (IdKey, Id))
- data StackSlot
- = SlotId !Id !Int
- | SlotUnknown
- data StaticInfo = StaticInfo {}
- data StaticAppKind
- data StaticVal
- data StaticUnboxed
- data StaticArg
- data StaticLit
- = BoolLit !Bool
- | IntLit !Integer
- | NullLit
- | DoubleLit !SaneDouble
- | StringLit !FastString
- | BinLit !ByteString
- | LabelLit !Bool !FastString
- data ForeignJSRef = ForeignJSRef {}
- data LinkableUnit = LinkableUnit {
- luObjBlock :: ObjBlock
- luIdExports :: [Id]
- luOtherExports :: [FastString]
- luIdDeps :: [Id]
- luPseudoIdDeps :: [Unique]
- luOtherDeps :: [OtherSymb]
- luRequired :: Bool
- luForeignRefs :: [ForeignJSRef]
- data ObjBlock = ObjBlock {
- oiSymbols :: [FastString]
- oiClInfo :: [ClosureInfo]
- oiStatic :: [StaticInfo]
- oiStat :: JStat
- oiRaw :: ByteString
- oiFExports :: [ExpFun]
- oiFImports :: [ForeignJSRef]
- data ExpFun = ExpFun {}
- data JSFFIType
- data TypedExpr = TypedExpr {
- typex_typ :: !PrimRep
- typex_expr :: [JStgExpr]
- data PrimRes
- data ExprResult
- newtype ExprValData = ExprValData [JStgExpr]
- data ClosureType
- ctNum :: ClosureType -> Int
- closureB :: ByteString
- closureNames :: Array ClosureType Ident
- ctJsName :: ClosureType -> String
- data ThreadStatus
- threadStatusNum :: ThreadStatus -> Int
- threadStatusJsName :: ThreadStatus -> String
Documentation
The JS code generator state
Constructors
| GenState | |
Fields
| |
data GenGroupState Source #
The JS code generator state relevant for the current binding group
Constructors
| GenGroupState | |
Fields
| |
data StgToJSConfig Source #
The Configuration record for the StgToJS pass
Constructors
| StgToJSConfig | |
Fields
| |
data ClosureInfo Source #
Closure info table
Constructors
| ClosureInfo | |
Fields
| |
Instances
| Binary ClosureInfo Source # | |
Defined in GHC.StgToJS.Object Methods put_ :: WriteBinHandle -> ClosureInfo -> IO () Source # put :: WriteBinHandle -> ClosureInfo -> IO (Bin ClosureInfo) Source # get :: ReadBinHandle -> IO ClosureInfo Source # | |
| Eq ClosureInfo Source # | |
Defined in GHC.StgToJS.Types Methods (==) :: ClosureInfo -> ClosureInfo -> Bool Source # (/=) :: ClosureInfo -> ClosureInfo -> Bool Source # | |
| Show ClosureInfo Source # | |
Defined in GHC.StgToJS.Types | |
Closure information, ClosureInfo, registers
Constructors
| CIRegsUnknown | A value witnessing a state of unknown registers |
| CIRegs | |
Fields
| |
Instances
| Binary CIRegs Source # | |
| Eq CIRegs Source # | |
| Ord CIRegs Source # | |
| Show CIRegs Source # | |
Closure Information, ClosureInfo, layout
Constructors
| CILayoutVariable | layout stored in object itself, first position from the start |
| CILayoutUnknown | fixed size, but content unknown (for example stack apply frame) |
Fields
| |
| CILayoutFixed | whole layout known |
Fields
| |
Instances
| Binary CILayout Source # | |
| Eq CILayout Source # | |
| Ord CILayout Source # | |
Defined in GHC.StgToJS.Types | |
| Show CILayout Source # | |
The type of ClosureInfo
Constructors
| CIFun | |
| CIThunk | The closure is a THUNK |
| CICon | The closure is a Constructor |
Fields
| |
| CIPap | The closure is a Partial Application |
| CIBlackhole | The closure is a black hole |
| CIStackFrame | The closure is a stack frame |
Instances
| Binary CIType Source # | |
| Eq CIType Source # | |
| Ord CIType Source # | |
| Show CIType Source # | |
Static references that must be kept alive
Constructors
| CIStaticRefs | |
Fields
| |
JS primitive representations
Constructors
| PtrV | pointer = reference to heap object (closure object), lifted or not. Can also be some RTS object (e.g. TVar#, MVar#, MutVar#, Weak#) |
| VoidV | no fields |
| DoubleV | A Double: one field |
| IntV | An Int (32bit because JS): one field |
| LongV | A Long: two fields one for the upper 32bits, one for the lower (NB: JS is little endian) |
| AddrV | a pointer not to the heap: two fields, array + index |
| ObjV | some JS object, user supplied, be careful around these, can be anything |
| ArrV | boxed array |
Instances
| ToJExpr JSRep Source # | |
| Binary JSRep Source # | |
| Eq JSRep Source # | |
| Ord JSRep Source # | |
Defined in GHC.StgToJS.Types | |
| Bounded JSRep Source # | |
| Enum JSRep Source # | |
Defined in GHC.StgToJS.Types Methods succ :: JSRep -> JSRep Source # pred :: JSRep -> JSRep Source # toEnum :: Int -> JSRep Source # fromEnum :: JSRep -> Int Source # enumFrom :: JSRep -> [JSRep] Source # enumFromThen :: JSRep -> JSRep -> [JSRep] Source # enumFromTo :: JSRep -> JSRep -> [JSRep] Source # enumFromThenTo :: JSRep -> JSRep -> JSRep -> [JSRep] Source # | |
| Show JSRep Source # | |
The type of identifiers. These determine the suffix of generated functions
in JS Land. For example, the entry function for the Just constructor is a
IdConEntry which compiles to:
function h$ghczminternalZCGHCziInternalziMaybeziJust_con_e() { return h$rs() };
which just returns whatever the stack point is pointing to. Whereas the entry
function to Just is an IdEntry and does the work. It compiles to:
function h$ghczminternalZCGHCziInternalziMaybeziJust_e() {
var h$$baseZCGHCziMaybezieta_8KXnScrCjF5 = h$r2;
h$r1 = h$c1(h$ghczminternalZCGHCziInternalziMaybeziJust_con_e, h$$ghczminternalZCGHCziInternalziMaybezieta_8KXnScrCjF5);
return h$rs();
};
Which loads some payload from register 2, and applies the Constructor Entry
function for the Just to the payload, returns the result in register 1 and
returns whatever is on top of the stack
Constructors
| IdPlain | A plain identifier for values, no suffix added |
| IdEntry | An entry function, suffix = "_e" in |
| IdConEntry | A Constructor entry function, suffix = "_con_e" in |
Instances
| Eq IdType Source # | |
| Ord IdType Source # | |
| Enum IdType Source # | |
Defined in GHC.StgToJS.Types Methods succ :: IdType -> IdType Source # pred :: IdType -> IdType Source # toEnum :: Int -> IdType Source # fromEnum :: IdType -> Int Source # enumFrom :: IdType -> [IdType] Source # enumFromThen :: IdType -> IdType -> [IdType] Source # enumFromTo :: IdType -> IdType -> [IdType] Source # enumFromThenTo :: IdType -> IdType -> IdType -> [IdType] Source # | |
Keys to differentiate Ident's in the ID Cache
Some other symbol
Constructors
| OtherSymb !Module !FastString |
Instances
| Eq OtherSymb Source # | |
| Ord OtherSymb Source # | |
Defined in GHC.StgToJS.Types | |
The identifier cache indexed on IdKey local to a module
newtype GlobalIdCache Source #
The global Identifier Cache
Constructors
| GlobalIdCache (UniqFM Ident (IdKey, Id)) |
A Stack Slot is either known or unknown. We avoid maybe here for more strictness.
Constructors
| SlotId !Id !Int | |
| SlotUnknown |
Instances
| Eq StackSlot Source # | |
| Ord StackSlot Source # | |
Defined in GHC.StgToJS.Types | |
data StaticInfo Source #
Constructors
| StaticInfo | |
Instances
| Binary StaticInfo Source # | |
Defined in GHC.StgToJS.Object Methods put_ :: WriteBinHandle -> StaticInfo -> IO () Source # put :: WriteBinHandle -> StaticInfo -> IO (Bin StaticInfo) Source # get :: ReadBinHandle -> IO StaticInfo Source # | |
| Eq StaticInfo Source # | |
Defined in GHC.StgToJS.Types Methods (==) :: StaticInfo -> StaticInfo -> Bool Source # (/=) :: StaticInfo -> StaticInfo -> Bool Source # | |
| Show StaticInfo Source # | |
Defined in GHC.StgToJS.Types | |
data StaticAppKind Source #
Instances
| Eq StaticAppKind Source # | |
Defined in GHC.StgToJS.Types Methods (==) :: StaticAppKind -> StaticAppKind -> Bool Source # (/=) :: StaticAppKind -> StaticAppKind -> Bool Source # | |
| Show StaticAppKind Source # | |
Defined in GHC.StgToJS.Types | |
Constructors
| StaticUnboxed !StaticUnboxed | unboxed constructor (Bool, Int, Double etc) |
| StaticList [StaticArg] (Maybe FastString) | list initializer (with optional tail) |
| StaticApp StaticAppKind !FastString [StaticArg] | static application of static args. Can be a CAF, a FUN, or a CON app. |
data StaticUnboxed Source #
Constructors
| StaticUnboxedBool !Bool | |
| StaticUnboxedInt !Integer | |
| StaticUnboxedDouble !SaneDouble | |
| StaticUnboxedString !ByteString | |
| StaticUnboxedStringOffset !ByteString |
Instances
| Binary StaticUnboxed Source # | |
Defined in GHC.StgToJS.Object Methods put_ :: WriteBinHandle -> StaticUnboxed -> IO () Source # put :: WriteBinHandle -> StaticUnboxed -> IO (Bin StaticUnboxed) Source # get :: ReadBinHandle -> IO StaticUnboxed Source # | |
| Eq StaticUnboxed Source # | |
Defined in GHC.StgToJS.Types Methods (==) :: StaticUnboxed -> StaticUnboxed -> Bool Source # (/=) :: StaticUnboxed -> StaticUnboxed -> Bool Source # | |
| Ord StaticUnboxed Source # | |
Defined in GHC.StgToJS.Types Methods compare :: StaticUnboxed -> StaticUnboxed -> Ordering Source # (<) :: StaticUnboxed -> StaticUnboxed -> Bool Source # (<=) :: StaticUnboxed -> StaticUnboxed -> Bool Source # (>) :: StaticUnboxed -> StaticUnboxed -> Bool Source # (>=) :: StaticUnboxed -> StaticUnboxed -> Bool Source # max :: StaticUnboxed -> StaticUnboxed -> StaticUnboxed Source # min :: StaticUnboxed -> StaticUnboxed -> StaticUnboxed Source # | |
| Show StaticUnboxed Source # | |
Defined in GHC.StgToJS.Types | |
Static Arguments. Static Arguments are things that are statically allocated, i.e., they exist at program startup. These are static heap objects or literals or things that have been floated to the top level binding by ghc.
Constructors
| StaticObjArg !FastString | reference to a heap object |
| StaticLitArg !StaticLit | literal |
| StaticConArg !FastString [StaticArg] | unfloated constructor |
A Static literal value
Constructors
| BoolLit !Bool | |
| IntLit !Integer | |
| NullLit | |
| DoubleLit !SaneDouble | |
| StringLit !FastString | |
| BinLit !ByteString | |
| LabelLit !Bool !FastString | is function pointer, label (also used for string / binary init) |
data ForeignJSRef Source #
A foreign reference to some JS code
Constructors
| ForeignJSRef | |
Fields | |
Instances
| Binary ForeignJSRef Source # | |
Defined in GHC.StgToJS.Object Methods put_ :: WriteBinHandle -> ForeignJSRef -> IO () Source # put :: WriteBinHandle -> ForeignJSRef -> IO (Bin ForeignJSRef) Source # get :: ReadBinHandle -> IO ForeignJSRef Source # | |
| Show ForeignJSRef Source # | |
Defined in GHC.StgToJS.Types | |
data LinkableUnit Source #
data used to generate one ObjBlock in our object file
Constructors
| LinkableUnit | |
Fields
| |
one toplevel block in the object file
Constructors
| ObjBlock | |
Fields
| |
Instances
| Binary ExpFun Source # | |
| Eq ExpFun Source # | |
| Ord ExpFun Source # | |
| Show ExpFun Source # | |
Types of FFI values
Constructors
| Int8Type | |
| Int16Type | |
| Int32Type | |
| Int64Type | |
| Word8Type | |
| Word16Type | |
| Word32Type | |
| Word64Type | |
| DoubleType | |
| ByteArrayType | |
| PtrType | |
| RefType |
Instances
| Binary JSFFIType Source # | |
| Eq JSFFIType Source # | |
| Ord JSFFIType Source # | |
Defined in GHC.StgToJS.Types | |
| Enum JSFFIType Source # | |
Defined in GHC.StgToJS.Types Methods succ :: JSFFIType -> JSFFIType Source # pred :: JSFFIType -> JSFFIType Source # toEnum :: Int -> JSFFIType Source # fromEnum :: JSFFIType -> Int Source # enumFrom :: JSFFIType -> [JSFFIType] Source # enumFromThen :: JSFFIType -> JSFFIType -> [JSFFIType] Source # enumFromTo :: JSFFIType -> JSFFIType -> [JSFFIType] Source # enumFromThenTo :: JSFFIType -> JSFFIType -> JSFFIType -> [JSFFIType] Source # | |
| Show JSFFIType Source # | |
Typed expression
Constructors
| TypedExpr | |
Fields
| |
Instances
A Primop result is either an inlining of some JS payload, or a primitive call to a JS function defined in Shim files in base.
Constructors
| PrimInline JStgStat | primop is inline, result is assigned directly |
| PRPrimCall JStgStat | primop is async call, primop returns the next function to run. result returned to stack top in registers |
data ExprResult Source #
Constructors
| ExprCont | |
| ExprInline |
Instances
| Eq ExprResult Source # | |
Defined in GHC.StgToJS.Types Methods (==) :: ExprResult -> ExprResult -> Bool Source # (/=) :: ExprResult -> ExprResult -> Bool Source # | |
newtype ExprValData Source #
Constructors
| ExprValData [JStgExpr] |
Instances
| Eq ExprValData Source # | |
Defined in GHC.StgToJS.Types Methods (==) :: ExprValData -> ExprValData -> Bool Source # (/=) :: ExprValData -> ExprValData -> Bool Source # | |
data ClosureType Source #
A Closure is one of six types
Constructors
| Thunk | The closure is a THUNK |
| Fun | The closure is a Function |
| Pap | The closure is a Partial Application |
| Con | The closure is a Constructor |
| Blackhole | The closure is a Blackhole |
| StackFrame | The closure is a stack frame |
Instances
ctNum :: ClosureType -> Int Source #
Convert ClosureType to an Int
ctJsName :: ClosureType -> String Source #
Convert ClosureType to a String
data ThreadStatus Source #
A thread is in one of 4 states
Constructors
| Running | The thread is running |
| Blocked | The thread is blocked |
| Finished | The thread is done |
| Died | The thread has died |
Instances
threadStatusNum :: ThreadStatus -> Int Source #
Convert the status of a thread in JS land to an Int
threadStatusJsName :: ThreadStatus -> String Source #
convert the status of a thread in JS land to a string