Used colon-less keyword syntax in method signatures where the optional variable name...
[cslatevm.git] / src / llvm / internalcompiler.slate
blob855f27eab0616dd7aa86cf79a06e06bb9a6b313d
1 expr@(nodes MethodDefinition traits) inline
3   InternalCompiler new generate: expr.
4   expr disable
5 ].
7 define: #InternalCompiler &parents: {Cloneable} &slots: {#contexts -> Stack new}.
9 ic@(InternalCompiler traits) new
11   ic clone `>> [contexts := ic contexts new. ]
14 InternalCompiler traits define: #Context &parents: {Cloneable} &slots: {
15   #isClosure -> False "Whether the method being compiled is a closure.".
16   #method -> CompiledMethod new "The method the context targets.".
17   #selectors -> ExtensibleArray new.
18   "The gathering collection for the method's literal array; must be indexable
19   before committing."
20   #literals -> ExtensibleArray new.
21   "The gathering collection for the method's selector array; must be indexable
22   before committing."
25 ic@(InternalCompiler Context traits) newOn: method
27   "FIXME change method code to array instead of bytearray."
28   method code := Array new.
29   ic cloneSettingSlots: #{#method. #selectors. #literals}
30      to: {method.
31           ic selectors new.
32           ic literals new}
35 ic@(InternalCompiler Context traits) copy
37   resend `>> [selectors := ic selectors copy.
38               literals := ic literals copy]
41 ic@(InternalCompiler Context traits) flush
43   ic method literals := ic literals as: Array.
44   ic method selectors := ic selectors as: Array.
45   ic
48 ic@(InternalCompiler traits) currentContext
50   ic contexts top
53 ic@(InternalCompiler traits) currentMethod
55   ic currentContext method
58 ic@(InternalCompiler traits) literal: obj
60 "Ensure that the literal object is included in the literals array. If it is
61 not present already, it is appended to the end, thus ensuring that no other
62 indices require shifting. Answer the literal's index."
63   (ic contexts top literals indexOfFirstSatisfying:
64      [| :literal | obj = literal /\ [obj isSameAs: literal]])
65     ifNil:
66       [index ::= ic contexts top literals size.
67        ic contexts top literals addLast: obj.
68        index]
71 ic@(InternalCompiler traits) selector: selector
73 "Ensure that the literal object is included in the selectors array. If it is
74 not present already, it is appended to the end, thus ensuring that no other
75 indices require shifting. Answer the selector's index."
76   ic contexts top selectors `>> [include: selector. indexOf: selector]
79 _@(InternalCompiler traits) generate: _@(nodes Node traits)
81 "Do nothing in the default case, for comments and annotations and such."
84 ic@(InternalCompiler traits) generate: ann@(nodes Annotation traits)
86 "Generate the annotation's value."
87   ic generate: ann value
90 ic@(InternalCompiler traits) generate: block@(nodes Block traits) &topLevel
92 "Encountering a new block, build a new CompiledMethod object and push it and
93 a new bytecode array writer onto the generator, then go through the underlying
94 code and generate that. When done, pop both, set up the block as a literal
95 and push it onto the stack."
96   topLevel `defaultsTo: False.
97   newBlock ::= CompiledMethod new.
98   newBlock environment := ic contexts isEmpty
99     ifTrue: [block parentScope topLevel namespace]
100     ifFalse: [ic currentMethod environment].
101   newBlock sourceTree := block.
102   ic contexts push: (ic Context newOn: newBlock).
103     "we macroexpand everything before we set the current register because macroexpansion can add localvariables etc"
104   statements ::= block statements collect:
105     [| :statement | statement macroExpand &environment: ic currentMethod sourceTree].
106   statements allButLastDo: #(ic generate: _) `er.
107   statements size > 0
108     ifTrue: ["returnRegister" ic generate: statements last]
109     ifFalse: ["returnValue"].
111   "Set the variable information after generation, just in case it was modified."
112   newBlock `>>
113   [inputVariables := block inputVariables size.
114     localVariables := block localVariables size.
115     restVariable := block restVariable isNotNil.
116     optionalKeywords := block optionalKeywords. ].
117   isClosure ::= ic currentContext isClosure.
119   ic contexts pop flush.
120   "Forces the newBlock to record all the remaining stream input correctly."
122   ic contexts isEmpty \/ [topLevel] ifFalse:
123     [isClosure
124        ifTrue: ["newClosure"]
125        ifFalse: ["loadLiteral"]].
128 ic@(InternalCompiler traits) generate: def@(nodes MethodDefinition traits)
129 "Translate method definitions to equivalent asMethod:on: invocations."
131   ic contexts isEmpty ifTrue: [^ resend].
132   #visit: sendTo: {gen. def} through: {gen. nodes Block}.
133   def roles do: [| :role | ic generate: role].
134   "directSendMessage"
137 ic@(InternalCompiler traits) generate: r@(nodes Resend traits)
139   | lexOffset scope |
140   scope := ic currentMethod sourceTree.
141   lexOffset := ic contexts indexLast -
142     ((ic contexts indexOfLastSatisfying: [| :context | context method sourceTree isSameAs: nodes MethodDefinition])
143     ifNil:
144       [error: 'resend must be used within a method definition.']).
145   lexOffset > 0
146     ifTrue:
147     [(ic contexts fromTop: lexOffset) method heapAllocate := True.
148       (ic contexts top: lexOffset) do: #(isClosure: True) `er].
151 ic@(InternalCompiler traits) generate: r@(nodes Return traits)
153   overrideThis
156 ic@(InternalCompiler traits) generate: r@(nodes Return traits) by: lexOffset
158   lexOffset isPositive
159     ifTrue: [(ic contexts fromTop: lexOffset) method heapAllocate := True.
160              (ic contexts top: lexOffset) do: #(isClosure: True) `er].
161   ic generate: r value.
164 ic@(InternalCompiler traits) generate: r@(nodes ReturnClose traits)
165 "Exits the first enclosing named method in the lexical scope."
166 [| lexOffset |
167     lexOffset := ic contexts indexLast -
168     ((ic contexts indexOfLastSatisfying: [| :context | context method sourceTree isSameAs: nodes MethodDefinition])
169     ifNil:
170       [error: '^ must be used within a method definition.']).
171   ic generate: r by: lexOffset
174 ic@(InternalCompiler traits) generate: r@(nodes ReturnFar traits)
175 "Exits the last enclosing named method in the lexical scope."
176 [| lexOffset |
177   lexOffset := ic contexts indexLast -
178     ((ic contexts indexOfFirstSatisfying: [| :context | context method sourceTree isSameAs: nodes MethodDefinition])
179       ifNil: [error: '^^ must be used within a method definition.']).
180   ic generate: r by: lexOffset
183 ic@(InternalCompiler traits) generate: r@(nodes ReturnLevel traits)
184 "Exits the Nth enclosing lexical scope."
186   ic generate: r by: r level
189 ic@(InternalCompiler traits) generate: literal@(nodes Literal traits)
191   inform: ('Literal[' ; (ic literal: literal) printString ; ']: ' ; literal printString).
194 ic@(InternalCompiler traits) generate: n@(nodes CompoundStatement traits)
195 "return the registers that the values were saved into"
197   n statements do: #(ic generate: _) `er
200 ic@(InternalCompiler traits) generate: n@(nodes Parenthesis traits)
201 "return the registers that the values were saved into"
203   n statements do: #(ic generate: _) `er
206 ic@(InternalCompiler traits) generate: i@(nodes ImplicitArgument traits)
210 ic@(InternalCompiler traits) generate: _@(nodes Namespace traits)
212   shouldNotImplement
215 ic@(InternalCompiler traits) generate: load@(nodes LoadVariable traits)
216 [| scope lexOffset varIndex |
217   scope := load variable scope.
218   varIndex := scope localVariables indexOf: load variable.
219   lexOffset := ic contexts indexLast -
220     ((ic contexts indexOfLastSatisfying: [| :context | context method sourceTree == scope])
221       ifNil: [error: 'Could not determine variable scope.']).
224 ic@(InternalCompiler traits) generate: store@(nodes StoreVariable traits)
225 [| scope lexOffset varIndex |
226   scope := store variable scope.
227   varIndex := scope localVariables indexOf: store variable.
228   lexOffset := ic contexts indexLast -
229     ((ic contexts indexOfLastSatisfying: [| :context | context method sourceTree == scope])
230       ifNil: [error: 'Could not determine variable scope.']).
233 ic@(InternalCompiler traits) generate: array@(nodes Array traits)
235 "Generate the code to push the element expression results on the stack,
236 then the appropriate literal-array constructor bytecode."
239 ic@(InternalCompiler traits) generate: selector@(Symbol traits) on: args from: msg@(nodes Message traits)
241 "Generate the code to push the argument expression results on the stack, then
242 the push for the selector, and then the appropriate message send bytecode."
243   args do: #(ic generate: _) `er.
246 ic@(InternalCompiler traits) generate: msg@(nodes Message traits) &optionals: opts
248   ic generate: msg selector on: msg arguments from: (opts ifNil: [msg])
251 ic@(InternalCompiler traits) generate: macro@(nodes Macro traits) &optionals: opts
253   "ic generate: (macro macroExpand &optionals: opts &environment: ic currentMethod sourceTree)"
254   error: 'SSA InternalCompiler cannot support macroexpansion at code generation time because of localVariable side-effects'.
257 ic@(InternalCompiler traits) generate: def@(nodes Deferred traits) &optionals: opts
259   block ::= nodes Block new `>> [parentScope := ic currentMethod sourceTree. ].
260   def arguments size timesRepeat: [block addInputVariable].
261   message ::= nodes Message sending: def selector to:
262     (block inputVariables collect: [| :var | nodes LoadVariable from: var]).
263   opts
264     ifNotNil:
265     [message :=
266       ((nodes OptionalArguments for: message)
267       `>> [arguments := opts arguments deepCopy: block. ])].
268   block statements := {message}.
269   ic generate:
270     (nodes KeywordMessage
271        sending: #whenFulfilled:
272        to: {def arguments as: nodes Array. block})
275 ic@(InternalCompiler traits) generate: selector@(Symbol traits) on: args from: opts@(nodes OptionalKeywords traits)
276 "Generate the code to push the argument expression results on the stack, then
277 the push for the selector, and then the appropriate message send bytecode."
279   args do: #(ic generate: _) `er.
280   opts keywords with: opts arguments do:
281     [| :key :arg | ic generate: arg]
284 ic@(InternalCompiler traits) generate: opts@(nodes OptionalKeywords traits)
286   ic generate: opts message &optionals: opts