ghc-7.10.3: The GHC API

Safe HaskellNone
LanguageHaskell2010

LlvmCodeGen.Base

Description

Base LLVM Code Generation module

Contains functions useful through out the code generator.

Synopsis

Documentation

type LiveGlobalRegs = [GlobalReg] Source

Global registers live on proc entry

type LlvmUnresData = (CLabel, Section, LlvmType, [UnresStatic]) Source

Unresolved code. Of the form: (data label, data type, unresolved data)

type LlvmData = ([LMGlobal], [LlvmType]) Source

Top level LLVM Data (globals and type aliases)

type UnresLabel = CmmLit Source

An unresolved Label.

Labels are unresolved when we haven't yet determined if they are defined in the module we are currently compiling, or an external one.

type LlvmVersion = Int Source

LLVM Version Number

defaultLlvmVersion :: LlvmVersion Source

The LLVM Version we assume if we don't know

data LlvmM a Source

The Llvm monad. Wraps LlvmEnv state as well as the IO monad

runLlvm :: DynFlags -> LlvmVersion -> BufHandle -> UniqSupply -> LlvmM () -> IO () Source

Get initial Llvm environment.

liftStream :: Stream IO a x -> Stream LlvmM a x Source

Lift a stream into the LlvmM monad

withClearVars :: LlvmM a -> LlvmM a Source

Clear variables from the environment for a subcomputation

varLookup :: Uniquable key => key -> LlvmM (Maybe LlvmType) Source

Lookup variables or functions in the environment.

varInsert :: Uniquable key => key -> LlvmType -> LlvmM () Source

Insert variables or functions into the environment.

markStackReg :: GlobalReg -> LlvmM () Source

Set a register as allocated on the stack

checkStackReg :: GlobalReg -> LlvmM Bool Source

Check whether a register is allocated on the stack

funLookup :: Uniquable key => key -> LlvmM (Maybe LlvmType) Source

Lookup variables or functions in the environment.

funInsert :: Uniquable key => key -> LlvmType -> LlvmM () Source

Insert variables or functions into the environment.

getLlvmVer :: LlvmM LlvmVersion Source

Get the LLVM version we are generating code for

getDynFlag :: (DynFlags -> a) -> LlvmM a Source

Get the platform we are generating code for

getLlvmPlatform :: LlvmM Platform Source

Get the platform we are generating code for

dumpIfSetLlvm :: DumpFlag -> String -> SDoc -> LlvmM () Source

Dumps the document if the corresponding flag has been set by the user

renderLlvm :: SDoc -> LlvmM () Source

Prints the given contents to the output handle

runUs :: UniqSM a -> LlvmM a Source

Run a UniqSM action with our unique supply

markUsedVar :: LlvmVar -> LlvmM () Source

Marks a variable as "used"

getUsedVars :: LlvmM [LlvmVar] Source

Return all variables marked as "used" so far

ghcInternalFunctions :: LlvmM () Source

Here we pre-initialise some functions that are used internally by GHC so as to make sure they have the most general type in the case that user code also uses these functions but with a different type than GHC internally. (Main offender is treating return type as void instead of 'void *'). Fixes trac #5486.

getMetaUniqueId :: LlvmM Int Source

Allocate a new global unnamed metadata identifier

setUniqMeta :: Unique -> Int -> LlvmM () Source

Sets metadata node for a given unique

getUniqMeta :: Unique -> LlvmM (Maybe Int) Source

Gets metadata node for given unique

freshSectionId :: LlvmM Int Source

Returns a fresh section ID

cmmToLlvmType :: CmmType -> LlvmType Source

Translate a basic CmmType to an LlvmType.

widthToLlvmFloat :: Width -> LlvmType Source

Translate a Cmm Float Width to a LlvmType.

widthToLlvmInt :: Width -> LlvmType Source

Translate a Cmm Bit Width to a LlvmType.

llvmFunTy :: LiveGlobalRegs -> LlvmM LlvmType Source

Llvm Function type for Cmm function

llvmStdFunAttrs :: [LlvmFuncAttr] Source

Llvm standard fun attributes

llvmFunAlign :: DynFlags -> LMAlign Source

Alignment to use for functions

llvmInfAlign :: DynFlags -> LMAlign Source

Alignment to use for into tables

llvmPtrBits :: DynFlags -> Int Source

Pointer width

mkLlvmFunc :: LiveGlobalRegs -> CLabel -> LlvmLinkageType -> LMSection -> LlvmBlocks -> LlvmM LlvmFunction Source

Create a Haskell function in LLVM.

tysToParams :: [LlvmType] -> [LlvmParameter] Source

Convert a list of types to a list of function parameters (each with no parameter attributes)

getGlobalPtr :: LMString -> LlvmM LlvmVar Source

Create/get a pointer to a global value. Might return an alias if the value in question hasn't been defined yet. We especially make no guarantees on the type of the returned pointer.

generateExternDecls :: LlvmM ([LMGlobal], [LlvmType]) Source

Generate definitions for aliases forward-referenced by getGlobalPtr.

Must be called at a point where we are sure that no new global definitions will be generated anymore!

aliasify :: LMGlobal -> LlvmM [LMGlobal] Source

Here we take a global variable definition, rename it with a $def suffix, and generate the appropriate alias.