Safe Haskell | None |
---|---|
Language | Haskell98 |
The LLVM abstract syntax.
- type LlvmBlockId = Unique
- data LlvmBlock = LlvmBlock {}
- type LlvmBlocks = [LlvmBlock]
- data LlvmModule = LlvmModule {
- modComments :: [LMString]
- modAliases :: [LlvmAlias]
- modMeta :: [MetaDecl]
- modGlobals :: [LMGlobal]
- modFwdDecls :: LlvmFunctionDecls
- modFuncs :: LlvmFunctions
- data LlvmFunction = LlvmFunction {
- funcDecl :: LlvmFunctionDecl
- funcArgs :: [LMString]
- funcAttrs :: [LlvmFuncAttr]
- funcSect :: LMSection
- funcBody :: LlvmBlocks
- type LlvmFunctions = [LlvmFunction]
- data LlvmSyncOrdering
- data LlvmStatement
- = Assignment LlvmVar LlvmExpression
- | Fence Bool LlvmSyncOrdering
- | Branch LlvmVar
- | BranchIf LlvmVar LlvmVar LlvmVar
- | Comment [LMString]
- | MkLabel LlvmBlockId
- | Store LlvmVar LlvmVar
- | Switch LlvmVar LlvmVar [(LlvmVar, LlvmVar)]
- | Return (Maybe LlvmVar)
- | Unreachable
- | Expr LlvmExpression
- | Nop
- | MetaStmt [MetaAnnot] LlvmStatement
- data LlvmExpression
- = Alloca LlvmType Int
- | LlvmOp LlvmMachOp LlvmVar LlvmVar
- | Compare LlvmCmpOp LlvmVar LlvmVar
- | Extract LlvmVar LlvmVar
- | Insert LlvmVar LlvmVar LlvmVar
- | Malloc LlvmType Int
- | Load LlvmVar
- | GetElemPtr Bool LlvmVar [LlvmVar]
- | Cast LlvmCastOp LlvmVar LlvmType
- | Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr]
- | CallM LlvmCallType LlvmVar [MetaExpr] [LlvmFuncAttr]
- | Phi LlvmType [(LlvmVar, LlvmVar)]
- | Asm LMString LMString LlvmType [LlvmVar] Bool Bool
- | MExpr [MetaAnnot] LlvmExpression
Documentation
type LlvmBlockId = Unique Source
Block labels
A block of LLVM code.
LlvmBlock | |
|
type LlvmBlocks = [LlvmBlock] Source
data LlvmModule Source
An LLVM Module. This is a top level container in LLVM.
LlvmModule | |
|
data LlvmFunction Source
An LLVM Function
LlvmFunction | |
|
type LlvmFunctions = [LlvmFunction] Source
data LlvmSyncOrdering Source
LLVM ordering types for synchronization purposes. (Introduced in LLVM 3.0). Please see the LLVM documentation for a better description.
SyncUnord | Some partial order of operations exists. |
SyncMonotonic | A single total order for operations at a single address exists. |
SyncAcquire | Acquire synchronization operation. |
SyncRelease | Release synchronization operation. |
SyncAcqRel | Acquire + Release synchronization operation. |
SyncSeqCst | Full sequential Consistency operation. |
data LlvmStatement Source
Llvm Statements
Assignment LlvmVar LlvmExpression | Assign an expression to an variable: * dest: Variable to assign to * source: Source expression |
Fence Bool LlvmSyncOrdering | Memory fence operation |
Branch LlvmVar | Always branch to the target label |
BranchIf LlvmVar LlvmVar LlvmVar | Branch to label targetTrue if cond is true otherwise to label targetFalse * cond: condition that will be tested, must be of type i1 * targetTrue: label to branch to if cond is true * targetFalse: label to branch to if cond is false |
Comment [LMString] | Comment Plain comment. |
MkLabel LlvmBlockId | Set a label on this position. * name: Identifier of this label, unique for this module |
Store LlvmVar LlvmVar | Store variable value in pointer ptr. If value is of type t then ptr must be of type t*. * value: Variable/Constant to store. * ptr: Location to store the value in |
Switch LlvmVar LlvmVar [(LlvmVar, LlvmVar)] | Mutliway branch * scrutinee: Variable or constant which must be of integer type that is determines which arm is chosen. * def: The default label if there is no match in target. * target: A list of (value,label) where the value is an integer constant and label the corresponding label to jump to if the scrutinee matches the value. |
Return (Maybe LlvmVar) | Return a result. * result: The variable or constant to return |
Unreachable | An instruction for the optimizer that the code following is not reachable |
Expr LlvmExpression | Raise an expression to a statement (if don't want result or want to use Llvm unnamed values. |
Nop | A nop LLVM statement. Useful as its often more efficient to use this then to wrap LLvmStatement in a Just or []. |
MetaStmt [MetaAnnot] LlvmStatement | A LLVM statement with metadata attached to it. |
data LlvmExpression Source
Llvm Expressions
Alloca LlvmType Int | Allocate amount * sizeof(tp) bytes on the stack * tp: LlvmType to reserve room for * amount: The nr of tp's which must be allocated |
LlvmOp LlvmMachOp LlvmVar LlvmVar | Perform the machine operator op on the operands left and right * op: operator * left: left operand * right: right operand |
Compare LlvmCmpOp LlvmVar LlvmVar | Perform a compare operation on the operands left and right * op: operator * left: left operand * right: right operand |
Extract LlvmVar LlvmVar | Extract a scalar element from a vector * val: The vector * idx: The index of the scalar within the vector |
Insert LlvmVar LlvmVar LlvmVar | Insert a scalar element into a vector * val: The source vector * elt: The scalar to insert * index: The index at which to insert the scalar |
Malloc LlvmType Int | Allocate amount * sizeof(tp) bytes on the heap * tp: LlvmType to reserve room for * amount: The nr of tp's which must be allocated |
Load LlvmVar | Load the value at location ptr |
GetElemPtr Bool LlvmVar [LlvmVar] | Navigate in an structure, selecting elements * inbound: Is the pointer inbounds? (computed pointer doesn't overflow) * ptr: Location of the structure * indexes: A list of indexes to select the correct value. |
Cast LlvmCastOp LlvmVar LlvmType | Cast the variable from to the to type. This is an abstraction of three cast operators in Llvm, inttoptr, prttoint and bitcast. * cast: Cast type * from: Variable to cast * to: type to cast to |
Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr] | Call a function. The result is the value of the expression. * tailJumps: CallType to signal if the function should be tail called * fnptrval: An LLVM value containing a pointer to a function to be invoked. Can be indirect. Should be LMFunction type. * args: Concrete arguments for the parameters * attrs: A list of function attributes for the call. Only NoReturn, NoUnwind, ReadOnly and ReadNone are valid here. |
CallM LlvmCallType LlvmVar [MetaExpr] [LlvmFuncAttr] | Call a function as above but potentially taking metadata as arguments. * tailJumps: CallType to signal if the function should be tail called * fnptrval: An LLVM value containing a pointer to a function to be invoked. Can be indirect. Should be LMFunction type. * args: Arguments that may include metadata. * attrs: A list of function attributes for the call. Only NoReturn, NoUnwind, ReadOnly and ReadNone are valid here. |
Phi LlvmType [(LlvmVar, LlvmVar)] | Merge variables from different basic blocks which are predecessors of this basic block in a new variable of type tp. * tp: type of the merged variable, must match the types of the predecessor variables. * precessors: A list of variables and the basic block that they originate from. |
Asm LMString LMString LlvmType [LlvmVar] Bool Bool | Inline assembly expression. Syntax is very similar to the style used by GCC. * assembly: Actual inline assembly code. * constraints: Operand constraints. * return ty: Return type of function. * vars: Any variables involved in the assembly code. * sideeffect: Does the expression have side effects not visible from the constraints list. * alignstack: Should the stack be conservatively aligned before this expression is executed. |
MExpr [MetaAnnot] LlvmExpression | A LLVM expression with metadata attached to it. |