ghc-7.0.3: The GHC API

CgExtCode

Description

Our extended FCode monad.

Synopsis

Documentation

newtype ExtFCode a Source

Does a computation in the FCode monad, with a current environment and a list of local declarations. Returns the resulting list of declarations.

Constructors

EC 

Fields

unEC :: Env -> Decls -> FCode (Decls, a)
 

Instances

data Named Source

The environment contains variable definitions or blockids.

Constructors

Var CmmExpr

Holds CmmLit(CmmLabel ..) which gives the label type, eg, RtsLabel, ForeignLabel, CmmLabel etc.

Fun PackageId

A function name from this package

Label BlockId

A blockid of some code or data.

type Env = UniqFM NamedSource

An environment of named things.

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'

getEnv :: ExtFCode EnvSource

Get the current environment from the monad.

newLocalSource

Arguments

:: 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.

newFunctionNameSource

Arguments

:: 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.

code :: FCode a -> ExtFCode aSource

Lift an FCode computation into the ExtFCode monad

code2 :: (FCode (Decls, b) -> FCode ((Decls, b), c)) -> ExtFCode b -> ExtFCode cSource

nopEC :: ExtFCode ()Source

Do nothing in the ExtFCode monad.

stmtEC :: CmmStmt -> ExtFCode ()Source

Accumulate a CmmStmt into the monad state.

stmtsEC :: [CmmStmt] -> ExtFCode ()Source

Accumulate some CmmStmts into the monad state.

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.