stgi-1.0.1: Educational implementation of the STG (Spineless Tagless G-machine)

Safe HaskellNone
LanguageHaskell2010

Stg.Machine.Types

Contents

Description

Types used in the execution of the STG machine.

Synopsis

Documentation

data StgState Source

The internal state of an STG.

Constructors

StgState 

Fields

stgCode :: Code

Operation the STG should perform next

stgStack :: Stack StackFrame

The stack stores not-yet-used arguments (argument stack part), computations to return to once case evaluation has finished (return stack part), and instructions to update heap entries once computation of a certain value is done.

stgHeap :: Heap

The heap stores values allocated at the top level or in let(rec) expressions.

stgGlobals :: Globals

The environment consisting of the top-level definitions.

stgSteps :: !Integer

A counter, used to generte fresh variable names from.

stgInfo :: Info

Information about the current state

data StgStateStyle Source

Package of style definitions used in this module.

Constructors

StgStateStyle 

Fields

headline :: Doc -> Doc

Style of headlines in the state overview, such as "Heap" and "Frame i".

address :: Doc -> Doc

Style of memory addresses, including 0x prefix.

addressCore :: Doc -> Doc

Style of memory addresses; applied only to the actual address number, such as ff in 0xff.

closureType :: Doc -> Doc

Style of the type of a closure, such as BLACKHOLE or FUN.

stackFrameType :: Doc -> Doc

Style of the stack frame annotation, such as UPD or ARG.

data StackFrame Source

Constructors

ArgumentFrame Value

Argument frames store values on the argument stack, so that they can later be retrieved when the calling function can be applied to them.

ReturnFrame Alts Locals

Return frames are used when the scrutinee of a case expression is done being evaluated, and the branch to continue on has to be decided.

UpdateFrame MemAddr

When an updatable closure is entered, an update frame with its heap address is created. Once its computation finishes, its heap entry is updated with the computed value.

data Code Source

The different code states the STG can be in.

Constructors

Eval Expr Locals

Evaluate an expression within a local environment

Enter MemAddr

Load the closure at a certain heap address

ReturnCon Constr [Value]

Sub-computation terminated with algebraic constructor

ReturnInt Integer

Sub-computation terminated with a primitive integer

data Mapping k v Source

A single key -> value association.

Used to make 2-tuples to be inserted into association maps clearer.

Constructors

Mapping k v 

Instances

(Eq k, Eq v) => Eq (Mapping k v) Source 
(Ord k, Ord v) => Ord (Mapping k v) Source 
(Show k, Show v) => Show (Mapping k v) Source 
Generic (Mapping k v) Source 
(Pretty k, Pretty v) => Pretty (Mapping k v) Source 
(NFData k, NFData v) => NFData (Mapping k v) Source 
type Rep (Mapping k v) Source 

newtype Globals Source

The global environment consists of the mapping from top-level definitions to their respective values.

Constructors

Globals (Map Var Value) 

newtype Locals Source

The global environment consists if the mapping from local definitions to their respective values.

Constructors

Locals (Map Var Value) 

data Closure Source

A closure is a lambda form, together with the values of its free variables.

Constructors

Closure LambdaForm [Value] 

newtype Heap Source

The heap stores closures addressed by memory location.

Constructors

Heap (Map MemAddr HeapObject) 

data HeapObject Source

Constructors

HClosure Closure 
Blackhole Integer

When an updatable closure is entered, it is overwritten by a black hole. This has two main benefits:

  1. Memory mentioned only in the closure is now ready to be collected, avoiding certain space leaks.
  2. Entering a black hole means a thunk depends on itself, allowing the interpreter to catch some non-terminating computations with a useful error

To make the black hole a bit more transparent, it is tagged with the STG tick in which it was introduced. This tag is used only for display purposes.

State information

data Info Source

User-facing information about the current state of the STG.

Constructors

Info InfoShort [InfoDetail] 

data InfoShort Source

Short machine status info. This field may be used programmatically, in particular it tells the stepper whether the machine has halted.

Constructors

NoRulesApply

There is no valid state transition to continue with.

MaxStepsExceeded

The machine did not halt within a number of steps. Used by evalUntil.

HaltedByPredicate

The machine halted because a user-specified halting predicate held.

StateError StateError

The machine halted in a state that is known to be invalid, there is no valid state transition to continue with.

An example of this would be a ReturnCon state with an empty return stack.

StateTransition StateTransition

Description of the state transition that lead to the current state.

StateInitial

Used to mark the initial state of the machine.

GarbageCollection

A garbage collection step, in which no ordinary evaluation is done.