ce731a7364017c0898c2db52ab2a6592ba9a0f84
[bpt/guile.git] / module / language / ecmascript / parse.scm
1 ;;; ECMAScript for Guile
2
3 ;; Copyright (C) 2009 Free Software Foundation, Inc.
4
5 ;;;; This library is free software; you can redistribute it and/or
6 ;;;; modify it under the terms of the GNU Lesser General Public
7 ;;;; License as published by the Free Software Foundation; either
8 ;;;; version 3 of the License, or (at your option) any later version.
9 ;;;;
10 ;;;; This library is distributed in the hope that it will be useful,
11 ;;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
12 ;;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
13 ;;;; Lesser General Public License for more details.
14 ;;;;
15 ;;;; You should have received a copy of the GNU Lesser General Public
16 ;;;; License along with this library; if not, write to the Free Software
17 ;;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
18
19 ;;; Code:
20
21 (define-module (language ecmascript parse)
22 #:use-module (language ecmascript parse-lalr)
23 #:use-module (language ecmascript tokenize)
24 #:export (read-ecmascript read-ecmascript/1 parse-ecmascript))
25
26 (define (syntax-error message . args)
27 (apply throw 'SyntaxError message args))
28
29 (define (read-ecmascript port)
30 (parse-ecmascript (make-tokenizer port) syntax-error))
31
32 (define (read-ecmascript/1 port)
33 (parse-ecmascript (make-tokenizer/1 port) syntax-error))
34
35 (define *eof-object*
36 (call-with-input-string "" read-char))
37
38 (define parse-ecmascript
39 (lalr-parser
40 ;; terminal (i.e. input) token types
41 (lbrace rbrace lparen rparen lbracket rbracket dot semicolon comma <
42 > <= >= == != === !== + - * % ++ -- << >> >>> & bor ^ ! ~ && or ?
43 colon = += -= *= %= <<= >>= >>>= &= bor= ^= / /=
44
45 break else new var case finally return void catch for switch while
46 continue function this with default if throw delete in try do
47 instanceof typeof null true false
48
49 Identifier StringLiteral NumericLiteral RegexpLiteral)
50
51
52 (Program (SourceElements) -> $1
53 (*eoi*) -> *eof-object*)
54
55 ;;
56 ;; Verily, here we define statements. Expressions are defined
57 ;; afterwards.
58 ;;
59
60 (SourceElement (Statement) -> $1
61 (FunctionDeclaration) -> $1)
62
63 (FunctionDeclaration (function Identifier lparen rparen lbrace FunctionBody rbrace) -> `(var (,$2 (lambda () ,$6)))
64 (function Identifier lparen FormalParameterList rparen lbrace FunctionBody rbrace) -> `(var (,$2 (lambda ,$4 ,$7))))
65 (FunctionExpression (function lparen rparen lbrace FunctionBody rbrace) -> `(lambda () ,$5)
66 (function Identifier lparen rparen lbrace FunctionBody rbrace) -> `(lambda () ,$6)
67 (function lparen FormalParameterList rparen lbrace FunctionBody rbrace) -> `(lambda ,$3 ,$6)
68 (function Identifier lparen FormalParameterList rparen lbrace FunctionBody rbrace) -> `(lambda ,$4 ,$7))
69 (FormalParameterList (Identifier) -> `(,$1)
70 (FormalParameterList comma Identifier) -> `(,@$1 ,$3))
71 (SourceElements (SourceElement) -> $1
72 (SourceElements SourceElement) -> (if (and (pair? $1) (eq? (car $1) 'begin))
73 `(begin ,@(cdr $1) ,$2)
74 `(begin ,$1 ,$2)))
75 (FunctionBody (SourceElements) -> $1)
76
77 (Statement (Block) -> $1
78 (VariableStatement) -> $1
79 (EmptyStatement) -> $1
80 (ExpressionStatement) -> $1
81 (IfStatement) -> $1
82 (IterationStatement) -> $1
83 (ContinueStatement) -> $1
84 (BreakStatement) -> $1
85 (ReturnStatement) -> $1
86 (WithStatement) -> $1
87 (LabelledStatement) -> $1
88 (SwitchStatement) -> $1
89 (ThrowStatement) -> $1
90 (TryStatement) -> $1)
91
92 (Block (lbrace StatementList rbrace) -> `(block ,$2))
93 (StatementList (Statement) -> $1
94 (StatementList Statement) -> (if (and (pair? $1) (eq? (car $1) 'begin))
95 `(begin ,@(cdr $1) ,$2)
96 `(begin ,$1 ,$2)))
97
98 (VariableStatement (var VariableDeclarationList) -> `(var ,@$2))
99 (VariableDeclarationList (VariableDeclaration) -> `(,$1)
100 (VariableDeclarationList comma VariableDeclaration) -> `(,@$1 ,$2))
101 (VariableDeclarationListNoIn (VariableDeclarationNoIn) -> `(,$1)
102 (VariableDeclarationListNoIn comma VariableDeclarationNoIn) -> `(,@$1 ,$2))
103 (VariableDeclaration (Identifier) -> `(,$1)
104 (Identifier Initialiser) -> `(,$1 ,$2))
105 (VariableDeclarationNoIn (Identifier) -> `(,$1)
106 (Identifier Initialiser) -> `(,$1 ,$2))
107 (Initialiser (= AssignmentExpression) -> $2)
108 (InitialiserNoIn (= AssignmentExpressionNoIn) -> $2)
109
110 (EmptyStatement (semicolon) -> '(begin))
111
112 (ExpressionStatement (Expression semicolon) -> $1)
113
114 (IfStatement (if lparen Expression rparen Statement else Statement) -> `(if ,$3 ,$5 ,$7)
115 (if lparen Expression rparen Statement) -> `(if ,$3 ,$5))
116
117 (IterationStatement (do Statement while lparen Expression rparen semicolon) -> `(do ,$2 ,$5)
118
119 (while lparen Expression rparen Statement) -> `(while ,$3 ,$5)
120
121 (for lparen semicolon semicolon rparen Statement) -> `(for #f #f #f ,$6)
122 (for lparen semicolon semicolon Expression rparen Statement) -> `(for #f #f ,$5 ,$7)
123 (for lparen semicolon Expression semicolon rparen Statement) -> `(for #f ,$4 #f ,$7)
124 (for lparen semicolon Expression semicolon Expression rparen Statement) -> `(for #f ,$4 ,$6 ,$8)
125
126 (for lparen ExpressionNoIn semicolon semicolon rparen Statement) -> `(for ,$3 #f #f ,$7)
127 (for lparen ExpressionNoIn semicolon semicolon Expression rparen Statement) -> `(for ,$3 #f ,$6 ,$8)
128 (for lparen ExpressionNoIn semicolon Expression semicolon rparen Statement) -> `(for ,$3 ,$5 #f ,$8)
129 (for lparen ExpressionNoIn semicolon Expression semicolon Expression rparen Statement) -> `(for ,$3 ,$5 ,$7 ,$9)
130
131 (for lparen var VariableDeclarationListNoIn semicolon semicolon rparen Statement) -> `(for (var ,@$4) #f #f ,$8)
132 (for lparen var VariableDeclarationListNoIn semicolon semicolon Expression rparen Statement) -> `(for (var ,@$4) #f ,$7 ,$9)
133 (for lparen var VariableDeclarationListNoIn semicolon Expression semicolon rparen Statement) -> `(for (var ,@$4) ,$6 #f ,$9)
134 (for lparen var VariableDeclarationListNoIn semicolon Expression semicolon Expression rparen Statement) -> `(for (var ,@$4) ,$6 ,$8 ,$10)
135
136 (for lparen LeftHandSideExpression in Expression rparen Statement) -> `(for-in ,$3 ,$5 ,$7)
137 (for lparen var VariableDeclarationNoIn in Expression rparen Statement) -> `(begin (var ,$4) (for-in (ref ,@$4) ,$6 ,$8)))
138
139 (ContinueStatement (continue Identifier semicolon) -> `(continue ,$2)
140 (continue semicolon) -> `(continue))
141
142 (BreakStatement (break Identifier semicolon) -> `(break ,$2)
143 (break semicolon) -> `(break))
144
145 (ReturnStatement (return Expression semicolon) -> `(return ,$2)
146 (return semicolon) -> `(return))
147
148 (WithStatement (with lparen Expression rparen Statement) -> `(with ,$3 ,$5))
149
150 (SwitchStatement (switch lparen Expression rparen CaseBlock) -> `(switch ,$3 ,@$5))
151 (CaseBlock (lbrace rbrace) -> '()
152 (lbrace CaseClauses rbrace) -> $2
153 (lbrace CaseClauses DefaultClause rbrace) -> `(,@$2 ,@$3)
154 (lbrace DefaultClause rbrace) -> `(,$2)
155 (lbrace DefaultClause CaseClauses rbrace) -> `(,@$2 ,@$3))
156 (CaseClauses (CaseClause) -> `(,$1)
157 (CaseClauses CaseClause) -> `(,@$1 ,$2))
158 (CaseClause (case Expression colon) -> `(case ,$2)
159 (case Expression colon StatementList) -> `(case ,$2 ,$4))
160 (DefaultClause (default colon) -> `(default)
161 (default colon StatementList) -> `(default ,$3))
162
163 (LabelledStatement (Identifier colon Statement) -> `(label ,$1 ,$3))
164
165 (ThrowStatement (throw Expression semicolon) -> `(throw ,$2))
166
167 (TryStatement (try Block Catch) -> `(try ,$2 ,$3 #f)
168 (try Block Finally) -> `(try ,$2 #f ,$3)
169 (try Block Catch Finally) -> `(try ,$2 ,$3 ,$4))
170 (Catch (catch lparen Identifier rparen Block) -> `(catch ,$3 ,$5))
171 (Finally (finally Block) -> `(finally ,$2))
172
173 ;;
174 ;; As promised, expressions. We build up to Expression bottom-up, so
175 ;; as to get operator precedence right.
176 ;;
177
178 (PrimaryExpression (this) -> 'this
179 (null) -> 'null
180 (true) -> 'true
181 (false) -> 'false
182 (Identifier) -> `(ref ,$1)
183 (StringLiteral) -> `(string ,$1)
184 (RegexpLiteral) -> `(regexp ,$1)
185 (NumericLiteral) -> `(number ,$1)
186 (ArrayLiteral) -> $1
187 (ObjectLiteral) -> $1
188 (lparen Expression rparen) -> $2)
189
190 (ArrayLiteral (lbracket rbracket) -> '(array)
191 (lbracket Elision rbracket) -> '(array ,@$2)
192 (lbracket ElementList rbracket) -> `(array ,@$2)
193 (lbracket ElementList comma rbracket) -> `(array ,@$2)
194 (lbracket ElementList comma Elision rbracket) -> `(array ,@$2))
195 (ElementList (AssignmentExpression) -> `(,$1)
196 (Elision AssignmentExpression) -> `(,@$1 ,$2)
197 (ElementList comma AssignmentExpression) -> `(,@$1 ,$3)
198 (ElementList comma Elision AssignmentExpression) -> `(,@$1 ,@$3 ,$4))
199 (Elision (comma) -> '((number 0))
200 (Elision comma) -> `(,@$1 (number 0)))
201
202 (ObjectLiteral (lbrace rbrace) -> `(object)
203 (lbrace PropertyNameAndValueList rbrace) -> `(object ,@$2))
204 (PropertyNameAndValueList (PropertyName colon AssignmentExpression) -> `((,$1 ,$3))
205 (PropertyNameAndValueList comma PropertyName colon AssignmentExpression) -> `(,@$1 (,$3 ,$5)))
206 (PropertyName (Identifier) -> $1
207 (StringLiteral) -> (string->symbol $1)
208 (NumericLiteral) -> $1)
209
210 (MemberExpression (PrimaryExpression) -> $1
211 (FunctionExpression) -> $1
212 (MemberExpression lbracket Expression rbracket) -> `(aref ,$1 ,$3)
213 (MemberExpression dot Identifier) -> `(pref ,$1 ,$3)
214 (new MemberExpression Arguments) -> `(new ,$2 ,$3))
215
216 (NewExpression (MemberExpression) -> $1
217 (new NewExpression) -> `(new ,$2 ()))
218
219 (CallExpression (MemberExpression Arguments) -> `(call ,$1 ,$2)
220 (CallExpression Arguments) -> `(call ,$1 ,$2)
221 (CallExpression lbracket Expression rbracket) -> `(aref ,$1 ,$3)
222 (CallExpression dot Identifier) -> `(pref ,$1 ,$3))
223 (Arguments (lparen rparen) -> '()
224 (lparen ArgumentList rparen) -> $2)
225 (ArgumentList (AssignmentExpression) -> `(,$1)
226 (ArgumentList comma AssignmentExpression) -> `(,@$1 ,$3))
227
228 (LeftHandSideExpression (NewExpression) -> $1
229 (CallExpression) -> $1)
230
231 (PostfixExpression (LeftHandSideExpression) -> $1
232 (LeftHandSideExpression ++) -> `(postinc ,$1)
233 (LeftHandSideExpression --) -> `(postdec ,$1))
234
235 (UnaryExpression (PostfixExpression) -> $1
236 (delete UnaryExpression) -> `(delete ,$2)
237 (void UnaryExpression) -> `(void ,$2)
238 (typeof UnaryExpression) -> `(typeof ,$2)
239 (++ UnaryExpression) -> `(preinc ,$2)
240 (-- UnaryExpression) -> `(predec ,$2)
241 (+ UnaryExpression) -> `(+ ,$2)
242 (- UnaryExpression) -> `(- ,$2)
243 (~ UnaryExpression) -> `(~ ,$2)
244 (! UnaryExpression) -> `(! ,$2))
245
246 (MultiplicativeExpression (UnaryExpression) -> $1
247 (MultiplicativeExpression * UnaryExpression) -> `(* ,$1 ,$3)
248 (MultiplicativeExpression / UnaryExpression) -> `(/ ,$1 ,$3)
249 (MultiplicativeExpression % UnaryExpression) -> `(% ,$1 ,$3))
250
251 (AdditiveExpression (MultiplicativeExpression) -> $1
252 (AdditiveExpression + MultiplicativeExpression) -> `(+ ,$1 ,$3)
253 (AdditiveExpression - MultiplicativeExpression) -> `(- ,$1 ,$3))
254
255 (ShiftExpression (AdditiveExpression) -> $1
256 (ShiftExpression << MultiplicativeExpression) -> `(<< ,$1 ,$3)
257 (ShiftExpression >> MultiplicativeExpression) -> `(>> ,$1 ,$3)
258 (ShiftExpression >>> MultiplicativeExpression) -> `(>>> ,$1 ,$3))
259
260 (RelationalExpression (ShiftExpression) -> $1
261 (RelationalExpression < ShiftExpression) -> `(< ,$1 ,$3)
262 (RelationalExpression > ShiftExpression) -> `(> ,$1 ,$3)
263 (RelationalExpression <= ShiftExpression) -> `(<= ,$1 ,$3)
264 (RelationalExpression >= ShiftExpression) -> `(>= ,$1 ,$3)
265 (RelationalExpression instanceof ShiftExpression) -> `(instanceof ,$1 ,$3)
266 (RelationalExpression in ShiftExpression) -> `(in ,$1 ,$3))
267
268 (RelationalExpressionNoIn (ShiftExpression) -> $1
269 (RelationalExpressionNoIn < ShiftExpression) -> `(< ,$1 ,$3)
270 (RelationalExpressionNoIn > ShiftExpression) -> `(> ,$1 ,$3)
271 (RelationalExpressionNoIn <= ShiftExpression) -> `(<= ,$1 ,$3)
272 (RelationalExpressionNoIn >= ShiftExpression) -> `(>= ,$1 ,$3)
273 (RelationalExpressionNoIn instanceof ShiftExpression) -> `(instanceof ,$1 ,$3))
274
275 (EqualityExpression (RelationalExpression) -> $1
276 (EqualityExpression == RelationalExpression) -> `(== ,$1 ,$3)
277 (EqualityExpression != RelationalExpression) -> `(!= ,$1 ,$3)
278 (EqualityExpression === RelationalExpression) -> `(=== ,$1 ,$3)
279 (EqualityExpression !== RelationalExpression) -> `(!== ,$1 ,$3))
280
281 (EqualityExpressionNoIn (RelationalExpressionNoIn) -> $1
282 (EqualityExpressionNoIn == RelationalExpressionNoIn) -> `(== ,$1 ,$3)
283 (EqualityExpressionNoIn != RelationalExpressionNoIn) -> `(!= ,$1 ,$3)
284 (EqualityExpressionNoIn === RelationalExpressionNoIn) -> `(=== ,$1 ,$3)
285 (EqualityExpressionNoIn !== RelationalExpressionNoIn) -> `(!== ,$1 ,$3))
286
287 (BitwiseANDExpression (EqualityExpression) -> $1
288 (BitwiseANDExpression & EqualityExpression) -> `(& ,$1 ,$3))
289 (BitwiseANDExpressionNoIn (EqualityExpressionNoIn) -> $1
290 (BitwiseANDExpressionNoIn & EqualityExpressionNoIn) -> `(& ,$1 ,$3))
291
292 (BitwiseXORExpression (BitwiseANDExpression) -> $1
293 (BitwiseXORExpression ^ BitwiseANDExpression) -> `(^ ,$1 ,$3))
294 (BitwiseXORExpressionNoIn (BitwiseANDExpressionNoIn) -> $1
295 (BitwiseXORExpressionNoIn ^ BitwiseANDExpressionNoIn) -> `(^ ,$1 ,$3))
296
297 (BitwiseORExpression (BitwiseXORExpression) -> $1
298 (BitwiseORExpression bor BitwiseXORExpression) -> `(bor ,$1 ,$3))
299 (BitwiseORExpressionNoIn (BitwiseXORExpressionNoIn) -> $1
300 (BitwiseORExpressionNoIn bor BitwiseXORExpressionNoIn) -> `(bor ,$1 ,$3))
301
302 (LogicalANDExpression (BitwiseORExpression) -> $1
303 (LogicalANDExpression && BitwiseORExpression) -> `(and ,$1 ,$3))
304 (LogicalANDExpressionNoIn (BitwiseORExpressionNoIn) -> $1
305 (LogicalANDExpressionNoIn && BitwiseORExpressionNoIn) -> `(and ,$1 ,$3))
306
307 (LogicalORExpression (LogicalANDExpression) -> $1
308 (LogicalORExpression or LogicalANDExpression) -> `(or ,$1 ,$3))
309 (LogicalORExpressionNoIn (LogicalANDExpressionNoIn) -> $1
310 (LogicalORExpressionNoIn or LogicalANDExpressionNoIn) -> `(or ,$1 ,$3))
311
312 (ConditionalExpression (LogicalORExpression) -> $1
313 (LogicalORExpression ? AssignmentExpression colon AssignmentExpression) -> `(if ,$1 ,$3 ,$5))
314 (ConditionalExpressionNoIn (LogicalORExpressionNoIn) -> $1
315 (LogicalORExpressionNoIn ? AssignmentExpressionNoIn colon AssignmentExpressionNoIn) -> `(if ,$1 ,$3 ,$5))
316
317 (AssignmentExpression (ConditionalExpression) -> $1
318 (LeftHandSideExpression AssignmentOperator AssignmentExpression) -> `(,$2 ,$1 ,$3))
319 (AssignmentExpressionNoIn (ConditionalExpressionNoIn) -> $1
320 (LeftHandSideExpression AssignmentOperator AssignmentExpressionNoIn) -> `(,$2 ,$1 ,$3))
321 (AssignmentOperator (=) -> '=
322 (*=) -> '*=
323 (/=) -> '/=
324 (%=) -> '%=
325 (+=) -> '+=
326 (-=) -> '-=
327 (<<=) -> '<<=
328 (>>=) -> '>>=
329 (>>>=) -> '>>>=
330 (&=) -> '&=
331 (^=) -> '^=
332 (bor=) -> 'bor=)
333
334 (Expression (AssignmentExpression) -> $1
335 (Expression comma AssignmentExpression) -> `(begin ,$1 ,$3))
336 (ExpressionNoIn (AssignmentExpressionNoIn) -> $1
337 (ExpressionNoIn comma AssignmentExpressionNoIn) -> `(begin ,$1 ,$3))))