Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Base LLVM Code Generation module
Contains functions useful through out the code generator.
Synopsis
- type LlvmCmmDecl = GenCmmDecl [LlvmData] (Maybe RawCmmStatics) (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
- data LlvmM a
- runLlvm :: Logger -> LlvmCgConfig -> LlvmVersion -> BufHandle -> LlvmM a -> IO a
- 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
- dumpIfSetLlvm :: DumpFlag -> String -> DumpFormat -> SDoc -> LlvmM ()
- renderLlvm :: SDoc -> LlvmM ()
- markUsedVar :: LlvmVar -> LlvmM ()
- getUsedVars :: LlvmM [LlvmVar]
- ghcInternalFunctions :: LlvmM ()
- getPlatform :: LlvmM Platform
- getConfig :: LlvmM LlvmCgConfig
- getMetaUniqueId :: LlvmM MetaId
- setUniqMeta :: Unique -> MetaId -> LlvmM ()
- getUniqMeta :: Unique -> LlvmM (Maybe MetaId)
- liftIO :: IO a -> LlvmM a
- cmmToLlvmType :: CmmType -> LlvmType
- widthToLlvmFloat :: Width -> LlvmType
- widthToLlvmInt :: Width -> LlvmType
- llvmFunTy :: LiveGlobalRegs -> LlvmM LlvmType
- llvmFunSig :: LiveGlobalRegs -> CLabel -> LlvmLinkageType -> LlvmM LlvmFunctionDecl
- llvmFunArgs :: Platform -> LiveGlobalRegs -> [LlvmVar]
- llvmStdFunAttrs :: [LlvmFuncAttr]
- llvmFunAlign :: Platform -> LMAlign
- llvmInfAlign :: Platform -> LMAlign
- llvmPtrBits :: Platform -> Int
- tysToParams :: [LlvmType] -> [LlvmParameter]
- llvmFunSection :: LlvmCgConfig -> LMString -> LMSection
- padLiveArgs :: Platform -> LiveGlobalRegs -> LiveGlobalRegs
- isFPR :: GlobalReg -> Bool
- strCLabel_llvm :: CLabel -> LlvmM LMString
- getGlobalPtr :: LMString -> LlvmM LlvmVar
- generateExternDecls :: LlvmM ([LMGlobal], [LlvmType])
- aliasify :: LMGlobal -> LlvmM [LMGlobal]
- llvmDefLabel :: LMString -> LMString
Documentation
type LlvmCmmDecl = GenCmmDecl [LlvmData] (Maybe RawCmmStatics) (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 #
The Llvm monad. Wraps LlvmEnv
state as well as the IO
monad
runLlvm :: Logger -> LlvmCgConfig -> LlvmVersion -> BufHandle -> LlvmM a -> IO a 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
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
dumpIfSetLlvm :: DumpFlag -> String -> DumpFormat -> 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.
getPlatform :: LlvmM Platform Source #
Get target platform
getMetaUniqueId :: LlvmM MetaId Source #
Allocate a new global unnamed metadata identifier
liftIO :: IO a -> LlvmM a Source #
Lifting of IO actions. Not exported, as we want to encapsulate IO.
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.
llvmFunSig :: LiveGlobalRegs -> CLabel -> LlvmLinkageType -> LlvmM LlvmFunctionDecl Source #
Llvm Function signature
llvmFunArgs :: Platform -> LiveGlobalRegs -> [LlvmVar] Source #
A Function's arguments
llvmStdFunAttrs :: [LlvmFuncAttr] Source #
Llvm standard fun attributes
llvmFunAlign :: Platform -> LMAlign Source #
Alignment to use for functions
llvmInfAlign :: Platform -> LMAlign Source #
Alignment to use for into tables
llvmPtrBits :: Platform -> Int Source #
Pointer width
tysToParams :: [LlvmType] -> [LlvmParameter] Source #
Convert a list of types to a list of function parameters (each with no parameter attributes)
llvmFunSection :: LlvmCgConfig -> LMString -> LMSection Source #
Section to use for a function
padLiveArgs :: Platform -> LiveGlobalRegs -> LiveGlobalRegs Source #
Return a list of "padding" registers for LLVM function calls.
When we generate LLVM function signatures, we can't just make any register alive on function entry. Instead, we need to insert fake arguments of the same register class until we are sure that one of them is mapped to the register we want alive. E.g. to ensure that F5 is alive, we may need to insert fake arguments mapped to F1, F2, F3 and F4.
Invariant: Cmm FPR regs with number "n" maps to real registers with number "n" If the calling convention uses registers in a different order or if the invariant doesn't hold, this code probably won't be correct.
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.
llvmDefLabel :: LMString -> LMString Source #
Derive the definition label. It has an identified structure type.