e25f5be2b987a4b127270a30b8e06d49d158c90e
[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 container in LLVM.
27 data LlvmModule = LlvmModule  {
28     -- | Comments to include at the start of the module.
29     modComments  :: [LMString],
30
31     -- | LLVM Alias type definitions.
32     modAliases   :: [LlvmAlias],
33
34     -- | Global variables to include in the module.
35     modGlobals   :: [LMGlobal],
36
37     -- | LLVM Functions used in this module but defined in other modules.
38     modFwdDecls  :: LlvmFunctionDecls,
39
40     -- | LLVM Functions defined in this module.
41     modFuncs     :: LlvmFunctions
42   }
43
44 -- | An LLVM Function
45 data LlvmFunction = LlvmFunction {
46     -- | The signature of this declared function.
47     funcDecl  :: LlvmFunctionDecl,
48
49     -- | The functions arguments
50     funcArgs  :: [LMString],
51
52     -- | The function attributes.
53     funcAttrs :: [LlvmFuncAttr],
54
55     -- | The section to put the function into,
56     funcSect  :: LMSection,
57
58     -- | The body of the functions.
59     funcBody  :: LlvmBlocks
60   }
61
62 type LlvmFunctions  = [LlvmFunction]
63
64
65 -- | Llvm Statements
66 data LlvmStatement
67   {- |
68     Assign an expression to an variable:
69       * dest:   Variable to assign to
70       * source: Source expression
71   -}
72   = Assignment LlvmVar LlvmExpression
73
74   {- |
75     Always branch to the target label
76   -}
77   | Branch LlvmVar
78
79   {- |
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
84   -}
85   | BranchIf LlvmVar LlvmVar LlvmVar
86
87   {- |
88     Comment
89     Plain comment.
90   -}
91   | Comment [LMString]
92
93   {- |
94     Set a label on this position.
95       * name: Identifier of this label, unique for this module
96   -}
97   | MkLabel LlvmBlockId
98
99   {- |
100     Store variable value in pointer ptr. If value is of type t then ptr must
101     be of type t*.
102       * value: Variable/Constant to store.
103       * ptr:   Location to store the value in
104   -}
105   | Store LlvmVar LlvmVar
106
107   {- |
108     Mutliway branch
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.
115   -}
116   | Switch LlvmVar LlvmVar [(LlvmVar, LlvmVar)]
117
118   {- |
119     Return a result.
120       * result: The variable or constant to return
121   -}
122   | Return (Maybe LlvmVar)
123
124   {- |
125     An instruction for the optimizer that the code following is not reachable
126   -}
127   | Unreachable
128
129   {- |
130     Raise an expression to a statement (if don't want result or want to use
131     Llvm unnamed values.
132   -}
133   | Expr LlvmExpression
134
135   deriving (Show, Eq)
136
137
138 -- | Llvm Expressions
139 data LlvmExpression
140   {- |
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
144   -}
145   = Alloca LlvmType Int
146
147   {- |
148     Perform the machine operator op on the operands left and right
149       * op:    operator
150       * left:  left operand
151       * right: right operand
152   -}
153   | LlvmOp LlvmMachOp LlvmVar LlvmVar
154
155   {- |
156     Perform a compare operation on the operands left and right
157       * op:    operator
158       * left:  left operand
159       * right: right operand
160   -}
161   | Compare LlvmCmpOp LlvmVar LlvmVar
162
163   {- |
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
167   -}
168   | Malloc LlvmType Int
169
170   {- |
171     Load the value at location ptr
172   -}
173   | Load LlvmVar
174
175   {- |
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.
180   -}
181   | GetElemPtr Bool LlvmVar [LlvmVar]
182
183   {- |
184      Cast the variable from to the to type. This is an abstraction of three
185      cast operators in Llvm, inttoptr, prttoint and bitcast.
186        * cast: Cast type
187        * from: Variable to cast
188        * to:   type to cast to
189   -}
190   | Cast LlvmCastOp LlvmVar LlvmType
191
192   {- |
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.
200   -}
201   | Call LlvmCallType LlvmVar [LlvmVar] [LlvmFuncAttr]
202
203   {- |
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
209                     from.
210   -}
211   | Phi LlvmType [(LlvmVar,LlvmVar)]
212
213   {- |
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
220                     constraints list.
221       * alignstack: Should the stack be conservatively aligned before this
222                     expression is executed.
223   -}
224   | Asm LMString LMString LlvmType [LlvmVar] Bool Bool
225
226   deriving (Show, Eq)
227