Safe Haskell | Safe-Inferred |
---|
- data Module = Module {
- modComments :: [String]
- modAliases :: [TypeAlias]
- modGlobals :: [Global]
- modFwdDecls :: [FunctionDecl]
- modFuncs :: [Function]
- modMDecls :: [MDecl]
- lookupCallConv :: String -> Module -> Maybe CallConv
- data Global
- typeOfGlobal :: Global -> Type
- varOfGlobal :: Global -> Var
- data Static
- = StaticComment String
- | StaticLit Lit
- | StaticUninitType Type
- | StaticStr String Type
- | StaticArray [Static] Type
- | StaticStruct [Static] Type
- | StaticPointer Var
- | StaticBitc Static Type
- | StaticPtoI Static Type
- | StaticAdd Static Static
- | StaticSub Static Static
- typeOfStatic :: Static -> Type
- data FunctionDecl = FunctionDecl {
- declName :: String
- declLinkage :: Linkage
- declCallConv :: CallConv
- declReturnType :: Type
- declParamListType :: ParamListType
- declParams :: [Param]
- declAlign :: Align
- data ParamListType
- data Param = Param {
- paramType :: Type
- paramAttrs :: [ParamAttr]
- data Align
- = AlignNone
- | AlignBytes Integer
- data Function = Function {
- funDecl :: FunctionDecl
- funParams :: [String]
- funAttrs :: [FuncAttr]
- funSection :: Section
- funBlocks :: [Block]
- data Section
- = SectionAuto
- | SectionSpecific String
- data Block = Block {
- blockLabel :: Label
- blockInstrs :: Seq AnnotInstr
- defVarsOfBlock :: Block -> Set Var
- data Label = Label String
- data AnnotInstr = AnnotInstr {
- annotInstr :: Instr
- annotMDecl :: [MDecl]
- annotNil :: Instr -> AnnotInstr
- annotWith :: Instr -> [MDecl] -> AnnotInstr
- data Instr
- = IComment [String]
- | ISet Var Exp
- | INop
- | IPhi Var [(Exp, Label)]
- | IReturn (Maybe Exp)
- | IBranch Label
- | IBranchIf Exp Label Label
- | ISwitch Exp Label [(Lit, Label)]
- | IUnreachable
- | IOp Var Op Exp Exp
- | IConv Var Conv Exp
- | ILoad Var Exp
- | IStore Exp Exp
- | IICmp Var ICond Exp Exp
- | IFCmp Var FCond Exp Exp
- | ICall (Maybe Var) CallType (Maybe CallConv) Type Name [Exp] [FuncAttr]
- branchTargetsOfInstr :: Instr -> Maybe (Set Label)
- defVarOfInstr :: Instr -> Maybe Var
- data Metadata
- data MDecl = MDecl MRef Metadata
- data MRef = MRef Int
- rval :: MDecl -> Metadata
- tbaaNode :: String -> MRef -> Bool -> Metadata
- data Type
- data TypeAlias = TypeAlias String Type
- isInt :: Type -> Bool
- isFloat :: Type -> Bool
- isPointer :: Type -> Bool
- takeBytesOfType :: Integer -> Type -> Maybe Integer
- data Exp
- typeOfExp :: Exp -> Type
- data Var = Var Name Type
- nameOfVar :: Var -> Name
- typeOfVar :: Var -> Type
- data Name
- = NameGlobal String
- | NameLocal String
- data Lit
- typeOfLit :: Lit -> Type
- data Op
- data ICond
- data FCond
- data Conv
- = ConvTrunc
- | ConvZext
- | ConvSext
- | ConvFptrunc
- | ConvFpext
- | ConvFptoui
- | ConvFptosi
- | ConvUintofp
- | ConvSintofp
- | ConvPtrtoint
- | ConvInttoptr
- | ConvBitcast
- data FuncAttr
- = AlwaysInline
- | InlineHint
- | NoInline
- | OptSize
- | NoReturn
- | NoUnwind
- | ReadNone
- | ReadOnly
- | Ssp
- | SspReq
- | NoRedZone
- | NoImplicitFloat
- | Naked
- data ParamAttr
- data CallConv
- = CC_Ccc
- | CC_Fastcc
- | CC_Coldcc
- | CC_Ncc Int
- | CC_X86_Stdcc
- data CallType
- data Linkage
- = Internal
- | LinkOnce
- | Weak
- | Appending
- | ExternWeak
- | ExternallyVisible
- | External
Modules
This is a top level container in LLVM.
Module | |
|
lookupCallConv :: String -> Module -> Maybe CallConvSource
Lookup the calling convention for this function, using the forward declarations as well as the function definitions.
Global variables
A global mutable variable. Maybe defined or external
typeOfGlobal :: Global -> TypeSource
Return the LlvmType
of the LMGlobal
varOfGlobal :: Global -> VarSource
Return the LlvmVar
part of a LMGlobal
Static data
Llvm Static Data. These represent the possible global level variables and constants.
StaticComment String | A comment in a static section. |
StaticLit Lit | A static variant of a literal value. |
StaticUninitType Type | For uninitialised data. |
StaticStr String Type | Defines a static |
StaticArray [Static] Type | A static array. |
StaticStruct [Static] Type | A static structure type. |
StaticPointer Var | A pointer to other data. |
StaticBitc Static Type | Pointer to Pointer conversion. |
StaticPtoI Static Type | Pointer to Integer conversion. |
StaticAdd Static Static | Constant addition operation. |
StaticSub Static Static | Constant subtraction operation. |
typeOfStatic :: Static -> TypeSource
Return the LlvmType
of the LlvmStatic
.
Function declarations
data FunctionDecl Source
An LLVM Function
FunctionDecl | |
|
Eq FunctionDecl | |
Show FunctionDecl | |
Pretty FunctionDecl |
data ParamListType Source
Functions can have a fixed amount of parameters, or a variable amount.
Eq ParamListType | |
Show ParamListType |
Describes a function parameter.
Param | |
|
Functions
A LLVM Function
Function | |
|
The section name to put the function in.
SectionAuto | Let the LLVM decide what section to put this in. |
SectionSpecific String | Put it in this specific section. |
Blocks
A block of LLVM code with an optional annotation.
Block | |
|
defVarsOfBlock :: Block -> Set VarSource
Get the set of LLVM variables that this block defines.
Block labels
Annotated Instructions
data AnnotInstr Source
Instructions annotated with metadata.
AnnotInstr | |
|
Show AnnotInstr | |
Pretty AnnotInstr |
annotNil :: Instr -> AnnotInstrSource
Construct an annotated instruction with no annotations.
annotWith :: Instr -> [MDecl] -> AnnotInstrSource
Annotate an instruction with some metadata.
Instructions
Instructions
IComment [String] | Comment meta-instruction. |
ISet Var Exp | Set meta instruction v1 = value.
This isn't accepted by the real LLVM compiler.
ISet instructions are erased by the |
INop | No operation.
This isn't accepted by the real LLVM compiler.
INop instructions are erased by the |
IPhi Var [(Exp, Label)] | |
IReturn (Maybe Exp) | Return a result. |
IBranch Label | Unconditional branch to the target label. |
IBranchIf Exp Label Label | Conditional branch. |
ISwitch Exp Label [(Lit, Label)] | Mutliway branch. If scruitniee matches one of the literals in the list then jump to the corresponding label, otherwise jump to the default. |
IUnreachable | Informs the optimizer that instructions after this point are unreachable. |
IOp Var Op Exp Exp | |
IConv Var Conv Exp | Cast the variable from to the to type. This is an abstraction of three cast operators in Llvm, inttoptr, prttoint and bitcast. |
ILoad Var Exp | Load a value from memory. |
IStore Exp Exp | Store a value to memory. First expression gives the destination pointer. |
IICmp Var ICond Exp Exp | Integer comparison. |
IFCmp Var FCond Exp Exp | Floating-point comparison. |
ICall (Maybe Var) CallType (Maybe CallConv) Type Name [Exp] [FuncAttr] | Call a function. Only NoReturn, NoUnwind and ReadNone attributes are valid. |
branchTargetsOfInstr :: Instr -> Maybe (Set Label)Source
If this instruction can branch to a label then return the possible targets.
defVarOfInstr :: Instr -> Maybe VarSource
Get the LLVM variable that this instruction assigns to,
or Nothing
if there isn't one.
Metadata
Different types of metadata used in LLVM IR
e.g. debug
, tbaa
, range
, etc.
Maps matadata references to metadata nodes e.g. !2 = !{ metadata id, !0, !i11}
:: String | A unique identifier for the node |
-> MRef | The parent node |
-> Bool | Whether this node represents a const region |
-> Metadata |
Construct a single tbaa node
Expression types
Llvm Types.
TVoid | Void type |
TInt Integer | An integer with a given width in bits. |
TFloat | 32-bit floating point |
TDouble | 64-bit floating point |
TFloat80 | 80 bit (x86 only) floating point |
TFloat128 | 128 bit floating point |
TLabel | A block label. |
TPointer Type | A pointer to another type of thing. |
TArray Integer Type | An array of things. |
TStruct [Type] | A structure type. |
TAlias TypeAlias | A type alias. |
TFunction FunctionDecl | Function type, used to create pointers to functions. |
A type alias.
takeBytesOfType :: Integer -> Type -> Maybe IntegerSource
Calculate the size in bytes of a Type, given the size of pointers.
Expressions
Variables
Names
Names of variables.
NameGlobal String | |
NameLocal String |
Literals
Literal data.
Primitive operators
Binary arithmetic operators.
OpAdd | add two integers, floating point or vector values. |
OpSub | subtract two ... |
OpMul | multiply .. |
OpUDiv | unsigned integer or vector division. |
OpSDiv | signed integer .. |
OpURem | unsigned integer or vector remainder |
OpSRem | signed ... |
OpFAdd | add two floating point or vector values. |
OpFSub | subtract two ... |
OpFMul | multiply ... |
OpFDiv | divide ... |
OpFRem | remainder ... |
OpShl | Left shift. |
OpLShr | Logical shift right |
OpAShr | Arithmetic shift right. The most significant bits of the result will be equal to the sign bit of the left operand. |
OpAnd | AND bitwise logical operation. |
OpOr | OR bitwise logical operation. |
OpXor | XOR bitwise logical operation. |
Integer comparison.
ICondEq | Equal (Signed and Unsigned) |
ICondNe | Not equal (Signed and Unsigned) |
ICondUgt | Unsigned greater than |
ICondUge | Unsigned greater than or equal |
ICondUlt | Unsigned less than |
ICondUle | Unsigned less than or equal |
ICondSgt | Signed greater than |
ICondSge | Signed greater than or equal |
ICondSlt | Signed less than |
ICondSle | Signed less than or equal |
Floating point comparison.
FCondFalse | Always yields false, regardless of operands. |
FCondOeq | Both operands are not a QNAN and op1 is equal to op2. |
FCondOgt | Both operands are not a QNAN and op1 is greater than op2. |
FCondOge | Both operands are not a QNAN and op1 is greater than or equal to op2. |
FCondOlt | Both operands are not a QNAN and op1 is less than op2. |
FCondOle | Both operands are not a QNAN and op1 is less than or equal to op2. |
FCondOne | Both operands are not a QNAN and op1 is not equal to op2. |
FCondOrd | Both operands are not a QNAN. |
FCondUeq | Either operand is a QNAN or op1 is equal to op2. |
FCondUgt | Either operand is a QNAN or op1 is greater than op2. |
FCondUge | Either operand is a QNAN or op1 is greater than or equal to op2. |
FCondUlt | Either operand is a QNAN or op1 is less than op2. |
FCondUle | Either operand is a QNAN or op1 is less than or equal to op2. |
FCondUne | Either operand is a QNAN or op1 is not equal to op2. |
FCondUno | Either operand is a QNAN. |
FCondTrue | Always yields true, regardless of operands. |
Conversion Operations
ConvTrunc | Integer truncate |
ConvZext | Integer extend (zero fill) |
ConvSext | Integer extend (sign fill) |
ConvFptrunc | Float truncate |
ConvFpext | Float extend |
ConvFptoui | Float to unsigned Integer |
ConvFptosi | Float to signed Integer |
ConvUintofp | Unsigned Integer to Float |
ConvSintofp | Signed Int to Float |
ConvPtrtoint | Pointer to Integer |
ConvInttoptr | Integer to Pointer |
ConvBitcast | Cast between types where no bit manipulation is needed |
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 | The inliner should attempt to inline this function into callers whenever possible, ignoring any active inlining size threshold for this caller. |
InlineHint | 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 | The inliner should never inline this function in any situation. This attribute may not be used together with the alwaysinline attribute. |
OptSize | 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 | The function never returns normally. This produces undefined behavior at runtime if the function ever does dynamically return. |
NoUnwind | The function never returns with an unwind or exceptional control flow. If the function does unwind, its runtime behavior is undefined. |
ReadNone | 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 | 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 | 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 | 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 | The code generator should not use a red zone, even if the target-specific ABI normally permits it. |
NoImplicitFloat | Disables implicit floating point instructions. |
Naked | Disables prologue / epilogue emission for the function. This can have very system-specific consequences. |
Parameter attributes are used to communicate additional information about the result or parameters of a function
ZeroExt | 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 | 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 | The 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 | The pointer parameter should really be passed by value to the function. |
SRet | The pointer parameter specifies the address of a structure that is the return value of the function in the source program. |
NoAlias | The pointer does not alias any global or any other parameter. |
NoCapture | The callee does not make any copies of the pointer that outlive the callee itself. |
Nest | The pointer parameter can be excised using the trampoline intrinsics. |
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 |
Different ways to call a function.
CallTypeStd | Normal call, allocate a new stack frame. |
CallTypeTail | Tail call, perform the call in the current stack frame. |
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 |