Revert "Revert "Made use of ::= in core libraries and defined a RebindError condition...
[cslatevm.git] / src / lib / module-compiled.slate
blob9e9187e0a3623cc0c322ef12cd157a7784566c0c
1 prototypes define: #CompiledModule &parents: {Cloneable} &slots: {
2   #magic.
3   #version.
4   #checksum.
5 }.
7 m@(CompiledModule traits) compile: filename
8 [| srcfile slcfile |
9   srcfile := (File newNamed: filename).
10   slcfile := (srcfile newNamed: filename copy &mode: srcfile CreateWrite).
11   slcfile locator fileType := 'slc'.
12   srcfile reader sessionDo:
13     [| :in p |
14      p := (Syntax Parser newOn: in).
15      slcfile writer sessionDo:
16        [| :out |
17         "TODO: write out a generic header with magic, version, checksum."
18         [p isAtEnd] whileFalse:
19           [| item |
20            item := p next.
21            inform: p lexer lineNumber printString.
22            m save: item to: out]]].
25 m@(CompiledModule traits) loadFrom: src
27   m loadFrom: src reader
30 m@(CompiledModule traits) loadFrom: src@(ExternalResource traits)
32   src reader sessionDo: #(m loadFrom: _) `er
35 m@(CompiledModule traits) loadFrom: r@(ReadStream traits)
36 [| kind |
37   (kind := r next) caseOf: {
38     $T -> [True].
39     $F -> [False].
40     $N -> [Nil].
41     $n -> [NoRole].
42     $s -> [m nextStringFrom: r].
43     $I -> [Integer readFrom: (m nextStringFrom: r)].
44     $f -> [Float readFrom: (m nextStringFrom: r)].
45     $x -> [(m nextStringFrom: r) intern].
46     $A -> [m next: Array from: r].
47     $a -> [m next: ByteArray from: r].
48     $S -> [m loadSyntaxTreeFrom: r].
49     $i -> [m nextInstructionSequenceFrom: r].
50     $M -> [CompiledMethod new `>>
51              [literals: (m loadFrom: r).
52               selectors: (m loadFrom: r).
53               optionalKeywords: (m loadFrom: r).
54               code: (m loadFrom: r). ]]
55   } otherwise: [error: 'Unknown type: ' ; kind printString]
58 m@(CompiledModule traits) loadSyntaxTreeFrom: r@(ReadStream traits)
59 [| kind proto |
60   proto := ((kind := m nextSyntaxTypeFrom: r) caseOf: {
61     'No' -> [Syntax Node].
62     'An' -> [Syntax Annotation].
63     'Cm' -> [Syntax Comment].
64     'IA' -> [Syntax ImplicitArgument].
65     'M ' -> [Syntax Message].
66     'Mu' -> [Syntax UnaryMessage].
67     'Mb' -> [Syntax BinaryMessage].
68     'Mk' -> [Syntax KeywordMessage].
69     'm ' -> [Syntax Macro].
70     'mu' -> [Syntax UnaryMacro].
71     'mb' -> [Syntax BinaryMacro].
72     'mk' -> [Syntax KeywordMacro].
73     'D ' -> [Syntax Deferred].
74     'Du' -> [Syntax UnaryDeferred].
75     'Db' -> [Syntax BinaryDeferred].
76     'Dk' -> [Syntax KeywordDeferred].
77     'MW' -> [Syntax MessageWrapper].
78     'Ok' -> [Syntax OptionalKeywords].
79     'RA' -> [Syntax RestArguments].
80     'Li' -> [Syntax Literal].
81     'CS' -> [Syntax CompoundStatement].
82     'A ' -> [Syntax Array].
83     'Pa' -> [Syntax Parenthesis].
84     'Na' -> [Syntax Namespace].
85     'Gr' -> [Syntax Ground].
86     'B ' -> [Syntax Block].
87     'MD' -> [Syntax MethodDefinition].
88     'Va' -> [Syntax Variable].
89     'LV' -> [Syntax LoadVariable].
90     'LR' -> [Syntax LoadRestVariable].
91     'SV' -> [Syntax StoreVariable].
92     'Rt' -> [Syntax Return].
93     'Rc' -> [Syntax ReturnClose].
94     'Rf' -> [Syntax ReturnFar].
95     'Rl' -> [Syntax ReturnLevel].
96     'Rs' -> [Syntax Resend]
97   } otherwise: [error: 'Unknown syntax type: ' ; kind printString]).
98   m load: proto from: r
101 m@(CompiledModule traits) nextSyntaxTypeFrom: r@(ReadStream traits)
102 [r next: 2].
104 m@(CompiledModule traits) nextCountFrom: r@(ReadStream traits)
105 [Integer readFrom: (r upToAnyOf: '\t\n')].
107 m@(CompiledModule traits) nextStringFrom: r@(ReadStream traits)
108 [| result |
109   result := (r next: (m nextCountFrom: r)).
110   r next.
111   result
114 m@(CompiledModule traits) next: s@(Sequence traits) from: r@(ReadStream traits)
116   (s newSize: (m nextCountFrom: r)) `>>
117     [| :newS | keysDo: [| :index | newS at: index put: (m loadFrom: r)]. ]
120 obj@(Root traits) saveInto: w@(WriteStream traits)
122   CompiledModule new save: obj to: w
125 obj@(Root traits) saveInto: sink@(ExternalResource traits)
127   sink create writer sessionDo: #(obj saveInto: _) `er
130 obj@(Root traits) saveInto: sink
132   obj saveInto: sink writer
135 m@(CompiledModule traits) save: obj to: w@(WriteStream traits)
137   error: 'Unknown type: ' ; obj printString
140 m@(CompiledModule traits) save: _@True to: w@(WriteStream traits)
141 [w ; 'T\n'].
143 m@(CompiledModule traits) save: _@False to: w@(WriteStream traits)
144 [w ; 'F\n'].
146 m@(CompiledModule traits) save: _@Nil to: w@(WriteStream traits)
147 [w ; 'N\n'].
149 m@(CompiledModule traits) save: _@NoRole to: w@(WriteStream traits)
150 [w ; 'n\n'].
152 m@(CompiledModule traits) saveString: s to: w@(WriteStream traits)
154   w ; s size printString ; '\t' ; s ; '\n'.
157 m@(CompiledModule traits) save: s@(String traits) to: w@(WriteStream traits)
159   w ; 's'.
160   m saveString: s to: w.
163 m@(CompiledModule traits) save: s@(Symbol traits) to: w@(WriteStream traits)
165   w ; 'x'.
166   m saveString: s to: w.
169 m@(CompiledModule traits) save: a@(Array traits) to: w@(WriteStream traits)
171   w ; 'A' ; a size printString ; '\n'.
172   a do: [| :each | m save: each to: w].
175 m@(CompiledModule traits) save: a@(ByteArray traits) to: w@(WriteStream traits)
177   w ; 'a' ; a size printString ; '\n'.
178   a do: [| :each | m save: each to: w].
181 m@(CompiledModule traits) save: n@(Integer traits) to: w@(WriteStream traits)
183   w ; 'I'.
184   m saveString: n printString to: w.
187 m@(CompiledModule traits) save: x@(Float traits) to: w@(WriteStream traits)
189   w ; 'f'.
190   m saveString: x printString to: w.
193 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Node traits) on: w@(WriteStream traits) [w ; 'SNo'].
194 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Annotation traits) on: w@(WriteStream traits) [w ; 'SAn'].
195 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Comment traits) on: w@(WriteStream traits) [w ; 'SCm'].
196 m@(CompiledModule traits) emitPrefixFor: node@(Syntax ImplicitArgument traits) on: w@(WriteStream traits) [w ; 'SIA'].
197 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Message traits) on: w@(WriteStream traits) [w ; 'SM '].
198 m@(CompiledModule traits) emitPrefixFor: node@(Syntax UnaryMessage traits) on: w@(WriteStream traits) [w ; 'SMu'].
199 m@(CompiledModule traits) emitPrefixFor: node@(Syntax BinaryMessage traits) on: w@(WriteStream traits) [w ; 'SMb'].
200 m@(CompiledModule traits) emitPrefixFor: node@(Syntax KeywordMessage traits) on: w@(WriteStream traits) [w ; 'SMk'].
201 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Macro traits) on: w@(WriteStream traits) [w ; 'Sm '].
202 m@(CompiledModule traits) emitPrefixFor: node@(Syntax UnaryMacro traits) on: w@(WriteStream traits) [w ; 'Smu'].
203 m@(CompiledModule traits) emitPrefixFor: node@(Syntax BinaryMacro traits) on: w@(WriteStream traits) [w ; 'Smb'].
204 m@(CompiledModule traits) emitPrefixFor: node@(Syntax KeywordMacro traits) on: w@(WriteStream traits) [w ; 'Smk'].
205 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Deferred traits) on: w@(WriteStream traits) [w ; 'SD '].
206 m@(CompiledModule traits) emitPrefixFor: node@(Syntax UnaryDeferred traits) on: w@(WriteStream traits) [w ; 'SDu'].
207 m@(CompiledModule traits) emitPrefixFor: node@(Syntax BinaryDeferred traits) on: w@(WriteStream traits) [w ; 'SDb'].
208 m@(CompiledModule traits) emitPrefixFor: node@(Syntax KeywordDeferred traits) on: w@(WriteStream traits) [w ; 'SDk'].
209 m@(CompiledModule traits) emitPrefixFor: node@(Syntax MessageWrapper traits) on: w@(WriteStream traits) [w ; 'SMW'].
210 m@(CompiledModule traits) emitPrefixFor: node@(Syntax OptionalKeywords traits) on: w@(WriteStream traits) [w ; 'SOk'].
211 m@(CompiledModule traits) emitPrefixFor: node@(Syntax RestArguments traits) on: w@(WriteStream traits) [w ; 'SRA'].
212 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Literal traits) on: w@(WriteStream traits) [w ; 'SLi'].
213 m@(CompiledModule traits) emitPrefixFor: node@(Syntax CompoundStatement traits) on: w@(WriteStream traits) [w ; 'SCS'].
214 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Array traits) on: w@(WriteStream traits) [w ; 'SA '].
215 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Parenthesis traits) on: w@(WriteStream traits) [w ; 'SPa'].
216 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Namespace traits) on: w@(WriteStream traits) [w ; 'SNa'].
217 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Ground traits) on: w@(WriteStream traits) [w ; 'SGr'].
218 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Block traits) on: w@(WriteStream traits) [w ; 'SB '].
219 m@(CompiledModule traits) emitPrefixFor: node@(Syntax MethodDefinition traits) on: w@(WriteStream traits) [w ; 'SMD'].
220 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Variable traits) on: w@(WriteStream traits) [w ; 'SVa'].
221 m@(CompiledModule traits) emitPrefixFor: node@(Syntax LoadVariable traits) on: w@(WriteStream traits) [w ; 'SLV'].
222 m@(CompiledModule traits) emitPrefixFor: node@(Syntax LoadRestVariable traits) on: w@(WriteStream traits) [w ; 'SLR'].
223 m@(CompiledModule traits) emitPrefixFor: node@(Syntax StoreVariable traits) on: w@(WriteStream traits) [w ; 'SSV'].
224 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Return traits) on: w@(WriteStream traits) [w ; 'SRt'].
225 m@(CompiledModule traits) emitPrefixFor: node@(Syntax ReturnClose traits) on: w@(WriteStream traits) [w ; 'SRc'].
226 m@(CompiledModule traits) emitPrefixFor: node@(Syntax ReturnFar traits) on: w@(WriteStream traits) [w ; 'SRf'].
227 m@(CompiledModule traits) emitPrefixFor: node@(Syntax ReturnLevel traits) on: w@(WriteStream traits) [w ; 'SRl'].
228 m@(CompiledModule traits) emitPrefixFor: node@(Syntax Resend traits) on: w@(WriteStream traits) [w ; 'SRs'].
230 m@(CompiledModule traits) save: node@(Syntax Node traits) to: w@(WriteStream traits)
232   m emitPrefixFor: node on: w.
233   "m save: node type to: w."
234   m save: node lineNumber to: w.
235   m save: node source to: w.
238 m@(CompiledModule traits) load: node@(Syntax Node traits) from: r@(ReadStream traits)
240   "node type: (m loadFrom: r)."
241   node lineNumber := (m loadFrom: r).
242   node source := (m loadFrom: r).
245 m@(CompiledModule traits) save: node@(Syntax Annotation traits) to: w@(WriteStream traits)
247   resend.
248   m save: node value to: w.
251 m@(CompiledModule traits) save: node@(Syntax Comment traits) to: w@(WriteStream traits)
253   resend.
254   m save: node comment to: w.
257 m@(CompiledModule traits) save: node@(Syntax Message traits) to: w@(WriteStream traits)
259   resend.
260   m save: node selector to: w.
261   m save: node arguments to: w.
264 m@(CompiledModule traits) save: node@(Syntax MessageWrapper traits) to: w@(WriteStream traits)
266   resend.
267   m save: node message to: w.
270 m@(CompiledModule traits) save: node@(Syntax OptionalKeywords traits) to: w@(WriteStream traits)
272   resend.
273   m save: node keywords to: w.
274   m save: node arguments to: w.
277 m@(CompiledModule traits) save: node@(Syntax RestArguments traits) to: w@(WriteStream traits)
279   resend.
280   m save: node arguments to: w.
283 m@(CompiledModule traits) save: node@(Syntax Literal traits) to: w@(WriteStream traits)
285   resend.
286   m save: node value to: w.
289 m@(CompiledModule traits) save: node@(Syntax CompoundStatement traits) to: w@(WriteStream traits)
291   resend.
292   m save: node statements to: w.
295 m@(CompiledModule traits) save: node@(Syntax Namespace traits) to: w@(WriteStream traits)
297   resend.
298   "TODO: serialize the namespace or the path to it?"
301 m@(CompiledModule traits) save: node@(Syntax Block traits) to: w@(WriteStream traits)
303   resend.
304   m save: node parentScope to: w.
305   m save: node inputVariables to: w.
306   m save: node restVariable to: w.
307   m save: node optionalKeywords to: w.
308   m save: node optionalVariables to: w.
309   m save: node localVariables to: w.
312 m@(CompiledModule traits) save: node@(Syntax MethodDefinition traits) to: w@(WriteStream traits)
314   resend.
315   m save: node selector to: w.
316   m save: node roles to: w.
319 m@(CompiledModule traits) save: node@(Syntax Variable traits) to: w@(WriteStream traits)
321   resend.
322   m save: node name to: w.
323   "TODO: same scope/namespace issue as above"
324   "m save: node scope to: w."
327 m@(CompiledModule traits) save: node@(Syntax LoadVariable traits) to: w@(WriteStream traits)
329   resend.
330   m save: node variable to: w.
333 m@(CompiledModule traits) save: node@(Syntax StoreVariable traits) to: w@(WriteStream traits)
335   resend.
336   m save: node variable to: w.
337   m save: node value to: w.
340 m@(CompiledModule traits) save: node@(Syntax Return traits) to: w@(WriteStream traits)
342   resend.
343   m save: node value to: w.
346 m@(CompiledModule traits) save: node@(Syntax ReturnLevel traits) to: w@(WriteStream traits)
348   resend.
349   m save: node level to: w.