Safe Haskell | None |
---|---|
Language | Haskell98 |
Base LLVM Code Generation module
Contains functions useful through out the code generator.
- type LlvmCmmDecl = GenCmmDecl [LlvmData] (Maybe CmmStatics) (ListGraph LlvmStatement)
- type LlvmBasicBlock = GenBasicBlock LlvmStatement
- type LiveGlobalRegs = [GlobalReg]
- type LlvmUnresData = (CLabel, Section, LlvmType, [UnresStatic])
- type LlvmData = ([LMGlobal], [LlvmType])
- type UnresLabel = CmmLit
- type UnresStatic = Either UnresLabel LlvmStatic
- type LlvmVersion = Int
- defaultLlvmVersion :: LlvmVersion
- minSupportLlvmVersion :: LlvmVersion
- maxSupportLlvmVersion :: LlvmVersion
- data LlvmM a
- runLlvm :: DynFlags -> LlvmVersion -> BufHandle -> UniqSupply -> LlvmM () -> IO ()
- liftStream :: Stream IO a x -> Stream LlvmM a x
- withClearVars :: LlvmM a -> LlvmM a
- varLookup :: Uniquable key => key -> LlvmM (Maybe LlvmType)
- varInsert :: Uniquable key => key -> LlvmType -> LlvmM ()
- markStackReg :: GlobalReg -> LlvmM ()
- checkStackReg :: GlobalReg -> LlvmM Bool
- funLookup :: Uniquable key => key -> LlvmM (Maybe LlvmType)
- funInsert :: Uniquable key => key -> LlvmType -> LlvmM ()
- getLlvmVer :: LlvmM LlvmVersion
- getDynFlags :: HasDynFlags m => m DynFlags
- getDynFlag :: (DynFlags -> a) -> LlvmM a
- getLlvmPlatform :: LlvmM Platform
- dumpIfSetLlvm :: DumpFlag -> String -> SDoc -> LlvmM ()
- renderLlvm :: SDoc -> LlvmM ()
- runUs :: UniqSM a -> LlvmM a
- markUsedVar :: LlvmVar -> LlvmM ()
- getUsedVars :: LlvmM [LlvmVar]
- ghcInternalFunctions :: LlvmM ()
- getMetaUniqueId :: LlvmM Int
- setUniqMeta :: Unique -> Int -> LlvmM ()
- getUniqMeta :: Unique -> LlvmM (Maybe Int)
- freshSectionId :: LlvmM Int
- cmmToLlvmType :: CmmType -> LlvmType
- widthToLlvmFloat :: Width -> LlvmType
- widthToLlvmInt :: Width -> LlvmType
- llvmFunTy :: LiveGlobalRegs -> LlvmM LlvmType
- llvmFunSig :: LiveGlobalRegs -> CLabel -> LlvmLinkageType -> LlvmM LlvmFunctionDecl
- llvmStdFunAttrs :: [LlvmFuncAttr]
- llvmFunAlign :: DynFlags -> LMAlign
- llvmInfAlign :: DynFlags -> LMAlign
- llvmPtrBits :: DynFlags -> Int
- mkLlvmFunc :: LiveGlobalRegs -> CLabel -> LlvmLinkageType -> LMSection -> LlvmBlocks -> LlvmM LlvmFunction
- tysToParams :: [LlvmType] -> [LlvmParameter]
- strCLabel_llvm :: CLabel -> LlvmM LMString
- strDisplayName_llvm :: CLabel -> LlvmM LMString
- strProcedureName_llvm :: CLabel -> LlvmM LMString
- getGlobalPtr :: LMString -> LlvmM LlvmVar
- generateAliases :: LlvmM ([LMGlobal], [LlvmType])
Documentation
type LlvmCmmDecl = GenCmmDecl [LlvmData] (Maybe CmmStatics) (ListGraph LlvmStatement) Source
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 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 UnresStatic = Either UnresLabel LlvmStatic Source
type LlvmVersion = Int Source
LLVM Version Number
defaultLlvmVersion :: LlvmVersion Source
The LLVM Version we assume if we don't know
The Llvm monad. Wraps LlvmEnv
state as well as the IO
monad
runLlvm :: DynFlags -> LlvmVersion -> BufHandle -> UniqSupply -> LlvmM () -> IO () Source
Get initial Llvm environment.
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
getDynFlags :: HasDynFlags m => m DynFlags Source
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
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
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
llvmFunSig :: LiveGlobalRegs -> CLabel -> LlvmLinkageType -> LlvmM LlvmFunctionDecl Source
Llvm Function signature
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.
generateAliases :: 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!