LLVM: Use the inbounds keyword for getelementptr instructions.
[ghc-hetmet.git] / compiler / llvmGen / Llvm / AbsSyn.hs
1 --------------------------------------------------------------------------------
2 -- | The LLVM abstract syntax.
3 --
4
5 module Llvm.AbsSyn where
6
7 import Llvm.Types
8
9 import Unique
10
11 -- | Block labels
12 type LlvmBlockId = Unique
13
14 -- | A block of LLVM code.
15 data LlvmBlock = LlvmBlock {
16     -- | The code label for this block
17     blockLabel :: LlvmBlockId,
18
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]
22   }
23
24 type LlvmBlocks = [LlvmBlock]
25
26 -- | An LLVM Module. This is a top level contianer in LLVM.
27 data LlvmModule = LlvmModule  {
28     -- | Comments to include at the start of the module.
29     modComments  :: [LMString],
30
31     -- | Global variables to include in the module.
32     modGlobals   :: [LMGlobal],
33
34     -- | LLVM Functions used in this module but defined in other modules.
35     modFwdDecls  :: LlvmFunctionDecls,
36
37     -- | LLVM Functions defined in this module.
38     modFuncs     :: LlvmFunctions
39   }
40
41 -- | An LLVM Function
42 data LlvmFunction = LlvmFunction {
43     -- | The signature of this declared function.
44     funcDecl  :: LlvmFunctionDecl,
45
46     -- | The functions arguments
47     funcArgs  :: [LMString],
48
49     -- | The function attributes.
50     funcAttrs :: [LlvmFuncAttr],
51
52     -- | The section to put the function into,
53     funcSect  :: LMSection,
54
55     -- | The body of the functions.
56     funcBody  :: LlvmBlocks
57   }
58
59 type LlvmFunctions  = [LlvmFunction]
60
61
62 -- | Llvm Statements
63 data LlvmStatement
64   {- |
65     Assign an expression to an variable:
66       * dest:   Variable to assign to
67       * source: Source expression
68   -}
69   = Assignment LlvmVar LlvmExpression
70
71   {- |
72     Always branch to the target label
73   -}
74   | Branch LlvmVar
75
76   {- |
77     Branch to label targetTrue if cond is true otherwise to label targetFalse
78       * cond:        condition that will be tested, must be of type i1
79       * targetTrue:  label to branch to if cond is true
80       * targetFalse: label to branch to if cond is false
81   -}
82   | BranchIf LlvmVar LlvmVar LlvmVar
83
84   {- |
85     Comment
86     Plain comment.
87   -}
88   | Comment [LMString]
89
90   {- |
91     Set a label on this position.
92       * name: Identifier of this label, unique for this module
93   -}
94   | MkLabel LlvmBlockId
95
96   {- |
97     Store variable value in pointer ptr. If value is of type t then ptr must
98     be of type t*.
99       * value: Variable/Constant to store.
100       * ptr:   Location to store the value in
101   -}
102   | Store LlvmVar LlvmVar
103
104   {- |
105     Mutliway branch
106       * scrutinee: Variable or constant which must be of integer type that is
107                    determines which arm is chosen.
108       * def:       The default label if there is no match in target.
109       * target:    A list of (value,label) where the value is an integer
110                    constant and label the corresponding label to jump to if the
111                    scrutinee matches the value.
112   -}
113   | Switch LlvmVar LlvmVar [(LlvmVar, LlvmVar)]
114
115   {- |
116     Return a result.
117       * result: The variable or constant to return
118   -}
119   | Return (Maybe LlvmVar)
120
121   {- |
122     An instruction for the optimizer that the code following is not reachable
123   -}
124   | Unreachable
125
126   {- |
127     Raise an expression to a statement (if don't want result or want to use
128     Llvm unamed values.
129   -}
130   | Expr LlvmExpression
131
132   deriving (Show, Eq)
133
134
135 -- | Llvm Expressions
136 data LlvmExpression
137   {- |
138     Allocate amount * sizeof(tp) bytes on the stack
139       * tp:     LlvmType to reserve room for
140       * amount: The nr of tp's which must be allocated
141   -}
142   = Alloca LlvmType Int
143
144   {- |
145     Perform the machine operator op on the operands left and right
146       * op:    operator
147       * left:  left operand
148       * right: right operand
149   -}
150   | LlvmOp LlvmMachOp LlvmVar LlvmVar
151
152   {- |
153     Perform a compare operation on the operands left and right
154       * op:    operator
155       * left:  left operand
156       * right: right operand
157   -}
158   | Compare LlvmCmpOp LlvmVar LlvmVar
159
160   {- |
161     Allocate amount * sizeof(tp) bytes on the heap
162       * tp:     LlvmType to reserve room for
163       * amount: The nr of tp's which must be allocated
164   -}
165   | Malloc LlvmType Int
166
167   {- |
168     Load the value at location ptr
169   -}
170   | Load LlvmVar
171
172   {- |
173     Navigate in an structure, selecting elements
174       * inbound: Is the pointer inbounds? (computed pointer doesn't overflow)
175       * ptr:     Location of the structure
176       * indexes: A list of indexes to select the correct value. For example
177                  the first element of the third element of the structure ptr
178                  is selected with [3,1] (zero indexed)
179   -}
180   | GetElemPtr Bool LlvmVar [Int]
181
182   {- |
183      Cast the variable from to the to type. This is an abstraction of three
184      cast operators in Llvm, inttoptr, prttoint and bitcast.
185        * cast: Cast type
186        * from: Variable to cast
187        * to:   type to cast to
188   -}
189   | Cast LlvmCastOp LlvmVar LlvmType
190
191   {- |
192     Call a function. The result is the value of the expression.
193       * tailJumps: CallType to signal if the function should be tail called
194       * fnptrval:  An LLVM value containing a pointer to a function to be
195                    invoked. Can be indirect. Should be LMFunction type.
196       * args:      Concrete arguments for the parameters
197       * attrs:     A list of function attributes for the call. Only NoReturn,
198                    NoUnwind, ReadOnly and ReadNone are valid here.
199   -}
200   | Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr]
201
202   {- |
203     Merge variables from different basic blocks which are predecessors of this
204     basic block in a new variable of type tp.
205       * tp:         type of the merged variable, must match the types of the
206                     precessors variables.
207       * precessors: A list of variables and the basic block that they originate
208                     from.
209   -}
210   | Phi LlvmType [(LlvmVar,LlvmVar)]
211
212   deriving (Show, Eq)
213