Our extended FCode monad.
- newtype ExtFCode a = EC {}
- type ExtCode = ExtFCode ()
- data Named
- type Env = UniqFM Named
- loopDecls :: ExtFCode a -> ExtFCode a
- getEnv :: ExtFCode Env
- newLocal :: CmmType -> FastString -> ExtFCode LocalReg
- newLabel :: FastString -> ExtFCode BlockId
- newFunctionName :: FastString -> PackageId -> ExtCode
- newImport :: (FastString, CLabel) -> ExtFCode ()
- lookupLabel :: FastString -> ExtFCode BlockId
- lookupName :: FastString -> ExtFCode CmmExpr
- code :: FCode a -> ExtFCode a
- code2 :: (FCode (Decls, b) -> FCode ((Decls, b), c)) -> ExtFCode b -> ExtFCode c
- nopEC :: ExtFCode ()
- stmtEC :: CmmStmt -> ExtFCode ()
- stmtsEC :: [CmmStmt] -> ExtFCode ()
- getCgStmtsEC :: ExtFCode a -> ExtFCode CgStmts
- getCgStmtsEC' :: ExtFCode a -> ExtFCode (a, CgStmts)
- forkLabelledCodeEC :: ExtFCode a -> ExtFCode BlockId
Documentation
Does a computation in the FCode monad, with a current environment and a list of local declarations. Returns the resulting list of declarations.
The environment contains variable definitions or blockids.
loopDecls :: ExtFCode a -> ExtFCode aSource
Takes the variable decarations and imports from the monad and makes an environment, which is looped back into the computation. In this way, we can have embedded declarations that scope over the whole procedure, and imports that scope over the entire module. Discards the local declaration contained within decl'
:: CmmType | data type |
-> FastString | name of variable |
-> ExtFCode LocalReg | register holding the value |
Create a fresh local variable of a given type.
newLabel :: FastString -> ExtFCode BlockIdSource
Allocate a fresh label.
:: FastString | name of the function |
-> PackageId | package of the current module |
-> ExtCode |
Add add a local function to the environment.
newImport :: (FastString, CLabel) -> ExtFCode ()Source
Add an imported foreign label to the list of local declarations. If this is done at the start of the module the declaration will scope over the whole module.
lookupLabel :: FastString -> ExtFCode BlockIdSource
Lookup the BlockId bound to the label with this name. If one hasn't been bound yet, create a fresh one based on the Unique of the name.
lookupName :: FastString -> ExtFCode CmmExprSource
Lookup the location of a named variable. Unknown names are treated as if they had been 'import'ed from the runtime system. This saves us a lot of bother in the RTS sources, at the expense of deferring some errors to link time.
getCgStmtsEC :: ExtFCode a -> ExtFCode CgStmtsSource
Get the generated statements out of the monad state.
getCgStmtsEC' :: ExtFCode a -> ExtFCode (a, CgStmts)Source
Get the generated statements, and the return value out of the monad state.
forkLabelledCodeEC :: ExtFCode a -> ExtFCode BlockIdSource
Emit a chunk of code outside the instruction stream, and return its block id.