ghc-9.6.1: The GHC API
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file LICENSE)
MaintainerJeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Sylvain Henry <sylvain.henry@iohk.io> Josh Meredith <josh.meredith@iohk.io>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.StgToJS.Types

Description

Module that holds the Types required for the StgToJS pass

Synopsis

Documentation

type G = StateT GenState IO Source #

A State monad over IO holding the generator state.

data GenState Source #

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 

data ClosureInfo Source #

Information relevenat to code generation for closures.

Constructors

ClosureInfo 

Fields

Instances

Instances details
Generic ClosureInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep ClosureInfo :: Type -> Type Source #

Show ClosureInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

Binary ClosureInfo Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq ClosureInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep ClosureInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

data CIRegs Source #

Closure information, ClosureInfo, registers

Constructors

CIRegsUnknown

A value witnessing a state of unknown registers

CIRegs 

Fields

Instances

Instances details
Generic CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep CIRegs :: Type -> Type Source #

Show CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Types

NFData CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

rnf :: CIRegs -> () Source #

Binary CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

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

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

Ord CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CIRegs = D1 ('MetaData "CIRegs" "GHC.StgToJS.Types" "ghc" 'False) (C1 ('MetaCons "CIRegsUnknown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CIRegs" 'PrefixI 'True) (S1 ('MetaSel ('Just "ciRegsSkip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ciRegsTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarType])))

data CILayout 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

  • layoutSize :: !Int

    closure size in array positions, including entry

CILayoutFixed

whole layout known

Fields

Instances

Instances details
Generic CILayout Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep CILayout :: Type -> Type Source #

Show CILayout Source # 
Instance details

Defined in GHC.StgToJS.Types

NFData CILayout Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

rnf :: CILayout -> () Source #

Binary CILayout Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq CILayout Source # 
Instance details

Defined in GHC.StgToJS.Types

Ord CILayout Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CILayout Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CILayout = D1 ('MetaData "CILayout" "GHC.StgToJS.Types" "ghc" 'False) (C1 ('MetaCons "CILayoutVariable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CILayoutUnknown" 'PrefixI 'True) (S1 ('MetaSel ('Just "layoutSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "CILayoutFixed" 'PrefixI 'True) (S1 ('MetaSel ('Just "layoutSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "layout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarType]))))

data CIType Source #

The type of ClosureInfo

Constructors

CIFun 

Fields

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

Instances details
Generic CIType Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep CIType :: Type -> Type Source #

Show CIType Source # 
Instance details

Defined in GHC.StgToJS.Types

NFData CIType Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

rnf :: CIType -> () Source #

Binary CIType Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq CIType Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

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

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

Ord CIType Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CIType Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CIType = D1 ('MetaData "CIType" "GHC.StgToJS.Types" "ghc" 'False) ((C1 ('MetaCons "CIFun" 'PrefixI 'True) (S1 ('MetaSel ('Just "citArity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "citRegs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "CIThunk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CICon" 'PrefixI 'True) (S1 ('MetaSel ('Just "citConstructor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :+: (C1 ('MetaCons "CIPap" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CIBlackhole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CIStackFrame" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype CIStatic Source #

Static references that must be kept alive

Constructors

CIStaticRefs 

Fields

Instances

Instances details
Monoid CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Types

Semigroup CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Types

Generic CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep CIStatic :: Type -> Type Source #

Show CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Types

ToJExpr CIStatic Source #

static refs: array = references, null = nothing to report note: only works after all top-level objects have been created

Instance details

Defined in GHC.StgToJS.Types

Binary CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep CIStatic = D1 ('MetaData "CIStatic" "GHC.StgToJS.Types" "ghc" 'True) (C1 ('MetaCons "CIStaticRefs" 'PrefixI 'True) (S1 ('MetaSel ('Just "staticRefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FastString])))

data VarType Source #

Free variable types

Constructors

PtrV

pointer = reference to heap object (closure object)

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

RtsObjV

some RTS object from GHCJS (for example TVar#, MVar#, MutVar#, Weak#)

ObjV

some JS object, user supplied, be careful around these, can be anything

ArrV

boxed array

Instances

Instances details
Bounded VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

Enum VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

Generic VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep VarType :: Type -> Type Source #

Show VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

NFData VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

rnf :: VarType -> () Source #

ToJExpr VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

Binary VarType Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

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

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

Ord VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep VarType Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep VarType = D1 ('MetaData "VarType" "GHC.StgToJS.Types" "ghc" 'False) (((C1 ('MetaCons "PtrV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VoidV" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DoubleV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IntV" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LongV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AddrV" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RtsObjV" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ObjV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrV" 'PrefixI 'False) (U1 :: Type -> Type)))))

data IdType 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$baseZCGHCziMaybeziJust_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$baseZCGHCziMaybeziJust_e() { var h$$baseZCGHCziMaybezieta_8KXnScrCjF5 = h$r2; h$r1 = h$c1(h$baseZCGHCziMaybeziJust_con_e, h$$baseZCGHCziMaybezieta_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 makeIdentForId

IdConEntry

A Constructor entry function, suffix = "_con_e" in makeIdentForId

Instances

Instances details
Enum IdType Source # 
Instance details

Defined in GHC.StgToJS.Types

Eq IdType Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

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

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

Ord IdType Source # 
Instance details

Defined in GHC.StgToJS.Types

data IdKey Source #

Keys to differentiate Ident's in the ID Cache

Constructors

IdKey !Int !Int !IdType 

Instances

Instances details
Eq IdKey Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

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

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

Ord IdKey Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

compare :: IdKey -> IdKey -> Ordering #

(<) :: IdKey -> IdKey -> Bool #

(<=) :: IdKey -> IdKey -> Bool #

(>) :: IdKey -> IdKey -> Bool #

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

max :: IdKey -> IdKey -> IdKey #

min :: IdKey -> IdKey -> IdKey #

data OtherSymb Source #

Some other symbol

Constructors

OtherSymb !Module !FastString 

Instances

Instances details
Eq OtherSymb Source # 
Instance details

Defined in GHC.StgToJS.Types

Ord OtherSymb Source # 
Instance details

Defined in GHC.StgToJS.Types

newtype IdCache Source #

The identifier cache indexed on IdKey local to a module

Constructors

IdCache (Map IdKey Ident) 

newtype GlobalIdCache Source #

The global Identifier Cache

Constructors

GlobalIdCache (UniqFM Ident (IdKey, Id)) 

data StackSlot Source #

A Stack Slot is either known or unknown. We avoid maybe here for more strictness.

Constructors

SlotId !Id !Int 
SlotUnknown 

Instances

Instances details
Eq StackSlot Source # 
Instance details

Defined in GHC.StgToJS.Types

Ord StackSlot Source # 
Instance details

Defined in GHC.StgToJS.Types

data StaticInfo Source #

Constructors

StaticInfo 

Fields

Instances

Instances details
Generic StaticInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep StaticInfo :: Type -> Type Source #

Show StaticInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

Binary StaticInfo Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq StaticInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep StaticInfo Source # 
Instance details

Defined in GHC.StgToJS.Types

data StaticVal Source #

Constructors

StaticFun !FastString [StaticArg]

heap object for function

StaticThunk !(Maybe (FastString, [StaticArg]))

heap object for CAF (field is Nothing when thunk is initialized in an alternative way, like string thunks through h$str)

StaticUnboxed !StaticUnboxed

unboxed constructor (Bool, Int, Double etc)

StaticData !FastString [StaticArg]

regular datacon app

StaticList [StaticArg] (Maybe FastString)

list initializer (with optional tail)

Instances

Instances details
Generic StaticVal Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep StaticVal :: Type -> Type Source #

Show StaticVal Source # 
Instance details

Defined in GHC.StgToJS.Types

Binary StaticVal Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq StaticVal Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep StaticVal Source # 
Instance details

Defined in GHC.StgToJS.Types

data StaticUnboxed Source #

Instances

Instances details
Generic StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep StaticUnboxed :: Type -> Type Source #

Show StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Types

NFData StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

rnf :: StaticUnboxed -> () Source #

Binary StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Types

Ord StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Types

data StaticArg Source #

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

Instances

Instances details
Generic StaticArg Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep StaticArg :: Type -> Type Source #

Show StaticArg Source # 
Instance details

Defined in GHC.StgToJS.Types

Binary StaticArg Source # 
Instance details

Defined in GHC.StgToJS.Object

Outputable StaticArg Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

ppr :: StaticArg -> SDoc Source #

Eq StaticArg Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep StaticArg Source # 
Instance details

Defined in GHC.StgToJS.Types

data StaticLit Source #

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)

Instances

Instances details
Generic StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep StaticLit :: Type -> Type Source #

Show StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Types

ToJExpr StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Types

Binary StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Object

Outputable StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

ppr :: StaticLit -> SDoc Source #

Eq StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Types

type Rep StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Types

data ForeignJSRef Source #

A foreign reference to some JS code

Instances

Instances details
Generic ForeignJSRef Source # 
Instance details

Defined in GHC.StgToJS.Types

Associated Types

type Rep ForeignJSRef :: Type -> Type Source #

Binary ForeignJSRef Source # 
Instance details

Defined in GHC.StgToJS.Object

type Rep ForeignJSRef Source # 
Instance details

Defined in GHC.StgToJS.Types

data LinkableUnit Source #

data used to generate one ObjUnit in our object file

Constructors

LinkableUnit 

Fields

data ObjUnit Source #

one toplevel block in the object file

Constructors

ObjUnit 

Fields

data ExpFun Source #

Constructors

ExpFun 

Fields

Instances

Instances details
Show ExpFun Source # 
Instance details

Defined in GHC.StgToJS.Types

Binary ExpFun Source # 
Instance details

Defined in GHC.StgToJS.Object

Eq ExpFun Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

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

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

Ord ExpFun Source # 
Instance details

Defined in GHC.StgToJS.Types

data JSFFIType Source #

Types of FFI values

data TypedExpr Source #

Typed expression

Constructors

TypedExpr 

Fields

Instances

Instances details
Outputable TypedExpr Source # 
Instance details

Defined in GHC.StgToJS.Types

Methods

ppr :: TypedExpr -> SDoc Source #

data PrimRes Source #

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 JStat

primop is inline, result is assigned directly

PRPrimCall JStat

primop is async call, primop returns the next function to run. result returned to stack top in registers

data ExprResult Source #

Constructors

ExprCont 
ExprInline (Maybe [JExpr]) 

Instances

Instances details
Eq ExprResult Source # 
Instance details

Defined in GHC.StgToJS.Types

newtype ExprValData Source #

Constructors

ExprValData [JExpr] 

Instances

Instances details
Eq ExprValData Source # 
Instance details

Defined in GHC.StgToJS.Types

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

Instances details
Bounded ClosureType Source # 
Instance details

Defined in GHC.StgToJS.Types

Enum ClosureType Source # 
Instance details

Defined in GHC.StgToJS.Types

Show ClosureType Source # 
Instance details

Defined in GHC.StgToJS.Types

ToJExpr ClosureType Source # 
Instance details

Defined in GHC.StgToJS.Types

Eq ClosureType Source # 
Instance details

Defined in GHC.StgToJS.Types

Ord ClosureType Source # 
Instance details

Defined in GHC.StgToJS.Types

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

Instances details
Bounded ThreadStatus Source # 
Instance details

Defined in GHC.StgToJS.Types

Enum ThreadStatus Source # 
Instance details

Defined in GHC.StgToJS.Types

Show ThreadStatus Source # 
Instance details

Defined in GHC.StgToJS.Types

Eq ThreadStatus Source # 
Instance details

Defined in GHC.StgToJS.Types

Ord ThreadStatus Source # 
Instance details

Defined in GHC.StgToJS.Types

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