linearscan-hoopl-1.0.0: Makes it easy to use the linearscan register allocator with Hoopl

Safe HaskellNone
LanguageHaskell2010

LinearScan.Hoopl.DSL

Contents

Synopsis

Compiling Assembly programs

compile Source

Arguments

:: (NonLocal n, HooplNode n) 
=> String

Entry label name

-> Program n

The assembly language program

-> SimpleUniqueMonad (Graph n C C, Label)

Returns the Hoopl Graph and its entry Label

When a program is compiled, the result is a closed Hoopl Graph, and the label corresponding to the requested entry label name. This is done within a SimpleUniqueMonad so that unique labels may be created.

Programs

data ProgramF n Source

A ProgramF abstracts a generic basic block: a series of Nodes, associated with a label, that ends in a final node.

Constructors

FreeBlock 

type Program n = FreeT ((,) (ProgramF n)) Asm () Source

A Program abstracts a sequence of basic blocks generated from an Asm environment.

Labels

type Labels = Map String Label Source

Labels is the type of a mapping from label names to Hoopl labels.

Assembly nodes

type Asm = StateT Labels SimpleUniqueMonad Source

The Asm static monad allows for the creation labels by name, and referencing them later.

type Nodes n a = Free ((,) (n O O)) a Source

A series of Nodes is a set of assembly instructions that ends with some kind of closing operation, such as a jump, branch or return. The Free monad is used as a convenient way to describe a list that must result in a closing operation at the end.

nodesToList :: Nodes n a -> (a, [n O O]) Source

nodesToList renders a set of nodes as a list of operations followed by a final value a.

type BodyNode n = Nodes n () Source

A BodyNode represents an instruction within a program.

bodyNode :: n O O -> BodyNode n Source

Construct a BodyNode from a Hoopl graph node.

type EndNode n = Nodes n (Asm (n O C)) Source

An EndNode represents a program with a final instruction. This instruction is generated from an Asm environment, so that it may refer to and create labels for other blocks.

endNode :: Asm (n O C) -> EndNode n Source

Construct an EndNode from a Hoopl final node generated from an Asm environment.

label :: String -> EndNode n -> Program n Source

Create and associate a label with an series of instructions, creating a Program for that block.

jump :: HooplNode n => String -> EndNode n Source

Create a final jump instruction to the given label.

Spill stack

data SpillStack Source

Constructors

SpillStack 

Fields

stackPtr :: Int

Offset to the beginning of the spill stack. This can have whatever meaning the user of this library desires; it is not used directly by the allocation code.

stackSlotSize :: Int

The size of a stack slot in bytes. This should be the same or larger than the size of a register.

stackSlots :: Map (Maybe VarId) Int

A mapping of variables to their stack slot offsets. The special variable Nothing is used for temporary storage, for example when swapping registers through the stack.

newSpillStack :: Int -> Int -> SpillStack Source

Create a new SpillStack, given an offset and slot size.

getStackSlot :: Maybe VarId -> Env Int Source

Given a variable identifier, determine its spill stack offset. The value Nothing refers to the temporary stack slot.