Safe Haskell | None |
---|---|
Language | Haskell98 |
The LLVM Type System.
- data LMGlobal = LMGlobal {}
- type LMString = FastString
- type LlvmAlias = (LMString, LlvmType)
- data LlvmType
- ppParams :: LlvmParameterListType -> [LlvmParameter] -> SDoc
- type LMSection = Maybe LMString
- type LMAlign = Maybe Int
- data LMConst
- data LlvmVar
- data LlvmLit
- data LlvmStatic
- = LMComment LMString
- | LMStaticLit LlvmLit
- | LMUninitType LlvmType
- | LMStaticStr LMString LlvmType
- | LMStaticArray [LlvmStatic] LlvmType
- | LMStaticStruc [LlvmStatic] LlvmType
- | LMStaticPointer LlvmVar
- | LMBitc LlvmStatic LlvmType
- | LMPtoI LlvmStatic LlvmType
- | LMAdd LlvmStatic LlvmStatic
- | LMSub LlvmStatic LlvmStatic
- pprStaticArith :: LlvmStatic -> LlvmStatic -> LitString -> LitString -> String -> SDoc
- ppName :: LlvmVar -> SDoc
- ppPlainName :: LlvmVar -> SDoc
- ppLit :: LlvmLit -> SDoc
- getVarType :: LlvmVar -> LlvmType
- getLitType :: LlvmLit -> LlvmType
- getStatType :: LlvmStatic -> LlvmType
- getLink :: LlvmVar -> LlvmLinkageType
- pLift :: LlvmType -> LlvmType
- pVarLift :: LlvmVar -> LlvmVar
- pLower :: LlvmType -> LlvmType
- pVarLower :: LlvmVar -> LlvmVar
- isInt :: LlvmType -> Bool
- isFloat :: LlvmType -> Bool
- isPointer :: LlvmType -> Bool
- isVector :: LlvmType -> Bool
- isGlobal :: LlvmVar -> Bool
- llvmWidthInBits :: DynFlags -> LlvmType -> Int
- i128 :: LlvmType
- i8Ptr :: LlvmType
- i1 :: LlvmType
- i8 :: LlvmType
- i16 :: LlvmType
- i32 :: LlvmType
- i64 :: LlvmType
- llvmWord :: DynFlags -> LlvmType
- llvmWordPtr :: DynFlags -> LlvmType
- data LlvmFunctionDecl = LlvmFunctionDecl {}
- type LlvmFunctionDecls = [LlvmFunctionDecl]
- type LlvmParameter = (LlvmType, [LlvmParamAttr])
- data LlvmParamAttr
- data LlvmFuncAttr
- data LlvmCallType
- data LlvmCallConvention
- data LlvmParameterListType
- data LlvmLinkageType
- data LlvmMachOp
- data LlvmCmpOp
- data LlvmCastOp
- ppDouble :: Double -> SDoc
- narrowFp :: Double -> Float
- widenFp :: Float -> Double
- ppFloat :: Float -> SDoc
- fixEndian :: [a] -> [a]
- ppCommaJoin :: Outputable a => [a] -> SDoc
- ppSpaceJoin :: Outputable a => [a] -> SDoc
LLVM Basic Types and Variables
A global mutable variable. Maybe defined or external
LMGlobal | |
|
type LMString = FastString Source
A String in LLVM
Llvm Types
LMInt Int | An integer with a given width in bits. |
LMFloat | 32 bit floating point |
LMDouble | 64 bit floating point |
LMFloat80 | 80 bit (x86 only) floating point |
LMFloat128 | 128 bit floating point |
LMPointer LlvmType | A pointer to a |
LMArray Int LlvmType | An array of |
LMVector Int LlvmType | A vector of |
LMLabel | A |
LMVoid | Void type |
LMStruct [LlvmType] | Structure type |
LMAlias LlvmAlias | A type alias |
LMMetadata | LLVM Metadata |
LMFunction LlvmFunctionDecl | Function type, used to create pointers to functions |
ppParams :: LlvmParameterListType -> [LlvmParameter] -> SDoc Source
type LMSection = Maybe LMString Source
An LLVM section definition. If Nothing then let LLVM decide the section
LLVM Variables
LMGlobalVar LMString LlvmType LlvmLinkageType LMSection LMAlign LMConst | Variables with a global scope. |
LMLocalVar Unique LlvmType | Variables local to a function or parameters. |
LMNLocalVar LMString LlvmType | Named local variables. Sometimes we need to be able to explicitly name variables (e.g for function arguments). |
LMLitVar LlvmLit | A constant variable |
Llvm Literal Data.
These can be used inline in expressions.
LMIntLit Integer LlvmType | Refers to an integer constant (i64 42). |
LMFloatLit Double LlvmType | Floating point literal |
LMNullLit LlvmType | Literal NULL, only applicable to pointer types |
LMVectorLit [LlvmLit] | Vector literal |
LMUndefLit LlvmType | Undefined value, random bit pattern. Useful for optimisations. |
data LlvmStatic Source
Llvm Static Data.
These represent the possible global level variables and constants.
LMComment LMString | A comment in a static section |
LMStaticLit LlvmLit | A static variant of a literal value |
LMUninitType LlvmType | For uninitialised data |
LMStaticStr LMString LlvmType | Defines a static |
LMStaticArray [LlvmStatic] LlvmType | A static array |
LMStaticStruc [LlvmStatic] LlvmType | A static structure type |
LMStaticPointer LlvmVar | A pointer to other data |
LMBitc LlvmStatic LlvmType | Pointer to Pointer conversion |
LMPtoI LlvmStatic LlvmType | Pointer to Integer conversion |
LMAdd LlvmStatic LlvmStatic | Constant addition operation |
LMSub LlvmStatic LlvmStatic | Constant subtraction operation |
pprStaticArith :: LlvmStatic -> LlvmStatic -> LitString -> LitString -> String -> SDoc Source
Operations on LLVM Basic Types and Variables
ppName :: LlvmVar -> SDoc Source
Return the variable name or value of the LlvmVar
in Llvm IR textual representation (e.g. @x
, %y
or 42
).
ppPlainName :: LlvmVar -> SDoc Source
Return the variable name or value of the LlvmVar
in a plain textual representation (e.g. x
, y
or 42
).
getStatType :: LlvmStatic -> LlvmType Source
Return the LlvmType
of the LlvmStatic
getLink :: LlvmVar -> LlvmLinkageType Source
Return the LlvmLinkageType
for a LlvmVar
pLower :: LlvmType -> LlvmType Source
Remove the pointer indirection of the supplied type. Only LMPointer
constructors can be lowered.
llvmWidthInBits :: DynFlags -> LlvmType -> Int Source
Width in bits of an LlvmType
, returns 0 if not applicable
Shortcut for Common Types
llvmWordPtr :: DynFlags -> LlvmType Source
The target architectures word size
LLVM Function Types
data LlvmFunctionDecl Source
An LLVM Function
LlvmFunctionDecl | |
|
type LlvmFunctionDecls = [LlvmFunctionDecl] Source
type LlvmParameter = (LlvmType, [LlvmParamAttr]) Source
data LlvmParamAttr Source
LLVM Parameter Attributes.
Parameter attributes are used to communicate additional information about the result or parameters of a function
ZeroExt | This indicates to the code generator that the parameter or return value should be zero-extended to a 32-bit value by the caller (for a parameter) or the callee (for a return value). |
SignExt | This indicates to the code generator that the parameter or return value should be sign-extended to a 32-bit value by the caller (for a parameter) or the callee (for a return value). |
InReg | This indicates that this parameter or return value should be treated in a special target-dependent fashion during while emitting code for a function call or return (usually, by putting it in a register as opposed to memory). |
ByVal | This indicates that the pointer parameter should really be passed by value to the function. |
SRet | This indicates that the pointer parameter specifies the address of a structure that is the return value of the function in the source program. |
NoAlias | This indicates that the pointer does not alias any global or any other parameter. |
NoCapture | This indicates that the callee does not make any copies of the pointer that outlive the callee itself |
Nest | This indicates that the pointer parameter can be excised using the trampoline intrinsics. |
data LlvmFuncAttr Source
Llvm Function Attributes.
Function attributes are set to communicate additional information about a function. Function attributes are considered to be part of the function, not of the function type, so functions with different parameter attributes can have the same function type. Functions can have multiple attributes.
Descriptions taken from http://llvm.org/docs/LangRef.html#fnattrs
AlwaysInline | This attribute indicates that the inliner should attempt to inline this function into callers whenever possible, ignoring any active inlining size threshold for this caller. |
InlineHint | This attribute indicates that the source code contained a hint that inlining this function is desirable (such as the "inline" keyword in C/C++). It is just a hint; it imposes no requirements on the inliner. |
NoInline | This attribute indicates that the inliner should never inline this function in any situation. This attribute may not be used together with the alwaysinline attribute. |
OptSize | This attribute suggests that optimization passes and code generator passes make choices that keep the code size of this function low, and otherwise do optimizations specifically to reduce code size. |
NoReturn | This function attribute indicates that the function never returns normally. This produces undefined behavior at runtime if the function ever does dynamically return. |
NoUnwind | This function attribute indicates that the function never returns with an unwind or exceptional control flow. If the function does unwind, its runtime behavior is undefined. |
ReadNone | This attribute indicates that the function computes its result (or decides to unwind an exception) based strictly on its arguments, without dereferencing any pointer arguments or otherwise accessing any mutable state (e.g. memory, control registers, etc) visible to caller functions. It does not write through any pointer arguments (including byval arguments) and never changes any state visible to callers. This means that it cannot unwind exceptions by calling the C++ exception throwing methods, but could use the unwind instruction. |
ReadOnly | This attribute indicates that the function does not write through any pointer arguments (including byval arguments) or otherwise modify any state (e.g. memory, control registers, etc) visible to caller functions. It may dereference pointer arguments and read state that may be set in the caller. A readonly function always returns the same value (or unwinds an exception identically) when called with the same set of arguments and global state. It cannot unwind an exception by calling the C++ exception throwing methods, but may use the unwind instruction. |
Ssp | This attribute indicates that the function should emit a stack smashing protector. It is in the form of a "canary"—a random value placed on the stack before the local variables that's checked upon return from the function to see if it has been overwritten. A heuristic is used to determine if a function needs stack protectors or not. If a function that has an ssp attribute is inlined into a function that doesn't have an ssp attribute, then the resulting function will have an ssp attribute. |
SspReq | This attribute indicates that the function should always emit a stack smashing protector. This overrides the ssp function attribute. If a function that has an sspreq attribute is inlined into a function that doesn't have an sspreq attribute or which has an ssp attribute, then the resulting function will have an sspreq attribute. |
NoRedZone | This attribute indicates that the code generator should not use a red zone, even if the target-specific ABI normally permits it. |
NoImplicitFloat | This attributes disables implicit floating point instructions. |
Naked | This attribute disables prologue / epilogue emission for the function. This can have very system-specific consequences. |
data LlvmCallType Source
Different types to call a function.
data LlvmCallConvention Source
Different calling conventions a function can use.
CC_Ccc | The C calling convention. This calling convention (the default if no other calling convention is specified) matches the target C calling conventions. This calling convention supports varargs function calls and tolerates some mismatch in the declared prototype and implemented declaration of the function (as does normal C). |
CC_Fastcc | This calling convention attempts to make calls as fast as possible (e.g. by passing things in registers). This calling convention allows the target to use whatever tricks it wants to produce fast code for the target, without having to conform to an externally specified ABI (Application Binary Interface). Implementations of this convention should allow arbitrary tail call optimization to be supported. This calling convention does not support varargs and requires the prototype of al callees to exactly match the prototype of the function definition. |
CC_Coldcc | This calling convention attempts to make code in the caller as efficient as possible under the assumption that the call is not commonly executed. As such, these calls often preserve all registers so that the call does not break any live ranges in the caller side. This calling convention does not support varargs and requires the prototype of all callees to exactly match the prototype of the function definition. |
CC_Ncc Int | Any calling convention may be specified by number, allowing target-specific calling conventions to be used. Target specific calling conventions start at 64. |
CC_X86_Stdcc | X86 Specific |
data LlvmParameterListType Source
Functions can have a fixed amount of parameters, or a variable amount.
data LlvmLinkageType Source
Linkage type of a symbol.
The description of the constructors is copied from the Llvm Assembly Language Reference Manual http://www.llvm.org/docs/LangRef.html#linkage, because they correspond to the Llvm linkage types.
Internal | Global values with internal linkage are only directly accessible by
objects in the current module. In particular, linking code into a module
with an internal global value may cause the internal to be renamed as
necessary to avoid collisions. Because the symbol is internal to the
module, all references can be updated. This corresponds to the notion
of the |
LinkOnce | Globals with |
Weak |
|
Appending |
|
ExternWeak | The semantics of this linkage follow the ELF model: the symbol is weak until linked, if not linked, the symbol becomes null instead of being an undefined reference. |
ExternallyVisible | The symbol participates in linkage and can be used to resolve external symbol references. |
External | Alias for |
Private | Symbol is private to the module and should not appear in the symbol table |
LLVM Operations
data LlvmMachOp Source
Llvm binary operators machine operations.
LM_MO_Add | add two integer, floating point or vector values. |
LM_MO_Sub | subtract two ... |
LM_MO_Mul | multiply .. |
LM_MO_UDiv | unsigned integer or vector division. |
LM_MO_SDiv | signed integer .. |
LM_MO_URem | unsigned integer or vector remainder (mod) |
LM_MO_SRem | signed ... |
LM_MO_FAdd | add two floating point or vector values. |
LM_MO_FSub | subtract two ... |
LM_MO_FMul | multiply ... |
LM_MO_FDiv | divide ... |
LM_MO_FRem | remainder ... |
LM_MO_Shl | Left shift |
LM_MO_LShr | Logical shift right Shift right, filling with zero |
LM_MO_AShr | Arithmetic shift right The most significant bits of the result will be equal to the sign bit of the left operand. |
LM_MO_And | AND bitwise logical operation. |
LM_MO_Or | OR bitwise logical operation. |
LM_MO_Xor | XOR bitwise logical operation. |
Llvm compare operations.
LM_CMP_Eq | Equal (Signed and Unsigned) |
LM_CMP_Ne | Not equal (Signed and Unsigned) |
LM_CMP_Ugt | Unsigned greater than |
LM_CMP_Uge | Unsigned greater than or equal |
LM_CMP_Ult | Unsigned less than |
LM_CMP_Ule | Unsigned less than or equal |
LM_CMP_Sgt | Signed greater than |
LM_CMP_Sge | Signed greater than or equal |
LM_CMP_Slt | Signed less than |
LM_CMP_Sle | Signed less than or equal |
LM_CMP_Feq | Float equal |
LM_CMP_Fne | Float not equal |
LM_CMP_Fgt | Float greater than |
LM_CMP_Fge | Float greater than or equal |
LM_CMP_Flt | Float less than |
LM_CMP_Fle | Float less than or equal |
data LlvmCastOp Source
Llvm cast operations.
LM_Trunc | Integer truncate |
LM_Zext | Integer extend (zero fill) |
LM_Sext | Integer extend (sign fill) |
LM_Fptrunc | Float truncate |
LM_Fpext | Float extend |
LM_Fptoui | Float to unsigned Integer |
LM_Fptosi | Float to signed Integer |
LM_Uitofp | Unsigned Integer to Float |
LM_Sitofp | Signed Int to Float |
LM_Ptrtoint | Pointer to Integer |
LM_Inttoptr | Integer to Pointer |
LM_Bitcast | Cast between types where no bit manipulation is needed |
Floating point conversion
ppDouble :: Double -> SDoc Source
Convert a Haskell Double to an LLVM hex encoded floating point form. In Llvm float literals can be printed in a big-endian hexadecimal format, regardless of underlying architecture.
See Note [LLVM Float Types].
Misc functions
ppCommaJoin :: Outputable a => [a] -> SDoc Source
ppSpaceJoin :: Outputable a => [a] -> SDoc Source