Fixed a bug where two code branches with Bindings would never "unify" to one variable.
[cslatevm.git] / src / syntax / lexer.slate
blob181bd9c9913e5eea5b11d8f3965f357975e38da6
1 define: #Lexer &parents: {StreamProcessor}
2   &slots: {#inputBuffer -> ExtensibleArray new.
3            #outputBuffer -> ExtensibleArray new.
4            "A backing buffer of tokens for undo functionality."
5            #lineNumber -> 1 "The current line number."}.
6 "The lexer takes an input character Stream and divides it up into Tokens,
7 using a buffer as necessary to hold the tokenized contents.
8 Also, debugging information is stored for now in terms of the line number that
9 the current stream position has reached."
10 Lexer traits define: #WordTerminatingTokens -> '()[]{}@,.|!#$`"\'%'.
12 l@(Lexer traits) on: stream
13 "Target the lexer to the particular stream and initialize it."
15   l `>> [resend. reset. ]
18 l@(Lexer traits) reset
20   l inputBuffer := l inputBuffer new.
21   l outputBuffer := l outputBuffer new.
22   l lineNumber := 1.
25 l@(Lexer traits) showTokensFrom: src
27   (l newOn: src) do: [| :x | inform: x printString].
30 l@(Lexer traits) isEndOfLine: char [char == $\n].
31 l@(Lexer traits) isEscape: char [char == $\\].
33 l@(Lexer traits) isAtEnd
34 "The lexer has reached its end when the stream is exhausted and the buffer is
35 empty."
37   l outputBuffer isEmpty /\ [l hasMoreCharacters not]
40 l@(Lexer traits) hasMoreCharacters
41 "Answers whether more characters are immediately available."
43   "It is important not to query the source stream, unless the input buffer is
44    actually empty."
45   l inputBuffer isEmpty not \/ [l source isAtEnd not]
48 Lexer traits define: #Error &parents: {DescriptiveError}
49   &slots: {#lineNumber -> 0 "The line number on which the error was detected."}.
50 "An error that occurred in parsing, always requiring a description."
52 l@(Lexer traits) error: description
54   (l Error newDescription:
55     'Line ' ; l lineNumber printString ; ': ' ; description)
56     `>> [lineNumber := l lineNumber. signal]
59 l@(Lexer traits) nextCharacter
60 "To get the next character, either pull one from the buffer or read from the
61 stream of characters. Raise an error if this is used at the end, and advance
62 the line number if a new-line is reached."
63 [| c |
64   c := l inputBuffer isEmpty
65     ifTrue:
66       [l source isAtEnd
67          ifTrue: [l error: 'Unexpected end of stream'].
68        l source next]
69     ifFalse: [l inputBuffer removeLast].
70   (l isEndOfLine: c) ifTrue: [l lineNumber += 1].
71   c
74 l@(Lexer traits) undoCharacter: c
75 "Put the character back into the buffer, and decrement the line number if it's
76 a new-line."
78   (l isEndOfLine: c) ifTrue: [l lineNumber -= 1].
79   l inputBuffer addLast: c
82 l@(Lexer traits) peekCharacter
83 "Grab the next character, but leave it in the buffer, so the position is not
84 advanced."
86   l inputBuffer isEmpty
87     ifTrue: [l undoCharacter: l nextCharacter]
88     ifFalse: [l inputBuffer last]
91 l@(Lexer traits) peekCharacterForwardBy: n
93   l inputBuffer isEmpty
94     ifTrue: [l undoCharacter: l nextCharacter]
95     ifFalse: [l inputBuffer last]
98 l@(Lexer traits) readInteger: radix
99 "The general method for building integers from the raw characters, with a
100 radix (number of digits) parameter. Grab all following digits for the radix,
101 multiplying the accumulator by the radix and adding the numeric equivalent
102 of the character."
103 [| number |
104   number := 0.
105   [l hasMoreCharacters /\ [(l peekCharacter isDigit: radix) \/ [l peekCharacter == $_]]] whileTrue:
106     [| c |
107      ((c := l nextCharacter) toDigit: radix) ifNotNilDo:
108        [| :digit | number := number * radix + digit]].
109   number
112 l@(Lexer traits) readMantissa: radix
113 "Build a floating-point number's fractional part."
114 [| number place |
115   number := 0.
116   place := 1.
117   [l hasMoreCharacters /\ [(l peekCharacter isDigit: radix) \/ [l peekCharacter == $_]]] whileTrue:
118     [| c |
119      ((c := l nextCharacter) toDigit: radix) ifNotNilDo:
120        [| :digit |
121         number := number * radix + digit.
122         place *= radix]].
123   (number as: Float) / (place as: Float)
126 l@(Lexer traits) readExponent: radix
127 "Build a floating-point number's exponent as an integer."
128 [| c |
129   (c := l nextCharacter) == $-
130     ifTrue: [(l readInteger: radix) negated]
131     ifFalse:
132       [c == $+ ifFalse: [l undoCharacter: c]. l readInteger: radix]
135 l@(Lexer traits) newLiteralFor: obj
136 [tokens LiteralToken for: obj].
138 "l@(Lexer traits) newLiteralFor: a@(ByteArray traits)
140   a isEmpty
141     ifTrue: [TODO: 'intern empty array/bytearray/string']
142     ifFalse: [resend]
145 l@(Lexer traits) readNumber
146 "The overall routine for building numbers."
147 [| number isNegative radix c |
148   isNegative := False.
149   radix := 10.
150   (c := l nextCharacter) == $-
151     ifTrue: [isNegative := True]
152     ifFalse: [c == $+ ifFalse: [l undoCharacter: c]].
153   "Now read in all the continuous string of digits possible as an integer."
154   number := l readInteger: radix.
155   "Reaching the end of the lexing stream just finalizes the process."
156   l hasMoreCharacters ifTrue:
157     ["Conditionalize on the next character: it may set up a radix or a decimal."
158      (c := l nextCharacter) == $r \/ [c == $R] ifTrue:
159        [((radix := number) between: 2 and: 36) ifFalse:
160           [l error: 'Number radix must be between 2 and 36.'].
161         number := l readInteger: radix.
162         l hasMoreCharacters
163           ifTrue: [c := l nextCharacter]
164           ifFalse:
165             [^ (l newLiteralFor: (isNegative ifTrue: [number negated] ifFalse: [number]))]].
166      c == $. /\ [l hasMoreCharacters] /\ [l peekCharacter isDigit: radix] ifTrue:
167        [number := (number as: Float) + (l readMantissa: radix).
168         l hasMoreCharacters
169           ifTrue: [c := l nextCharacter]
170           ifFalse:
171             [^ (l newLiteralFor: (isNegative ifTrue: [number negated] ifFalse: [number]))]].
172      c == $e \/ [c == $E]
173        ifTrue:
174          [number := (number as: Float) * ((radix as: Float) raisedTo: (l readExponent: 10))]
175        ifFalse:
176          [l undoCharacter: c]].
177   l newLiteralFor: (isNegative ifTrue: [number negated] ifFalse: [number])
180 l@(Lexer traits) readEscapedCharacter
181 "Language support for character escapes. This should be called at the point
182 after the initial escape is seen, whether as a character or part of a string."
183 [| c |
184   (c := l nextCharacter) caseOf: {
185     $n -> [$\n].
186     $t -> [$\t].
187     $r -> [$\r].
188     $b -> [$\b].
189     $s -> [$\s].
190     $a -> [$\a].
191     $v -> [$\v].
192     $f -> [$\f].
193     $e -> [$\e].
194     $0 -> [$\0].
195     $x ->
196       [((l nextCharacter toDigit: 16) ifNil:
197           [l error: 'Unexpected numeric-escape Character syntax. Expected $\\xNN']) * 16
198          + ((l nextCharacter toDigit: 16) ifNil:
199               [l error: 'Unexpected numeric-escape Character syntax. Expected $\\xNN'])
200          as: ASCIIString Character]
201   } otherwise: [c]
204 l@(Lexer traits) characterFor: c
205 [(l isEscape: c) ifTrue: [l readEscapedCharacter] ifFalse: [c]].
207 l@(Lexer traits) readString
208 "Build a string until the next single-quote character is encountered.
209 Escaping is accounted for."
210 [| c |
211   l newLiteralFor: ([| :result |
212     [(c := l nextCharacter) == $\']
213       whileFalse:
214         [result nextPut: (l characterFor: c)]] writingAs: '')
217 l@(Lexer traits) read: t@(tokens Comment traits)
218 "Build a comment string until the next double-quote character is encountered.
219 Escaping is accounted for."
220 [| c |
221   t for: ([| :result |
222     [(c := l nextCharacter) == $\"]
223       whileFalse:
224         [result nextPut: (l characterFor: c)]] writingAs: '')
227 l@(Lexer traits) nextWordCharactersInto: s@(WriteStream traits)
228 [| c |
229   [l hasMoreCharacters
230      /\ [(c := l peekCharacter) isWhitespace not]
231      /\ [(l WordTerminatingTokens includes: c) not]]
232     whileTrue: [s nextPut: l nextCharacter]
235 l@(Lexer traits) read: type@(tokens Selector traits)
236 "Read a selector symbol into a token."
237 [| result |
238   (result :=
239      [| :result |
240       l hasMoreCharacters /\ [l peekCharacter isDigit] ifFalse:
241         [l nextWordCharactersInto: result]] writingAs: '') isEmpty
242    ifTrue: []
243    ifFalse: [type for: result]
246 l@(Lexer traits) readLiteralPastHash
247 "This handles the literal brace array syntaxes as well as literal symbols."
249   l hasMoreCharacters
250     /\ ['({[\'#' includes: l peekCharacter]
251     ifTrue:
252       [l nextCharacter caseOf: {
253          $\( -> [tokens BeginPattern].
254          $\{ -> [tokens BeginLiteralArray].
255          $\[ -> [tokens BeginLiteralBlock].
256          $\' -> [l newLiteralFor:
257                    ([| :result c |
258                      [(c := l nextCharacter) == $\']
259                        whileFalse:
260                          [result nextPut: (l characterFor: c)]]
261                       writingAs: '') intern].
262          $#  -> [l nextCharacter = $\(
263                    ifTrue: [tokens BeginLiteralParenthesis]
264                    ifFalse: [l error: 'Expected ( after ##']]
265      }]
266     ifFalse:
267       [l newLiteralFor:
268          (#(l nextWordCharactersInto: _) `er writingAs: '') intern]
271 l@(Lexer traits) readCharacter
272 "Read in a single character into a token or an escaped one."
274   l newLiteralFor: (l characterFor: l nextCharacter)
277 l@(Lexer traits) read: w@(tokens Whitespace traits)
278 "A way to preserve the whitespace in the original text. Unused by default."
279 [| result c |
280   result :=
281     [| :result |
282      [c := l nextCharacter.
283       l hasMoreCharacters
284         /\ [c isWhitespace]
285         /\ [(l isEndOfLine: c) not]]
286        whileTrue: [result nextPut: c]] writingAs: ''.
287   l undoCharacter: c.
288   w for: result
291 l@(Lexer traits) skipWhitespace
292 [| c |
293   l hasMoreCharacters ifTrue:
294     [[c := l nextCharacter.
295       l hasMoreCharacters
296         /\ [c isWhitespace]
297         /\ [(l isEndOfLine: c) not]]
298        whileTrue.
299      l undoCharacter: c].
302 l@(Lexer traits) readToken
303 "The overall handler for tokenization, this conditionalizes on the various
304 initializing characters to build the various token objects."
305 "TODO: place these dispatch tables in persistent places, much like a Lisp
306 read-table."
307 [| c |
308   "Consume/discard whitespace first."
309   l skipWhitespace.
310   l hasMoreCharacters
311     ifTrue:
312       [(c := l nextCharacter) caseOf: {
313          $\' -> [l readString].
314          $\" -> [l read: tokens Comment].
315          $$ -> [l readCharacter].
316          $# -> [l readLiteralPastHash].
317          $( -> [tokens BeginParenthesis].
318          $) -> [tokens EndParenthesis].
319          ${ -> [tokens BeginArray].
320          $} -> [tokens EndArray].
321          $[ -> [tokens BeginBlock].
322          $] -> [tokens EndBlock].
323          $@ -> [tokens At].
324          $. -> [tokens EndStatement].
325          $, -> [tokens Comma].
326          $\| -> [tokens BeginVariables].
327          $! -> [tokens Type].
328          $` -> [(l read: tokens MacroSelector) ifNil: [tokens Quote]].
329          $% -> [(l read: tokens DeferredSelector) ifNil: [tokens Eventually]].
330          $\n -> [tokens EndLine]
331        } otherwise:
332          [c isDigit \/ [c == $+ \/ [c == $-] /\ [l peekCharacter isDigit]]
333             ifTrue: [l undoCharacter: c. l readNumber]
334             ifFalse: [l undoCharacter: c.
335                       (l read: tokens Selector)
336                         ifNil: [l error: 'Message selector must not be empty.']]]]
337     ifFalse: [tokens EndStream]
340 l@(Lexer traits) next
342   l outputBuffer isEmpty
343     ifTrue: [l readToken]
344     ifFalse: [l outputBuffer removeFirst]
347 l@(Lexer traits) peek
349   l outputBuffer isEmpty
350     ifTrue: [l outputBuffer addLast: l readToken].
351   l outputBuffer first
354 l@(Lexer traits) peek: n
356   [(l outputBuffer includesKey: n) not]
357     whileTrue: [l outputBuffer addLast: l readToken].
358   l outputBuffer first: n
361 l@(Lexer traits) peekForwardBy: n
363   [(l outputBuffer includesKey: n) not]
364     whileTrue: [l outputBuffer addLast: l readToken].
365   l outputBuffer at: n ifAbsent: [l error: 'Could not find token forward by: ' ; n printString]
368 l@(Lexer traits) undoToken: token
370   l outputBuffer addFirst: token
373 _@(Lexer traits) undoToken: t@(tokens EndStream traits)
374 "Avoid placing EndStream tokens in the output buffer."
375 [t].
377 t@(tokens Token traits) readFrom: s
378 [| next |
379   ((next := (Lexer newOn: s reader) next) is: t)
380     ifTrue: [next]
381     ifFalse: [error: 'The source did not parse into ' ; t printName asAn ; '.']