1 --------------------------------------------------------------------------------
2 -- | The LLVM abstract syntax.
5 module Llvm.AbsSyn where
12 type LlvmBlockId = Unique
14 -- | A block of LLVM code.
15 data LlvmBlock = LlvmBlock {
16 -- | The code label for this block
17 blockLabel :: LlvmBlockId,
19 -- | A list of LlvmStatement's representing the code for this block.
20 -- This list must end with a control flow statement.
21 blockStmts :: [LlvmStatement]
24 type LlvmBlocks = [LlvmBlock]
26 -- | An LLVM Module. This is a top level container in LLVM.
27 data LlvmModule = LlvmModule {
28 -- | Comments to include at the start of the module.
29 modComments :: [LMString],
31 -- | LLVM Alias type definitions.
32 modAliases :: [LlvmAlias],
34 -- | Global variables to include in the module.
35 modGlobals :: [LMGlobal],
37 -- | LLVM Functions used in this module but defined in other modules.
38 modFwdDecls :: LlvmFunctionDecls,
40 -- | LLVM Functions defined in this module.
41 modFuncs :: LlvmFunctions
45 data LlvmFunction = LlvmFunction {
46 -- | The signature of this declared function.
47 funcDecl :: LlvmFunctionDecl,
49 -- | The functions arguments
50 funcArgs :: [LMString],
52 -- | The function attributes.
53 funcAttrs :: [LlvmFuncAttr],
55 -- | The section to put the function into,
56 funcSect :: LMSection,
58 -- | The body of the functions.
59 funcBody :: LlvmBlocks
62 type LlvmFunctions = [LlvmFunction]
68 Assign an expression to an variable:
69 * dest: Variable to assign to
70 * source: Source expression
72 = Assignment LlvmVar LlvmExpression
75 Always branch to the target label
80 Branch to label targetTrue if cond is true otherwise to label targetFalse
81 * cond: condition that will be tested, must be of type i1
82 * targetTrue: label to branch to if cond is true
83 * targetFalse: label to branch to if cond is false
85 | BranchIf LlvmVar LlvmVar LlvmVar
94 Set a label on this position.
95 * name: Identifier of this label, unique for this module
100 Store variable value in pointer ptr. If value is of type t then ptr must
102 * value: Variable/Constant to store.
103 * ptr: Location to store the value in
105 | Store LlvmVar LlvmVar
109 * scrutinee: Variable or constant which must be of integer type that is
110 determines which arm is chosen.
111 * def: The default label if there is no match in target.
112 * target: A list of (value,label) where the value is an integer
113 constant and label the corresponding label to jump to if the
114 scrutinee matches the value.
116 | Switch LlvmVar LlvmVar [(LlvmVar, LlvmVar)]
120 * result: The variable or constant to return
122 | Return (Maybe LlvmVar)
125 An instruction for the optimizer that the code following is not reachable
130 Raise an expression to a statement (if don't want result or want to use
133 | Expr LlvmExpression
138 -- | Llvm Expressions
141 Allocate amount * sizeof(tp) bytes on the stack
142 * tp: LlvmType to reserve room for
143 * amount: The nr of tp's which must be allocated
145 = Alloca LlvmType Int
148 Perform the machine operator op on the operands left and right
151 * right: right operand
153 | LlvmOp LlvmMachOp LlvmVar LlvmVar
156 Perform a compare operation on the operands left and right
159 * right: right operand
161 | Compare LlvmCmpOp LlvmVar LlvmVar
164 Allocate amount * sizeof(tp) bytes on the heap
165 * tp: LlvmType to reserve room for
166 * amount: The nr of tp's which must be allocated
168 | Malloc LlvmType Int
171 Load the value at location ptr
176 Navigate in an structure, selecting elements
177 * inbound: Is the pointer inbounds? (computed pointer doesn't overflow)
178 * ptr: Location of the structure
179 * indexes: A list of indexes to select the correct value.
181 | GetElemPtr Bool LlvmVar [LlvmVar]
184 Cast the variable from to the to type. This is an abstraction of three
185 cast operators in Llvm, inttoptr, prttoint and bitcast.
187 * from: Variable to cast
188 * to: type to cast to
190 | Cast LlvmCastOp LlvmVar LlvmType
193 Call a function. The result is the value of the expression.
194 * tailJumps: CallType to signal if the function should be tail called
195 * fnptrval: An LLVM value containing a pointer to a function to be
196 invoked. Can be indirect. Should be LMFunction type.
197 * args: Concrete arguments for the parameters
198 * attrs: A list of function attributes for the call. Only NoReturn,
199 NoUnwind, ReadOnly and ReadNone are valid here.
201 | Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr]
204 Merge variables from different basic blocks which are predecessors of this
205 basic block in a new variable of type tp.
206 * tp: type of the merged variable, must match the types of the
207 predecessor variables.
208 * precessors: A list of variables and the basic block that they originate
211 | Phi LlvmType [(LlvmVar,LlvmVar)]
214 Inline assembly expression. Syntax is very similar to the style used by GCC.
215 * assembly: Actual inline assembly code.
216 * contraints: Operand constraints.
217 * return ty: Return type of function.
218 * vars: Any variables involved in the assembly code.
219 * sideeffect: Does the expression have side effects not visible from the
221 * alignstack: Should the stack be conservatively aligned before this
222 expression is executed.
224 | Asm LMString LMString LlvmType [LlvmVar] Bool Bool