Safe Haskell | None |
---|
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 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 LlvmEnv
- initLlvmEnv :: DynFlags -> LlvmEnv
- clearVars :: LlvmEnv -> LlvmEnv
- varLookup :: Uniquable key => key -> LlvmEnv -> Maybe LlvmType
- varInsert :: Uniquable key => key -> LlvmType -> LlvmEnv -> LlvmEnv
- funLookup :: Uniquable key => key -> LlvmEnv -> Maybe LlvmType
- funInsert :: Uniquable key => key -> LlvmType -> LlvmEnv -> LlvmEnv
- getLlvmVer :: LlvmEnv -> LlvmVersion
- setLlvmVer :: LlvmVersion -> LlvmEnv -> LlvmEnv
- getLlvmPlatform :: LlvmEnv -> Platform
- getDflags :: LlvmEnv -> DynFlags
- ghcInternalFunctions :: [(LMString, LlvmFunctionDecl)]
- cmmToLlvmType :: CmmType -> LlvmType
- widthToLlvmFloat :: Width -> LlvmType
- widthToLlvmInt :: Width -> LlvmType
- llvmFunTy :: LlvmType
- llvmFunSig :: LlvmEnv -> CLabel -> LlvmLinkageType -> LlvmFunctionDecl
- llvmStdFunAttrs :: [LlvmFuncAttr]
- llvmFunAlign :: LMAlign
- llvmInfAlign :: LMAlign
- llvmPtrBits :: Int
- mkLlvmFunc :: LlvmEnv -> CLabel -> LlvmLinkageType -> LMSection -> LlvmBlocks -> LlvmFunction
- tysToParams :: [LlvmType] -> [LlvmParameter]
- strCLabel_llvm :: LlvmEnv -> CLabel -> LMString
- genCmmLabelRef :: LlvmEnv -> CLabel -> LMGlobal
- genStringLabelRef :: LMString -> LMGlobal
Documentation
type LlvmCmmDecl = GenCmmDecl [LlvmData] (Maybe CmmStatics) (ListGraph LlvmStatement)Source
type LlvmUnresData = (CLabel, Section, LlvmType, [UnresStatic])Source
Unresolved code. Of the form: (data label, data type, unresolved data)
type UnresLabel = CmmLitSource
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 = IntSource
LLVM Version Number
defaultLlvmVersion :: LlvmVersionSource
The LLVM Version we assume if we don't know
initLlvmEnv :: DynFlags -> LlvmEnvSource
Get initial Llvm environment.
varLookup :: Uniquable key => key -> LlvmEnv -> Maybe LlvmTypeSource
Lookup local variables in the environment.
varInsert :: Uniquable key => key -> LlvmType -> LlvmEnv -> LlvmEnvSource
Insert local variables into the environment.
funLookup :: Uniquable key => key -> LlvmEnv -> Maybe LlvmTypeSource
Lookup functions in the environment.
funInsert :: Uniquable key => key -> LlvmType -> LlvmEnv -> LlvmEnvSource
Insert functions into the environment.
getLlvmVer :: LlvmEnv -> LlvmVersionSource
Get the LLVM version we are generating code for
setLlvmVer :: LlvmVersion -> LlvmEnv -> LlvmEnvSource
Set the LLVM version we are generating code for
getLlvmPlatform :: LlvmEnv -> PlatformSource
Get the platform we are generating code for
ghcInternalFunctions :: [(LMString, LlvmFunctionDecl)]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.
cmmToLlvmType :: CmmType -> LlvmTypeSource
Translate a basic CmmType to an LlvmType.
widthToLlvmFloat :: Width -> LlvmTypeSource
Translate a Cmm Float Width to a LlvmType.
widthToLlvmInt :: Width -> LlvmTypeSource
Translate a Cmm Bit Width to a LlvmType.
llvmFunSig :: LlvmEnv -> CLabel -> LlvmLinkageType -> LlvmFunctionDeclSource
Llvm Function signature
llvmStdFunAttrs :: [LlvmFuncAttr]Source
Llvm standard fun attributes
Alignment to use for functions
Alignment to use for into tables
Pointer width
mkLlvmFunc :: LlvmEnv -> CLabel -> LlvmLinkageType -> LMSection -> LlvmBlocks -> LlvmFunctionSource
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)
genCmmLabelRef :: LlvmEnv -> CLabel -> LMGlobalSource
Create an external definition for a CLabel
defined in another module.
genStringLabelRef :: LMString -> LMGlobalSource
As above (genCmmLabelRef
) but taking a LMString
, not CLabel
.