| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
LinearScan.Hoopl.DSL
- compile :: (NonLocal n, HooplNode n) => String -> Program n -> SimpleUniqueMonad (Graph n C C, Label)
- data ProgramF n = FreeBlock {
- labelEntry :: Label
- labelBody :: EndNode n
- type Program n = FreeT ((,) (ProgramF n)) Asm ()
- type Labels = Map String Label
- getLabel :: String -> Asm Label
- type Asm = StateT Labels SimpleUniqueMonad
- type Nodes n a = Free ((,) (n O O)) a
- nodesToList :: Nodes n a -> (a, [n O O])
- type BodyNode n = Nodes n ()
- bodyNode :: n O O -> BodyNode n
- type EndNode n = Nodes n (Asm (n O C))
- endNode :: Asm (n O C) -> EndNode n
- label :: String -> EndNode n -> Program n
- jump :: HooplNode n => String -> EndNode n
- data SpillStack = SpillStack {
- stackPtr :: Int
- stackSlotSize :: Int
- stackSlots :: Map (Maybe VarId) Int
- newSpillStack :: Int -> Int -> SpillStack
- getStackSlot :: Maybe VarId -> Env Int
- type Env = State ([Int], SpillStack)
Compiling Assembly programs
Arguments
| :: (NonLocal n, HooplNode n) | |
| => String | Entry label name |
| -> Program n | The assembly language program |
| -> SimpleUniqueMonad (Graph n C C, 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
A ProgramF abstracts a generic basic block: a series of Nodes,
associated with a label, that ends in a final node.
Constructors
| FreeBlock | |
Fields
| |
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.
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
| |
Instances
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.
type Env = State ([Int], SpillStack) Source