1 /**
2 This module implements the bytecode compiler
3 ────────────────────────────────────────────────────────────────────────────────
4 Copyright (C) 2021 pillager86.rf.gd
5 
6 This program is free software: you can redistribute it and/or modify it under 
7 the terms of the GNU General Public License as published by the Free Software 
8 Foundation, either version 3 of the License, or (at your option) any later 
9 version.
10 
11 This program is distributed in the hope that it will be useful, but WITHOUT ANY
12 WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A
13 PARTICULAR PURPOSE.  See the GNU General Public License for more details.
14 
15 You should have received a copy of the GNU General Public License along with 
16 this program.  If not, see <https://www.gnu.org/licenses/>.
17 */
18 module mildew.compiler;
19 
20 debug import std.stdio;
21 import std.typecons;
22 import std.variant;
23 
24 import mildew.exceptions;
25 import mildew.lexer;
26 import mildew.parser;
27 import mildew.nodes;
28 import mildew.types;
29 import mildew.util.encode;
30 import mildew.util.stack;
31 import mildew.visitors;
32 import mildew.vm.chunk;
33 import mildew.vm.consttable;
34 import mildew.vm.debuginfo;
35 import mildew.vm.virtualmachine;
36 
37 private enum BREAKLOOP_CODE = uint.max;
38 private enum BREAKSWITCH_CODE = uint.max - 1;
39 private enum CONTINUE_CODE = uint.max - 2;
40 
41 /**
42  * Implements a bytecode compiler that can be used by mildew.vm.virtualmachine. This class is not thread safe and each thread
43  * must use its own Compiler instance. Only one chunk can be compiled at a time.
44  */
45 class Compiler : INodeVisitor
46 {
47 public:
48 
49     /// thrown when a feature is missing
50     class UnimplementedException : Exception
51     {
52         /// constructor
53         this(string msg, string file=__FILE__, size_t line = __LINE__)
54         {
55             super(msg, file, line);
56         }
57     }
58 
59     /// compile code into chunk usable by vm
60     Chunk compile(string source)
61     {
62         import core.memory: GC;
63         import std..string: splitLines;
64         _currentSource = source;
65         _chunk = new Chunk();
66         _compDataStack.push(CompilationData.init);
67         auto lexer = Lexer(source);
68         auto parser = Parser(lexer.tokenize());
69         _debugInfoStack.push(new DebugInfo(source));
70         // for now just expressions
71         auto block = parser.parseProgram();
72         block.accept(this);
73         destroy(block);
74         GC.free(cast(void*)block);
75         block = null;
76         Chunk send = _chunk;
77         _chunk.debugMap[_chunk.bytecode.idup] = _debugInfoStack.pop();
78         _chunk = null; // ensure node functions cannot be used by outsiders at all
79         _compDataStack.pop();
80         _currentSource = null;
81         return send;
82     }
83 
84     /**
85      * This is strictly for use by the Parser to evaluate case expressions and such.
86      */
87     package Chunk compile(StatementNode[] statements)
88     {
89         _chunk = new Chunk();
90         _compDataStack.push(CompilationData.init);
91         _debugInfoStack.push(new DebugInfo(""));
92         auto block = new BlockStatementNode(1, statements);
93         block.accept(this);
94         destroy(block);
95         Chunk send = _chunk;
96         _chunk.debugMap[_chunk.bytecode.idup] = _debugInfoStack.pop();
97         _chunk = null;
98         _compDataStack.pop();
99         return send;
100     }
101 
102 // The visitNode methods are not intended for public use but are required to be public by D language constraints
103 
104     /// handle literal value node (easiest)
105 	Variant visitLiteralNode(LiteralNode lnode)
106     {
107         // want booleans to be booleans not 1
108         if(lnode.value.type == ScriptAny.Type.BOOLEAN)
109         {
110             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(lnode.value.toValue!bool);
111             return Variant(null);
112         }
113 
114         if(lnode.value == ScriptAny(0))
115             _chunk.bytecode ~= OpCode.CONST_0;
116         else if(lnode.value == ScriptAny(1))
117             _chunk.bytecode ~= OpCode.CONST_1;
118         else
119             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(lnode.value);
120 
121         if(lnode.literalToken.type == Token.Type.REGEX)
122             _chunk.bytecode ~= OpCode.REGEX;
123         return Variant(null);
124     }
125 
126     /// handle function literals. The VM should create new functions with the appropriate context
127     ///  when a function is loaded from the const table
128     Variant visitFunctionLiteralNode(FunctionLiteralNode flnode)
129     {
130         auto oldChunk = _chunk.bytecode; // @suppress(dscanner.suspicious.unmodified)
131         _compDataStack.push(CompilationData.init);
132         _compDataStack.top.stackVariables.push(VarTable.init);
133         _debugInfoStack.push(new DebugInfo(_currentSource, flnode.optionalName));
134         ++_funcDepth;
135         _chunk.bytecode = [];
136         foreach(stmt ; flnode.statements)
137             stmt.accept(this);
138         // add a return undefined statement in case missing one
139         _chunk.bytecode ~= OpCode.STACK_1;
140         _chunk.bytecode ~= OpCode.RETURN;
141         // create function
142         ScriptAny func;
143         if(!flnode.isClass)
144             func = new ScriptFunction(
145                 flnode.optionalName == "" ? "<anonymous function>" : flnode.optionalName, 
146                 flnode.argList, _chunk.bytecode, false, flnode.isGenerator, _chunk.constTable);
147         else
148             func = new ScriptFunction(
149                 flnode.optionalName == "" ? "<anonymous class>" : flnode.optionalName,
150                 flnode.argList, _chunk.bytecode, true, false, _chunk.constTable);
151         _chunk.debugMap[_chunk.bytecode.idup] = _debugInfoStack.pop();
152         _chunk.bytecode = oldChunk;
153         _compDataStack.top.stackVariables.pop;
154         _compDataStack.pop();
155         --_funcDepth;
156         _chunk.bytecode ~= OpCode.CONST ~ encodeConst(func);
157         return Variant(null);
158     }
159 
160     /// handle lambdas
161     Variant visitLambdaNode(LambdaNode lnode)
162     {
163         FunctionLiteralNode flnode;
164         if(lnode.returnExpression)
165         {
166             // lambda arrows should be on the same line as the expression unless the author is a psychopath
167             flnode = new FunctionLiteralNode(lnode.argList, [
168                     new ReturnStatementNode(lnode.arrowToken.position.line, lnode.returnExpression)
169                 ], "<lambda>", false);
170         }
171         else
172         {
173             flnode = new FunctionLiteralNode(lnode.argList, lnode.statements, "<lambda>", false);
174         }
175         flnode.accept(this);
176         return Variant(null);
177     }
178 
179     /// handles template strings
180     Variant visitTemplateStringNode(TemplateStringNode tsnode)
181     {
182         foreach(node ; tsnode.nodes)
183         {
184             node.accept(this);
185         }
186         _chunk.bytecode ~= OpCode.CONCAT ~ encode!uint(cast(uint)tsnode.nodes.length);
187         return Variant(null);
188     }
189 
190     /// handle array literals
191 	Variant visitArrayLiteralNode(ArrayLiteralNode alnode)
192     {
193         foreach(node ; alnode.valueNodes)
194         {
195             node.accept(this);
196         }
197         _chunk.bytecode ~= OpCode.ARRAY ~ encode!uint(cast(uint)alnode.valueNodes.length);
198         return Variant(null);
199     }
200 
201     /// handle object literal nodes
202 	Variant visitObjectLiteralNode(ObjectLiteralNode olnode)
203     {
204         assert(olnode.keys.length == olnode.valueNodes.length);
205         for(size_t i = 0; i < olnode.keys.length; ++i)
206         {
207             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(olnode.keys[i]);
208             olnode.valueNodes[i].accept(this);            
209         }
210         _chunk.bytecode ~= OpCode.OBJECT ~ encode(cast(uint)olnode.keys.length);
211         return Variant(null);
212     }
213 
214     /// Class literals. Parser is supposed to make sure string-function pairs match up
215 	Variant visitClassLiteralNode(ClassLiteralNode clnode)
216     {
217         // first make sure the data will fit in a 5 byte instruction
218         if(clnode.classDefinition.methods.length > ubyte.max
219         || clnode.classDefinition.getMethods.length > ubyte.max 
220         || clnode.classDefinition.setMethods.length > ubyte.max
221         || clnode.classDefinition.staticMethods.length > ubyte.max)
222         {
223             throw new ScriptCompileException("Class attributes exceed 255", clnode.classToken);
224         }
225 
226         if(clnode.classDefinition.baseClass)
227             _baseClassStack ~= clnode.classDefinition.baseClass;
228 
229         // method names then their functions
230         immutable ubyte numMethods = cast(ubyte)clnode.classDefinition.methods.length;
231         foreach(methodName ; clnode.classDefinition.methodNames)
232             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(methodName);
233         foreach(methodNode ; clnode.classDefinition.methods)
234             methodNode.accept(this);
235         
236         // getter names then their functions
237         immutable ubyte numGetters = cast(ubyte)clnode.classDefinition.getMethods.length;
238         foreach(getName ; clnode.classDefinition.getMethodNames)
239             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(getName);
240         foreach(getNode ; clnode.classDefinition.getMethods)
241             getNode.accept(this);
242         
243         // setter names then their functions
244         immutable ubyte numSetters = cast(ubyte)clnode.classDefinition.setMethods.length;
245         foreach(setName ; clnode.classDefinition.setMethodNames)
246             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(setName);
247         foreach(setNode ; clnode.classDefinition.setMethods)
248             setNode.accept(this);
249         
250         // static names then their functions
251         immutable ubyte numStatics = cast(ubyte)clnode.classDefinition.staticMethods.length;
252         foreach(staticName ; clnode.classDefinition.staticMethodNames)
253             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(staticName);
254         foreach(staticNode ; clnode.classDefinition.staticMethods)
255             staticNode.accept(this);
256         
257         // constructor (parse guarantees it exists)
258         clnode.classDefinition.constructor.accept(this);
259         // then finally base class
260         if(clnode.classDefinition.baseClass)
261             clnode.classDefinition.baseClass.accept(this);
262         else
263             _chunk.bytecode ~= OpCode.STACK_1;
264 
265         _chunk.bytecode ~= OpCode.CLASS ~ cast(ubyte[])([numMethods, numGetters, numSetters, numStatics]);
266 
267         if(clnode.classDefinition.baseClass)
268             _baseClassStack = _baseClassStack[0..$-1];
269 
270         return Variant(null);
271     }
272 
273     /// handles binary operations
274 	Variant visitBinaryOpNode(BinaryOpNode bonode)
275     {
276         if(bonode.opToken.isAssignmentOperator)
277         {
278             auto remade = reduceAssignment(bonode);
279             handleAssignment(remade.leftNode, remade.opToken, remade.rightNode);
280             return Variant(null);
281         }
282         // push operands
283         bonode.leftNode.accept(this);
284         bonode.rightNode.accept(this);
285         switch(bonode.opToken.type)
286         {
287         case Token.Type.POW:
288             _chunk.bytecode ~= OpCode.POW;
289             break;
290         case Token.Type.STAR:
291             _chunk.bytecode ~= OpCode.MUL;
292             break;
293         case Token.Type.FSLASH:
294             _chunk.bytecode ~= OpCode.DIV;
295             break;
296         case Token.Type.PERCENT:
297             _chunk.bytecode ~= OpCode.MOD;
298             break;
299         case Token.Type.PLUS:
300             _chunk.bytecode ~= OpCode.ADD;
301             break;
302         case Token.Type.DASH:
303             _chunk.bytecode ~= OpCode.SUB;
304             break;
305         case Token.Type.BIT_RSHIFT:
306             _chunk.bytecode ~= OpCode.BITRSH;
307             break;
308         case Token.Type.BIT_URSHIFT:
309             _chunk.bytecode ~= OpCode.BITURSH;
310             break;
311         case Token.Type.BIT_LSHIFT:
312             _chunk.bytecode ~= OpCode.BITLSH;
313             break;
314         case Token.Type.LT:
315             _chunk.bytecode ~= OpCode.LT;
316             break;
317         case Token.Type.LE:
318             _chunk.bytecode ~= OpCode.LE;
319             break;
320         case Token.Type.GT:
321             _chunk.bytecode ~= OpCode.GT;
322             break;
323         case Token.Type.GE:
324             _chunk.bytecode ~= OpCode.GE;
325             break;
326         case Token.Type.EQUALS:
327             _chunk.bytecode ~= OpCode.EQUALS;
328             break;
329         case Token.Type.NEQUALS:
330             _chunk.bytecode ~= OpCode.NEQUALS;
331             break;
332         case Token.Type.STRICT_EQUALS:
333             _chunk.bytecode ~= OpCode.STREQUALS;
334             break;
335         case Token.Type.STRICT_NEQUALS: // TODO add yet another OpCode as an optimization
336             _chunk.bytecode ~= OpCode.STREQUALS;
337             _chunk.bytecode ~= OpCode.NOT;
338             break;
339         case Token.Type.BIT_AND:
340             _chunk.bytecode ~= OpCode.BITAND;
341             break;
342         case Token.Type.BIT_OR:
343             _chunk.bytecode ~= OpCode.BITOR;
344             break;
345         case Token.Type.BIT_XOR:
346             _chunk.bytecode ~= OpCode.BITXOR;
347             break;
348         case Token.Type.AND:
349             _chunk.bytecode ~= OpCode.AND;
350             break;
351         case Token.Type.OR:
352             _chunk.bytecode ~= OpCode.OR;
353             break;
354         default:
355             if(bonode.opToken.isKeyword("instanceof"))
356                 _chunk.bytecode ~= OpCode.INSTANCEOF;
357             else
358                 throw new Exception("Uncaught parser or compiler error: " ~ bonode.toString());
359         }
360         return Variant(null);
361     }
362 
363     /// handle unary operations
364 	Variant visitUnaryOpNode(UnaryOpNode uonode)
365     {
366         switch(uonode.opToken.type)
367         {
368         case Token.Type.BIT_NOT:
369             uonode.operandNode.accept(this);
370             _chunk.bytecode ~= OpCode.BITNOT;
371             break;
372         case Token.Type.NOT:
373             uonode.operandNode.accept(this);
374             _chunk.bytecode ~= OpCode.NOT;
375             break;
376         case Token.Type.DASH:
377             uonode.operandNode.accept(this);
378             _chunk.bytecode ~= OpCode.NEGATE;
379             break;
380         case Token.Type.PLUS:
381             uonode.operandNode.accept(this);
382             break;
383         case Token.Type.INC: {
384             if(!nodeIsAssignable(uonode.operandNode))
385                 throw new ScriptCompileException("Invalid operand for prefix operation", uonode.opToken);
386             auto assignmentNode = reduceAssignment(new BinaryOpNode(Token.createFakeToken(Token.Type.PLUS_ASSIGN,""), 
387                     uonode.operandNode, 
388                     new LiteralNode(Token.createFakeToken(Token.Type.INTEGER, "1"), ScriptAny(1)))
389             );
390             handleAssignment(assignmentNode.leftNode, assignmentNode.opToken, assignmentNode.rightNode); 
391             break;        
392         }
393         case Token.Type.DEC:
394             if(!nodeIsAssignable(uonode.operandNode))
395                 throw new ScriptCompileException("Invalid operand for prefix operation", uonode.opToken);
396             auto assignmentNode = reduceAssignment(new BinaryOpNode(Token.createFakeToken(Token.Type.DASH_ASSIGN,""), 
397                     uonode.operandNode, 
398                     new LiteralNode(Token.createFakeToken(Token.Type.INTEGER, "1"), ScriptAny(1)))
399             );
400             handleAssignment(assignmentNode.leftNode, assignmentNode.opToken, assignmentNode.rightNode);
401             break;
402         default:
403             uonode.operandNode.accept(this);
404             if(uonode.opToken.isKeyword("typeof"))
405                 _chunk.bytecode ~= OpCode.TYPEOF;
406             else
407                 throw new Exception("Uncaught parser error: " ~ uonode.toString());
408         }
409         return Variant(null);
410     }
411 
412     /// Handle x++ and x--
413 	Variant visitPostfixOpNode(PostfixOpNode ponode)
414     {
415         if(!nodeIsAssignable(ponode.operandNode))
416             throw new ScriptCompileException("Invalid operand for postfix operator", ponode.opToken);
417         immutable incOrDec = ponode.opToken.type == Token.Type.INC ? 1 : -1;
418         // first push the original value
419         ponode.operandNode.accept(this);
420         // generate an assignment
421         auto assignmentNode = reduceAssignment(new BinaryOpNode(
422             Token.createFakeToken(Token.Type.PLUS_ASSIGN, ""),
423             ponode.operandNode,
424             new LiteralNode(Token.createFakeToken(Token.Type.IDENTIFIER, "?"), ScriptAny(incOrDec))
425         ));
426         // process the assignment
427         handleAssignment(assignmentNode.leftNode, assignmentNode.opToken, assignmentNode.rightNode);
428         // pop the value of the assignment, leaving original value on stack
429         _chunk.bytecode ~= OpCode.POP;
430         return Variant(null);
431     }
432 
433     /// handle :? operator
434 	Variant visitTerniaryOpNode(TerniaryOpNode tonode)
435     {
436         tonode.conditionNode.accept(this);
437         tonode.onTrueNode.accept(this);
438         tonode.onFalseNode.accept(this);
439         _chunk.bytecode ~= OpCode.TERN;
440         return Variant(null);
441     }
442 
443     /// These should not be directly visited for assignment
444 	Variant visitVarAccessNode(VarAccessNode vanode)
445     {
446         if(varExists(vanode.varToken.text))
447         {
448             auto varMeta = lookupVar(vanode.varToken.text);
449             if(varMeta.funcDepth == _funcDepth && varMeta.stackLocation != -1)
450             {
451                 _chunk.bytecode ~= OpCode.PUSH ~ encode!int(varMeta.stackLocation);
452                 return Variant(null);
453             }
454         }
455         _chunk.bytecode ~= OpCode.GETVAR ~ encodeConst(vanode.varToken.text);
456         return Variant(null);
457     }
458 
459     /// Handle function() calls
460 	Variant visitFunctionCallNode(FunctionCallNode fcnode)
461     {
462         // if returnThis is set this is an easy new op
463         if(fcnode.returnThis)
464         {
465             fcnode.functionToCall.accept(this);
466             foreach(argExpr ; fcnode.expressionArgs)
467                 argExpr.accept(this);
468             _chunk.bytecode ~= OpCode.NEW ~ encode!uint(cast(uint)fcnode.expressionArgs.length);
469             return Variant(null);
470         }
471         else
472         {
473             // if a member access then the "this" must be set to left hand side
474             if(auto man = cast(MemberAccessNode)fcnode.functionToCall)
475             {
476                 if(!cast(SuperNode)man.objectNode)
477                 {
478                     man.objectNode.accept(this); // first put object on stack
479                     _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1); // push it again
480                     auto van = cast(VarAccessNode)man.memberNode;
481                     if(van is null)
482                         throw new ScriptCompileException("Invalid `.` operand", man.dotToken);
483                     _chunk.bytecode ~= OpCode.CONST ~ encodeConst(van.varToken.text);
484                     _chunk.bytecode ~= OpCode.OBJGET; // this places obj as this and the func on stack
485                 }
486                 else
487                 {
488                     _chunk.bytecode ~= OpCode.THIS;
489                     fcnode.functionToCall.accept(this);
490                 }
491             } // else if an array access same concept
492             else if(auto ain = cast(ArrayIndexNode)fcnode.functionToCall)
493             {
494                 if(!cast(SuperNode)ain.objectNode)
495                 {
496                     ain.objectNode.accept(this);
497                     _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1); // push it again
498                     ain.indexValueNode.accept(this);
499                     _chunk.bytecode ~= OpCode.OBJGET; // now the array and function are on stack
500                 }
501                 else
502                 {
503                     _chunk.bytecode ~= OpCode.THIS;
504                     fcnode.functionToCall.accept(this);
505                 }
506             }
507             else // either a variable or literal function, pull this and function
508             {
509                 _chunk.bytecode ~= OpCode.THIS;
510                 fcnode.functionToCall.accept(this);
511                 if(cast(SuperNode)fcnode.functionToCall)
512                 {
513                     // could be a super() constructor call
514                     _chunk.bytecode ~= OpCode.CONST ~ encodeConst("constructor");
515                     _chunk.bytecode ~= OpCode.OBJGET;
516                 }
517             }
518             foreach(argExpr ; fcnode.expressionArgs)
519                 argExpr.accept(this);
520             _chunk.bytecode ~= OpCode.CALL ~ encode!uint(cast(uint)fcnode.expressionArgs.length);
521         }
522         return Variant(null);
523     }
524 
525     /// handle [] operator. This method cannot be used in assignment
526 	Variant visitArrayIndexNode(ArrayIndexNode ainode)
527     {
528         ainode.objectNode.accept(this);
529         ainode.indexValueNode.accept(this);
530         _chunk.bytecode ~= OpCode.OBJGET;
531         return Variant(null);
532     }
533 
534     /// handle . operator. This method cannot be used in assignment
535 	Variant visitMemberAccessNode(MemberAccessNode manode)
536     {
537         manode.objectNode.accept(this);
538         // memberNode has to be a var access node for this to make any sense
539         auto van = cast(VarAccessNode)manode.memberNode;
540         if(van is null)
541             throw new ScriptCompileException("Invalid right operand for `.` operator", manode.dotToken);
542         _chunk.bytecode ~= OpCode.CONST ~ encodeConst(van.varToken.text);
543         _chunk.bytecode ~= OpCode.OBJGET;
544         return Variant(null);
545     }
546 
547     /// handle new operator. visitFunctionCallExpression will handle returnThis field
548 	Variant visitNewExpressionNode(NewExpressionNode nenode)
549     {
550         nenode.functionCallExpression.accept(this);
551         return Variant(null);
552     }
553 
554     /// this should only be directly visited when used by itself
555     Variant visitSuperNode(SuperNode snode)
556     {
557         _chunk.bytecode ~= OpCode.THIS;
558         _chunk.bytecode ~= OpCode.CONST ~ encodeConst("__super__");
559         _chunk.bytecode ~= OpCode.OBJGET;
560         return Variant(null);
561     }
562 
563     /// handle yield statements.
564     Variant visitYieldNode(YieldNode ynode)
565     {
566         // it's just a function call to yield
567         _chunk.bytecode ~= OpCode.STACK_1; // disregard this
568         _chunk.bytecode ~= OpCode.GETVAR ~ encodeConst("yield");
569         if(ynode.yieldExpression)
570             ynode.yieldExpression.accept(this);
571         else
572             _chunk.bytecode ~= OpCode.STACK_1;
573         _chunk.bytecode ~= OpCode.CALL ~ encode!uint(1);
574         return Variant(null);
575     }
576     
577     /// Handle var declaration
578     Variant visitVarDeclarationStatementNode(VarDeclarationStatementNode vdsnode)
579     {
580         _debugInfoStack.top.addLine(_chunk.bytecode.length, vdsnode.line);
581         foreach(expr ; vdsnode.varAccessOrAssignmentNodes)
582         {
583             string varName = "";
584             DestructureTargetNode destr = null;
585 
586             // is it a validated binop node
587             if(auto bopnode = cast(BinaryOpNode)expr)
588             {
589                 // if the right hand side is a function literal, we can rename it
590                 if(auto flnode = cast(FunctionLiteralNode)bopnode.rightNode)
591                 {
592                     if(flnode.optionalName == "")
593                         flnode.optionalName = bopnode.leftNode.toString();
594                 }
595                 else if(auto clsnode = cast(ClassLiteralNode)bopnode.rightNode)
596                 {
597                     if(clsnode.classDefinition.className == "<anonymous class>")
598                     {
599                         clsnode.classDefinition.constructor.optionalName = bopnode.leftNode.toString();
600                         clsnode.classDefinition.className = bopnode.leftNode.toString();
601                     }
602                 }
603                 if(auto destru = cast(DestructureTargetNode)bopnode.leftNode)
604                 {
605                     bopnode.rightNode.accept(this);
606                     destr = destru;
607                 }
608                 else 
609                 {
610                     auto van = cast(VarAccessNode)bopnode.leftNode;
611                     bopnode.rightNode.accept(this); // push value to stack
612                     varName = van.varToken.text;
613                 }
614             }
615             else if(auto van = cast(VarAccessNode)expr)
616             {
617                 _chunk.bytecode ~= OpCode.STACK_1; // push undefined
618                 varName = van.varToken.text;
619             }
620             else
621                 throw new Exception("Parser failure or unimplemented feature: " ~ vdsnode.toString());
622 
623             // make sure it's not overwriting a stack value
624             /*if(vdsnode.qualifier.text != "var")
625             {
626                 immutable lookup = cast(immutable)lookupVar(varName);
627                 if(lookup.isDefined && lookup.stackLocation != -1)
628                     throw new ScriptCompileException("Attempt to redeclare stack variable " ~ varName, 
629                             vdsnode.qualifier);
630                 defineVar(varName, VarMetadata(true, -1, cast(int)_funcDepth, vdsnode.qualifier.text == "const"));
631             }*/
632 
633             if(vdsnode.qualifier.text != "var" && vdsnode.qualifier.text != "let" && vdsnode.qualifier.text != "const")
634                 throw new Exception("Parser failed to parse variable declaration");
635 
636             if(destr)
637             {
638                 for(size_t i = 0; i < destr.varNames.length; ++i)
639                 {
640                     _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
641                     if(destr.isObject)
642                         _chunk.bytecode ~= OpCode.CONST ~ encodeConst(destr.varNames[i]);
643                     else
644                         _chunk.bytecode ~= OpCode.CONST ~ encodeConst(i);
645                     _chunk.bytecode ~= OpCode.OBJGET;
646                     if(vdsnode.qualifier.text == "var")
647                         _chunk.bytecode ~= OpCode.DECLVAR ~ encodeConst(destr.varNames[i]);
648                     else if(vdsnode.qualifier.text == "let")
649                         _chunk.bytecode ~= OpCode.DECLLET ~ encodeConst(destr.varNames[i]);
650                     else if(vdsnode.qualifier.text == "const")
651                         _chunk.bytecode ~= OpCode.DECLCONST ~ encodeConst(destr.varNames[i]);
652                 }
653                 if(destr.remainderName)
654                 {
655                     if(!destr.isObject)
656                     {
657                         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
658                         _chunk.bytecode ~= OpCode.CONST ~ encodeConst("slice");
659                         _chunk.bytecode ~= OpCode.OBJGET;
660                         _chunk.bytecode ~= OpCode.CONST ~ encodeConst(destr.varNames.length);
661                         _chunk.bytecode ~= OpCode.CALL ~ encode!uint(1);
662                     }
663                     if(vdsnode.qualifier.text == "var")
664                         _chunk.bytecode ~= OpCode.DECLVAR ~ encodeConst(destr.remainderName);
665                     else if(vdsnode.qualifier.text == "let")
666                         _chunk.bytecode ~= OpCode.DECLLET ~ encodeConst(destr.remainderName);
667                     else if(vdsnode.qualifier.text == "const")
668                         _chunk.bytecode ~= OpCode.DECLCONST ~ encodeConst(destr.remainderName);
669                 }
670                 else
671                 {
672                     _chunk.bytecode ~= OpCode.POP;
673                 }
674             }
675             else
676             {
677                 if(vdsnode.qualifier.text == "var")
678                     _chunk.bytecode ~= OpCode.DECLVAR ~ encodeConst(varName);
679                 else if(vdsnode.qualifier.text == "let")
680                     _chunk.bytecode ~= OpCode.DECLLET ~ encodeConst(varName);
681                 else if(vdsnode.qualifier.text == "const")
682                     _chunk.bytecode ~= OpCode.DECLCONST ~ encodeConst(varName);
683             }
684         }
685         return Variant(null);
686     }
687 
688     /// handle {} braces
689 	Variant visitBlockStatementNode(BlockStatementNode bsnode)
690     {
691         import std.conv: to;
692         _debugInfoStack.top.addLine(_chunk.bytecode.length, bsnode.line);
693         // if there are no declarations at the top level the scope op can be omitted
694         bool omitScope = true;
695         foreach(stmt ; bsnode.statementNodes)
696         {
697             if(cast(VarDeclarationStatementNode)stmt
698             || cast(FunctionDeclarationStatementNode)stmt 
699             || cast(ClassDeclarationStatementNode)stmt)
700             {
701                 omitScope = false;
702                 break;
703             }
704         }
705         if(!omitScope)
706         {
707             ++_compDataStack.top.depthCounter;
708             _compDataStack.top.stackVariables.push(VarTable.init);
709 
710             _chunk.bytecode ~= OpCode.OPENSCOPE;
711         }
712         foreach(stmt ; bsnode.statementNodes)
713             stmt.accept(this);
714         
715         if(!omitScope)
716         {
717             _chunk.bytecode ~= OpCode.CLOSESCOPE;
718 
719             _compDataStack.top.stackVariables.pop();
720             --_compDataStack.top.depthCounter;
721         }
722         return Variant(null);
723     }
724 
725     /// emit if statements
726 	Variant visitIfStatementNode(IfStatementNode isnode)
727     {
728         _debugInfoStack.top.addLine(_chunk.bytecode.length, isnode.line);
729         isnode.onTrueStatement = new BlockStatementNode(isnode.onTrueStatement.line, [isnode.onTrueStatement]);
730         if(isnode.onFalseStatement)
731             isnode.onFalseStatement = new BlockStatementNode(isnode.onFalseStatement.line, [isnode.onFalseStatement]);
732         if(isnode.onFalseStatement)
733         {
734             if(cast(VarDeclarationStatementNode)isnode.onFalseStatement)
735                 isnode.onFalseStatement = new BlockStatementNode(isnode.onFalseStatement.line, 
736                         [isnode.onFalseStatement]);
737         }
738         isnode.conditionNode.accept(this);
739         auto length = cast(int)_chunk.bytecode.length;
740         auto jmpFalseToPatch = genJmpFalse();
741         isnode.onTrueStatement.accept(this);
742         auto length2 = cast(int)_chunk.bytecode.length;
743         auto jmpOverToPatch = genJmp();
744         *cast(int*)(_chunk.bytecode.ptr + jmpFalseToPatch) = cast(int)_chunk.bytecode.length - length;
745         length = cast(int)_chunk.bytecode.length;
746         if(isnode.onFalseStatement !is null)
747         {
748             isnode.onFalseStatement.accept(this);
749         }
750         *cast(int*)(_chunk.bytecode.ptr + jmpOverToPatch) = cast(int)_chunk.bytecode.length - length2;
751 
752         return Variant(null);
753     }
754 
755     /// Switch statements
756 	Variant visitSwitchStatementNode(SwitchStatementNode ssnode)
757     {
758         _debugInfoStack.top.addLine(_chunk.bytecode.length, ssnode.line);
759 
760         size_t[ScriptAny] unpatchedJumpTbl;
761         size_t statementCounter = 0;        
762         
763         ++_compDataStack.top.loopOrSwitchStack;
764         // generate unpatched jump array
765         foreach(key, value ; ssnode.switchBody.jumpTable)
766         {
767             unpatchedJumpTbl[key] = genJmpTableEntry(key);
768         }
769         _chunk.bytecode ~= OpCode.ARRAY ~ encode!uint(cast(uint)ssnode.switchBody.jumpTable.length);
770         // generate expression to test
771         ssnode.expressionNode.accept(this);
772         // generate switch statement
773         immutable unpatchedSwitchParam = genSwitchStatement();
774         bool patched = false;
775         // generate each statement, patching along the way
776         ++_compDataStack.top.depthCounter;
777         _compDataStack.top.stackVariables.push(VarTable.init);
778         _chunk.bytecode ~= OpCode.OPENSCOPE;
779         foreach(stmt ; ssnode.switchBody.statementNodes)
780         {
781             uint patchData = cast(uint)_chunk.bytecode.length;
782             foreach(k, v ; ssnode.switchBody.jumpTable)
783             {
784                 if(v == statementCounter)
785                 {
786                     immutable ptr = unpatchedJumpTbl[k];
787                     _chunk.bytecode[ptr .. ptr + 4] = encodeConst(patchData)[0..4];
788                 }
789             }
790             // could also be default in which case we patch the switch
791             if(statementCounter == ssnode.switchBody.defaultStatementID)
792             {
793                 *cast(uint*)(_chunk.bytecode.ptr + unpatchedSwitchParam) = patchData;
794                 patched = true;
795             }
796             stmt.accept(this);
797             ++statementCounter;
798         }
799         _chunk.bytecode ~= OpCode.CLOSESCOPE;
800         _compDataStack.top.stackVariables.pop();
801         --_compDataStack.top.depthCounter;
802         immutable breakLocation = _chunk.bytecode.length;
803         if(!patched)
804         {
805             *cast(uint*)(_chunk.bytecode.ptr + unpatchedSwitchParam) = cast(uint)breakLocation;
806         }
807         --_compDataStack.top.loopOrSwitchStack;
808 
809         patchBreaksAndContinues("", breakLocation, breakLocation, _compDataStack.top.depthCounter, 
810                 _compDataStack.top.loopOrSwitchStack);
811         removePatches();
812 
813         return Variant(null);
814     }
815 
816     /// Handle while loops
817 	Variant visitWhileStatementNode(WhileStatementNode wsnode)
818     {
819         _debugInfoStack.top.addLine(_chunk.bytecode.length, wsnode.line);
820         ++_compDataStack.top.loopOrSwitchStack;
821         immutable length0 = _chunk.bytecode.length;
822         immutable continueLocation = length0;
823         wsnode.conditionNode.accept(this);
824         immutable length1 = _chunk.bytecode.length;
825         immutable jmpFalse = genJmpFalse();
826         wsnode.bodyNode.accept(this);
827         immutable length2 = _chunk.bytecode.length;
828         immutable jmp = genJmp();
829         immutable breakLocation = _chunk.bytecode.length;
830         *cast(int*)(_chunk.bytecode.ptr + jmp) = -cast(int)(length2 - length0);
831         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = cast(int)(_chunk.bytecode.length - length1);
832         // patch gotos
833         patchBreaksAndContinues(wsnode.label, breakLocation, continueLocation,
834                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
835         --_compDataStack.top.loopOrSwitchStack;
836         removePatches();
837         return Variant(null);
838     }
839 
840     /// do-while loops
841 	Variant visitDoWhileStatementNode(DoWhileStatementNode dwsnode)
842     {
843         _debugInfoStack.top.addLine(_chunk.bytecode.length, dwsnode.line);
844         ++_compDataStack.top.loopOrSwitchStack;
845         immutable doWhile = _chunk.bytecode.length;
846         dwsnode.bodyNode.accept(this);
847         immutable continueLocation = _chunk.bytecode.length;
848         dwsnode.conditionNode.accept(this);
849         _chunk.bytecode ~= OpCode.NOT;
850         immutable whileCondition = _chunk.bytecode.length;
851         immutable jmpFalse = genJmpFalse();
852         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = -cast(int)(whileCondition - doWhile);
853         immutable breakLocation = _chunk.bytecode.length;
854         patchBreaksAndContinues(dwsnode.label, breakLocation, continueLocation, _compDataStack.top.depthCounter,
855                 _compDataStack.top.loopOrSwitchStack);
856         --_compDataStack.top.loopOrSwitchStack;
857         removePatches();
858         return Variant(null);
859     }
860 
861     /// handle regular for loops
862 	Variant visitForStatementNode(ForStatementNode fsnode)
863     {
864         _debugInfoStack.top.addLine(_chunk.bytecode.length, fsnode.line);
865         ++_compDataStack.top.loopOrSwitchStack;
866         // set up stack variables
867         // handleStackDeclaration(fsnode.varDeclarationStatement);
868         ++_compDataStack.top.depthCounter;
869         _chunk.bytecode ~= OpCode.OPENSCOPE;
870         if(fsnode.varDeclarationStatement)
871             fsnode.varDeclarationStatement.accept(this);
872         immutable length0 = _chunk.bytecode.length;
873         fsnode.conditionNode.accept(this);
874         immutable length1 = _chunk.bytecode.length;
875         immutable jmpFalse = genJmpFalse();
876         fsnode.bodyNode.accept(this);
877         immutable continueLocation = _chunk.bytecode.length;
878         // increment is a single expression not a statement so we must add a pop
879         fsnode.incrementNode.accept(this);
880         _chunk.bytecode ~= OpCode.POP;
881         immutable length2 = _chunk.bytecode.length;
882         immutable jmp = genJmp();
883         immutable breakLocation = _chunk.bytecode.length;
884         // handleStackCleanup(fsnode.varDeclarationStatement);
885         _chunk.bytecode ~= OpCode.CLOSESCOPE;
886         // patch jmps
887         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = cast(int)(breakLocation - length1);
888         *cast(int*)(_chunk.bytecode.ptr + jmp) = -cast(int)(length2 - length0);
889         patchBreaksAndContinues(fsnode.label, breakLocation, continueLocation, _compDataStack.top.depthCounter,
890                 _compDataStack.top.loopOrSwitchStack);
891         --_compDataStack.top.loopOrSwitchStack;
892         --_compDataStack.top.depthCounter;
893         removePatches();
894         return Variant(null);
895     }
896 
897     /// TODO
898 	Variant visitForOfStatementNode(ForOfStatementNode fosnode)
899     {
900         _debugInfoStack.top.addLine(_chunk.bytecode.length, fosnode.line);
901         string[] varNames;
902         foreach(van ; fosnode.varAccessNodes)
903             varNames ~= van.varToken.text;
904         fosnode.objectToIterateNode.accept(this);
905         _chunk.bytecode ~= OpCode.ITER;
906         ++_stackVarCounter;
907         _chunk.bytecode ~= OpCode.STACK_1;
908         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-2);
909         _chunk.bytecode ~= OpCode.CALL ~ encode!uint(0);
910         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
911         ++_stackVarCounter;
912         ++_compDataStack.top.forOfDepth;
913         _chunk.bytecode ~= OpCode.CONST ~ encodeConst("done");
914         _chunk.bytecode ~= OpCode.OBJGET;
915         _chunk.bytecode ~= OpCode.NOT;
916         immutable loop = _chunk.bytecode.length;
917         immutable jmpFalse = genJmpFalse();
918         _chunk.bytecode ~= OpCode.OPENSCOPE;
919         if(varNames.length == 1)
920         {
921             _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
922             _chunk.bytecode ~= OpCode.CONST ~ encodeConst("value");
923             _chunk.bytecode ~= OpCode.OBJGET;
924             _chunk.bytecode ~= (fosnode.qualifierToken.text == "let" ? OpCode.DECLLET : OpCode.DECLCONST)
925                 ~ encodeConst(varNames[0]);
926         }
927         else if(varNames.length == 2)
928         {
929             _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
930             _chunk.bytecode ~= OpCode.CONST ~ encodeConst("key");
931             _chunk.bytecode ~= OpCode.OBJGET;
932             _chunk.bytecode ~= (fosnode.qualifierToken.text == "let" ? OpCode.DECLLET : OpCode.DECLCONST)
933                 ~ encodeConst(varNames[0]);
934             _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
935             _chunk.bytecode ~= OpCode.CONST ~ encodeConst("value");
936             _chunk.bytecode ~= OpCode.OBJGET;
937             _chunk.bytecode ~= (fosnode.qualifierToken.text == "let" ? OpCode.DECLLET : OpCode.DECLCONST)
938                 ~ encodeConst(varNames[1]);
939         }
940         ++_compDataStack.top.loopOrSwitchStack;
941         fosnode.bodyNode.accept(this);
942         immutable continueLocation = _chunk.bytecode.length;
943         _chunk.bytecode ~= OpCode.POP;
944         _chunk.bytecode ~= OpCode.STACK_1;
945         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-2);
946         _chunk.bytecode ~= OpCode.CALL ~ encode!uint(0);
947         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
948         _chunk.bytecode ~= OpCode.CONST ~ encodeConst("done");
949         _chunk.bytecode ~= OpCode.OBJGET;
950         _chunk.bytecode ~= OpCode.NOT;
951         _chunk.bytecode ~= OpCode.CLOSESCOPE;
952         immutable loopAgain = _chunk.bytecode.length;
953         immutable jmp = genJmp();
954         *cast(int*)(_chunk.bytecode.ptr + jmp) = -cast(int)(loopAgain - loop);
955         immutable breakLocation = _chunk.bytecode.length;
956         _chunk.bytecode ~= OpCode.CLOSESCOPE;
957         immutable endLoop = _chunk.bytecode.length;
958         _chunk.bytecode ~= OpCode.POPN ~ encode!uint(2);
959         --_compDataStack.top.forOfDepth;
960         _stackVarCounter -= 2;
961         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = cast(int)(endLoop - loop);
962         patchBreaksAndContinues(fosnode.label, breakLocation, continueLocation, 
963                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
964         --_compDataStack.top.loopOrSwitchStack;
965         removePatches();
966         return Variant(null);
967     }
968 
969     /// TODO
970 	Variant visitBreakStatementNode(BreakStatementNode bsnode)
971     {
972         _debugInfoStack.top.addLine(_chunk.bytecode.length, bsnode.line);
973         immutable patchLocation = _chunk.bytecode.length + 1;
974         _chunk.bytecode ~= OpCode.GOTO ~ encode(uint.max) ~ cast(ubyte)0;
975         _compDataStack.top.breaksToPatch ~= BreakOrContinueToPatch(bsnode.label, patchLocation,
976                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
977         return Variant(null);
978     }
979 
980     /// TODO
981 	Variant visitContinueStatementNode(ContinueStatementNode csnode)
982     {
983         _debugInfoStack.top.addLine(_chunk.bytecode.length, csnode.line);
984         immutable patchLocation = _chunk.bytecode.length + 1;
985         _chunk.bytecode ~= OpCode.GOTO ~ encode(uint.max - 1) ~ cast(ubyte)0;
986         _compDataStack.top.continuesToPatch ~= BreakOrContinueToPatch(csnode.label, patchLocation,
987                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
988         return Variant(null);
989     }
990 
991     /// Return statements
992 	Variant visitReturnStatementNode(ReturnStatementNode rsnode)
993     {
994         _debugInfoStack.top.addLine(_chunk.bytecode.length, rsnode.line);
995         immutable numPops = _compDataStack.top.forOfDepth * 2;
996         if(numPops == 1)
997             _chunk.bytecode ~= OpCode.POP;
998         else if(numPops > 1)
999             _chunk.bytecode ~= OpCode.POPN ~ encode!uint(numPops);
1000         if(rsnode.expressionNode !is null)
1001             rsnode.expressionNode.accept(this);
1002         else
1003             _chunk.bytecode ~= OpCode.STACK_1;
1004         _chunk.bytecode ~= OpCode.RETURN;
1005         return Variant(null);
1006     }
1007 
1008     /// function declarations
1009 	Variant visitFunctionDeclarationStatementNode(FunctionDeclarationStatementNode fdsnode)
1010     {
1011         _debugInfoStack.top.addLine(_chunk.bytecode.length, fdsnode.line);
1012         // easy, reduce it to a let fname = function(){...} VarDeclarationStatement
1013         auto vdsn = new VarDeclarationStatementNode(
1014             fdsnode.line,
1015             Token.createFakeToken(Token.Type.KEYWORD, "let"), [
1016                 new BinaryOpNode(
1017                     Token.createFakeToken(Token.Type.ASSIGN, ""),
1018                     new VarAccessNode(Token.createFakeToken(Token.Type.IDENTIFIER, fdsnode.name)),
1019                     new FunctionLiteralNode(
1020                         fdsnode.argNames, fdsnode.statementNodes, fdsnode.name, false, fdsnode.isGenerator
1021                     )
1022                 )
1023             ]
1024         );
1025         vdsn.accept(this);
1026         return Variant(null);
1027     }
1028 
1029     /// Throw statement
1030 	Variant visitThrowStatementNode(ThrowStatementNode tsnode)
1031     {
1032         _debugInfoStack.top.addLine(_chunk.bytecode.length, tsnode.line);
1033         tsnode.expressionNode.accept(this);
1034         _chunk.bytecode ~= OpCode.THROW;
1035         return Variant(null);
1036     }
1037 
1038     /// Try catch
1039 	Variant visitTryCatchBlockStatementNode(TryCatchBlockStatementNode tcbsnode)
1040     {
1041         _debugInfoStack.top.addLine(_chunk.bytecode.length, tcbsnode.line);
1042         // emit try block
1043         immutable tryToPatch = genTry();
1044         tcbsnode.tryBlockNode.accept(this);
1045         _chunk.bytecode ~= OpCode.ENDTRY;
1046         immutable length0 = cast(int)_chunk.bytecode.length;
1047         immutable jmpToPatch = genJmp();
1048         *cast(uint*)(_chunk.bytecode.ptr + tryToPatch) = cast(uint)_chunk.bytecode.length;
1049         // emit catch block
1050         immutable omitScope = tcbsnode.exceptionName == ""? true: false;
1051         if(!omitScope)
1052         {
1053             ++_compDataStack.top.depthCounter;
1054             _compDataStack.top.stackVariables.push(VarTable.init);
1055             _chunk.bytecode ~= OpCode.OPENSCOPE;
1056         }
1057         if(tcbsnode.catchBlockNode)
1058         {
1059             _chunk.bytecode ~= OpCode.LOADEXC;
1060             if(!omitScope)
1061                 _chunk.bytecode ~= OpCode.DECLLET ~ encodeConst(tcbsnode.exceptionName);
1062             else
1063                 _chunk.bytecode ~= OpCode.POP;
1064             tcbsnode.catchBlockNode.accept(this);
1065         }
1066         if(!omitScope)
1067         {
1068             --_compDataStack.top.depthCounter;
1069             _compDataStack.top.stackVariables.pop();
1070             _chunk.bytecode ~= OpCode.CLOSESCOPE;
1071         }
1072         *cast(int*)(_chunk.bytecode.ptr + jmpToPatch) = cast(int)_chunk.bytecode.length - length0;
1073         // emit finally block
1074         if(tcbsnode.finallyBlockNode)
1075         {
1076             tcbsnode.finallyBlockNode.accept(this);
1077             if(tcbsnode.catchBlockNode is null)
1078                 _chunk.bytecode ~= OpCode.RETHROW;
1079         }
1080         return Variant(null);
1081     }
1082 
1083     /// delete statement. can be used on ArrayIndexNode or MemberAccessNode
1084 	Variant visitDeleteStatementNode(DeleteStatementNode dsnode)
1085     {
1086         _debugInfoStack.top.addLine(_chunk.bytecode.length, dsnode.line);
1087         if(auto ain = cast(ArrayIndexNode)dsnode.memberAccessOrArrayIndexNode)
1088         {
1089             ain.objectNode.accept(this);
1090             ain.indexValueNode.accept(this);
1091         }
1092         else if(auto man = cast(MemberAccessNode)dsnode.memberAccessOrArrayIndexNode)
1093         {
1094             man.objectNode.accept(this);
1095             auto van = cast(VarAccessNode)man.memberNode;
1096             if(van is null)
1097                 throw new Exception("Parser failure in delete statement");
1098             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(van.varToken.text);
1099         }
1100         else
1101             throw new ScriptCompileException("Invalid operand to delete", dsnode.deleteToken);
1102         _chunk.bytecode ~= OpCode.DEL;
1103         return Variant(null);
1104     }
1105 
1106     /// Class declarations. Reduce to let leftHand = classExpression
1107 	Variant visitClassDeclarationStatementNode(ClassDeclarationStatementNode cdsnode)
1108     {
1109         _debugInfoStack.top.addLine(_chunk.bytecode.length, cdsnode.line);
1110         auto reduction = new VarDeclarationStatementNode(
1111             Token.createFakeToken(Token.Type.KEYWORD, "let"),
1112             [
1113                 new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, "="),
1114                     new VarAccessNode(Token.createFakeToken(Token.Type.IDENTIFIER, cdsnode.classDefinition.className)),
1115                     new ClassLiteralNode(cdsnode.classToken, cdsnode.classDefinition))
1116             ]);
1117         reduction.accept(this);
1118         return Variant(null);
1119     }
1120 
1121     /// handle expression statements
1122 	Variant visitExpressionStatementNode(ExpressionStatementNode esnode)
1123     {
1124         _debugInfoStack.top.addLine(_chunk.bytecode.length, esnode.line);
1125         if(esnode.expressionNode is null)
1126             return Variant(null);
1127         esnode.expressionNode.accept(this);
1128         _chunk.bytecode ~= OpCode.POP;
1129         return Variant(null);
1130     }
1131 
1132 private:
1133     static const int UNPATCHED_JMP = 262_561_909;
1134     static const uint UNPATCHED_JMPENTRY = 3_735_890_861;
1135     static const uint UNPATCHED_TRY_GOTO = uint.max;
1136 
1137     size_t addStackVar(string name, bool isConst)
1138     {
1139         size_t id = _stackVarCounter++;
1140         defineVar(name, VarMetadata(true, cast(int)id, cast(int)_funcDepth, isConst));
1141         return id;
1142     }
1143 
1144     void defineVar(string name, VarMetadata vmeta)
1145     {
1146         _compDataStack.top.stackVariables.top[name] = vmeta;
1147     }
1148 
1149     ubyte[] encodeConst(T)(T value)
1150     {
1151         return encode(_chunk.constTable.addValueUint(ScriptAny(value)));
1152     }
1153 
1154     ubyte[] encodeConst(T : ScriptAny)(T value)
1155     {
1156         return encode(_chunk.constTable.addValueUint(value));
1157     }
1158 
1159     /// The return value MUST BE USED
1160     size_t genSwitchStatement()
1161     {
1162         immutable switchParam = _chunk.bytecode.length + 1;
1163         _chunk.bytecode ~= OpCode.SWITCH ~ encode!uint(UNPATCHED_JMPENTRY);
1164         return switchParam;
1165     }
1166 
1167     /// The return value MUST BE USED
1168     size_t genJmp()
1169     {
1170         _chunk.bytecode ~= OpCode.JMP ~ encode!int(UNPATCHED_JMP);
1171         return _chunk.bytecode.length - int.sizeof;
1172     }
1173 
1174     /// The return value MUST BE USED
1175     size_t genJmpFalse()
1176     {
1177         _chunk.bytecode ~= OpCode.JMPFALSE ~ encode!int(UNPATCHED_JMP);
1178         return _chunk.bytecode.length - int.sizeof;
1179     }
1180 
1181     /// The return value MUST BE USED
1182     size_t genJmpTableEntry(ScriptAny value)
1183     {
1184         _chunk.bytecode ~= OpCode.CONST ~ encodeConst(value);
1185         immutable constEntry = _chunk.bytecode.length + 1;
1186         _chunk.bytecode ~= OpCode.CONST ~ encode!uint(UNPATCHED_JMPENTRY);
1187         _chunk.bytecode ~= OpCode.ARRAY ~ encode!uint(2);
1188         return constEntry;
1189     }
1190 
1191     /// The return value MUST BE USED
1192     size_t genTry()
1193     {
1194         _chunk.bytecode ~= OpCode.TRY ~ encode!uint(uint.max);
1195         return _chunk.bytecode.length - uint.sizeof;
1196     }
1197 
1198     void handleAssignment(ExpressionNode leftExpr, Token opToken, ExpressionNode rightExpr)
1199     {
1200         // in case we are assigning to object access expressions
1201         if(auto classExpr = cast(ClassLiteralNode)rightExpr)
1202         {
1203             if(classExpr.classDefinition.className == ""
1204             || classExpr.classDefinition.className == "<anonymous class>")
1205                 classExpr.classDefinition.constructor.optionalName = leftExpr.toString();
1206         }
1207         else if(auto funcLit = cast(FunctionLiteralNode)rightExpr)
1208         {
1209             if(funcLit.optionalName == "" || funcLit.optionalName == "<anonymous function>")
1210                 funcLit.optionalName = leftExpr.toString();
1211         }
1212         if(auto van = cast(VarAccessNode)leftExpr)
1213         {
1214             rightExpr.accept(this);
1215             if(varExists(van.varToken.text))
1216             {
1217                 bool isConst; // @suppress(dscanner.suspicious.unmodified)
1218                 immutable varMeta = cast(immutable)lookupVar(van.varToken.text);
1219                 if(varMeta.stackLocation != -1)
1220                 {
1221                     if(varMeta.isConst)
1222                         throw new ScriptCompileException("Cannot reassign stack const " ~ van.varToken.text, 
1223                                 van.varToken);
1224                     _chunk.bytecode ~= OpCode.SET ~ encode!uint(cast(uint)varMeta.stackLocation);
1225                     return;
1226                 }
1227             }
1228             _chunk.bytecode ~= OpCode.SETVAR ~ encodeConst(van.varToken.text);
1229         }
1230         else if(auto man = cast(MemberAccessNode)leftExpr)
1231         {
1232             man.objectNode.accept(this);
1233             auto van = cast(VarAccessNode)man.memberNode;
1234             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(van.varToken.text);
1235             rightExpr.accept(this);
1236             _chunk.bytecode ~= OpCode.OBJSET;
1237         }
1238         else if(auto ain = cast(ArrayIndexNode)leftExpr)
1239         {
1240             ain.objectNode.accept(this);
1241             ain.indexValueNode.accept(this);
1242             rightExpr.accept(this);
1243             _chunk.bytecode ~= OpCode.OBJSET;
1244         }
1245         else
1246             throw new Exception("Another parser fail");
1247     }
1248 
1249     void handleStackCleanup(VarDeclarationStatementNode vdsnode)
1250     {
1251         if(vdsnode is null)
1252             return;
1253         uint numToPop = 0;
1254         foreach(node ; vdsnode.varAccessOrAssignmentNodes)
1255         {
1256             ++numToPop;
1257         }
1258         if(numToPop == 1)
1259             _chunk.bytecode ~= OpCode.POP;
1260         else
1261             _chunk.bytecode ~= OpCode.POPN ~ encode!uint(numToPop);
1262         _stackVarCounter -= numToPop;
1263         _counterStack.pop();
1264         _compDataStack.top.stackVariables.pop();
1265     }
1266 
1267     void handleStackDeclaration(VarDeclarationStatementNode vdsnode)
1268     {
1269         if(vdsnode is null)
1270             return;
1271         _compDataStack.top.stackVariables.push(VarTable.init);
1272         foreach(node ; vdsnode.varAccessOrAssignmentNodes)
1273         {
1274             if(auto bopnode = cast(BinaryOpNode)node)
1275             {
1276                 if(bopnode.opToken.type != Token.Type.ASSIGN)
1277                     throw new ScriptCompileException("Invalid declaration in for loop", bopnode.opToken);
1278                 auto van = cast(VarAccessNode)bopnode.leftNode;
1279                 auto id = addStackVar(van.varToken.text, vdsnode.qualifier.text == "const");
1280                 _chunk.bytecode ~= OpCode.STACK_1;
1281                 bopnode.rightNode.accept(this);
1282                 _chunk.bytecode ~= OpCode.SET ~ encode!int(cast(int)id);
1283                 _chunk.bytecode ~= OpCode.POP;
1284             }
1285             else if(auto van = cast(VarAccessNode)node)
1286             {
1287                 addStackVar(van.varToken.text, vdsnode.qualifier.text == "const");
1288                 _chunk.bytecode ~= OpCode.STACK_1;
1289             }
1290             else
1291                 throw new Exception("Not sure what happened here");
1292         }
1293         _counterStack.push(_stackVarCounter);
1294     }
1295 
1296     VarMetadata lookupVar(string name)
1297     {
1298         for(auto n = _compDataStack.size; n > 0; --n)
1299         {
1300             for(auto i = 0; i < _compDataStack.array[n-1].stackVariables.array.length; ++i)
1301             {
1302                 if(name in _compDataStack.array[n-1].stackVariables.array[$-i-1])
1303                     return _compDataStack.array[n-1].stackVariables.array[$-i-1][name];
1304             }
1305         }
1306         return VarMetadata(false, -1, 0, false);
1307     }
1308 
1309     bool nodeIsAssignable(ExpressionNode node)
1310     {
1311         if(cast(VarAccessNode)node)
1312             return true;
1313         if(cast(ArrayIndexNode)node)
1314             return true;
1315         if(cast(MemberAccessNode)node)
1316             return true;
1317         return false;
1318     }
1319 
1320     void patchBreaksAndContinues(string label, size_t breakGoto, size_t continueGoto, int depthCounter, int loopLevel)
1321     {
1322         for(size_t i = 0; i < _compDataStack.top.breaksToPatch.length; ++i)
1323         {
1324             BreakOrContinueToPatch* brk = &_compDataStack.top.breaksToPatch[i];
1325             if(!brk.patched)
1326             {
1327                 if((brk.labelName == label) || (brk.labelName == "" && brk.loopLevel == loopLevel))
1328                 {
1329                     *cast(uint*)(_chunk.bytecode.ptr + brk.gotoPatchParam) = cast(uint)breakGoto;
1330                     immutable depthSize = brk.depth - depthCounter;
1331                     if(depthSize > ubyte.max)
1332                         throw new ScriptCompileException("Break depth exceeds ubyte.max",
1333                             Token.createFakeToken(Token.Type.KEYWORD, "break"));
1334                     _chunk.bytecode[brk.gotoPatchParam + uint.sizeof] = cast(ubyte)depthSize;
1335                     brk.patched = true;
1336                 }
1337             }
1338         }
1339 
1340         for(size_t i = 0; i < _compDataStack.top.continuesToPatch.length; ++i)
1341         {
1342             BreakOrContinueToPatch* cont = &_compDataStack.top.continuesToPatch[i];
1343             if(!cont.patched)
1344             {
1345                 if((cont.labelName == label) || (cont.labelName == "" && cont.loopLevel == loopLevel))
1346                 {
1347                     *cast(uint*)(_chunk.bytecode.ptr + cont.gotoPatchParam) = cast(uint)continueGoto;
1348                     immutable depthSize = cont.depth - depthCounter;
1349                     if(depthSize > ubyte.max)
1350                         throw new ScriptCompileException("Continue depth exceeds ubyte.max",
1351                             Token.createFakeToken(Token.Type.KEYWORD, "continue"));
1352                     _chunk.bytecode[cont.gotoPatchParam + uint.sizeof] = cast(ubyte)depthSize;
1353                     cont.patched = true;
1354                 }
1355             }
1356         }
1357 
1358     }
1359 
1360     BinaryOpNode reduceAssignment(BinaryOpNode original)
1361     {
1362         switch(original.opToken.type)
1363         {
1364         case Token.Type.ASSIGN:
1365             return original; // nothing to do
1366         case Token.Type.POW_ASSIGN:
1367             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1368                     original.leftNode, 
1369                     new BinaryOpNode(Token.createFakeToken(Token.Type.POW,""),
1370                             original.leftNode, original.rightNode)
1371             );
1372         case Token.Type.STAR_ASSIGN:
1373             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1374                     original.leftNode, 
1375                     new BinaryOpNode(Token.createFakeToken(Token.Type.STAR,""),
1376                             original.leftNode, original.rightNode)
1377             );
1378         case Token.Type.FSLASH_ASSIGN:
1379             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1380                     original.leftNode, 
1381                     new BinaryOpNode(Token.createFakeToken(Token.Type.FSLASH,""),
1382                             original.leftNode, original.rightNode)
1383             );
1384         case Token.Type.PERCENT_ASSIGN:
1385             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1386                     original.leftNode, 
1387                     new BinaryOpNode(Token.createFakeToken(Token.Type.PERCENT,""),
1388                             original.leftNode, original.rightNode)
1389             );
1390         case Token.Type.PLUS_ASSIGN:
1391             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1392                     original.leftNode, 
1393                     new BinaryOpNode(Token.createFakeToken(Token.Type.PLUS,""),
1394                             original.leftNode, original.rightNode)
1395             );
1396         case Token.Type.DASH_ASSIGN:
1397             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1398                     original.leftNode, 
1399                     new BinaryOpNode(Token.createFakeToken(Token.Type.DASH,""),
1400                             original.leftNode, original.rightNode)
1401             );
1402         case Token.Type.BAND_ASSIGN:
1403             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1404                     original.leftNode, 
1405                     new BinaryOpNode(Token.createFakeToken(Token.Type.BIT_AND,""),
1406                             original.leftNode, original.rightNode)
1407             );
1408         case Token.Type.BXOR_ASSIGN:
1409             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1410                     original.leftNode, 
1411                     new BinaryOpNode(Token.createFakeToken(Token.Type.BIT_XOR,""),
1412                             original.leftNode, original.rightNode)
1413             );
1414         case Token.Type.BOR_ASSIGN:
1415             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1416                     original.leftNode, 
1417                     new BinaryOpNode(Token.createFakeToken(Token.Type.BIT_OR,""),
1418                             original.leftNode, original.rightNode)
1419             );
1420         case Token.Type.BLS_ASSIGN:
1421             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1422                     original.leftNode, 
1423                     new BinaryOpNode(Token.createFakeToken(Token.Type.BIT_LSHIFT,""),
1424                             original.leftNode, original.rightNode)
1425             );
1426         case Token.Type.BRS_ASSIGN:
1427             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1428                     original.leftNode, 
1429                     new BinaryOpNode(Token.createFakeToken(Token.Type.BIT_RSHIFT,""),
1430                             original.leftNode, original.rightNode)
1431             );
1432         case Token.Type.BURS_ASSIGN:
1433             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1434                     original.leftNode, 
1435                     new BinaryOpNode(Token.createFakeToken(Token.Type.BIT_URSHIFT,""),
1436                             original.leftNode, original.rightNode)
1437             );
1438         default:
1439             throw new Exception("Misuse of reduce assignment");
1440         }
1441     }
1442 
1443     void removePatches()
1444     {
1445         if(_compDataStack.top.loopOrSwitchStack == 0)
1446         {
1447             bool unresolved = false;
1448             if(_compDataStack.top.loopOrSwitchStack == 0)
1449             {
1450                 foreach(brk ; _compDataStack.top.breaksToPatch)
1451                 {
1452                     if(!brk.patched)
1453                     {
1454                         unresolved = true;
1455                         break;
1456                     }
1457                 }
1458 
1459                 foreach(cont ; _compDataStack.top.continuesToPatch)
1460                 {
1461                     if(!cont.patched)
1462                     {
1463                         unresolved = true;
1464                         break;
1465                     }
1466                 }
1467             }
1468             if(unresolved)
1469                 throw new ScriptCompileException("Unresolvable break or continue statement", 
1470                         Token.createInvalidToken(Position(0,0), "break/continue"));
1471             _compDataStack.top.breaksToPatch = [];
1472             _compDataStack.top.continuesToPatch = [];
1473         }
1474     }
1475 
1476     void throwUnimplemented(ExpressionNode expr)
1477     {
1478         throw new UnimplementedException("Unimplemented: " ~ expr.toString());
1479     }
1480 
1481     void throwUnimplemented(StatementNode stmt)
1482     {
1483         throw new UnimplementedException("Unimplemented: " ~ stmt.toString());
1484     }
1485 
1486     bool varExists(string name)
1487     {
1488         for(auto n = _compDataStack.size; n > 0; --n)
1489         {
1490             for(auto i = 1; i <= _compDataStack.array[n-1].stackVariables.array.length; ++i)
1491             {
1492                 if(name in _compDataStack.array[n-1].stackVariables.array[$-i])
1493                     return true;
1494             }
1495         }
1496         return false;
1497     }
1498 
1499     struct CompilationData
1500     {
1501         /// environment depth counter
1502         int depthCounter;
1503         /// how many loops nested
1504         int loopOrSwitchStack = 0;
1505         /// list of breaks needing patched
1506         BreakOrContinueToPatch[] breaksToPatch;
1507         /// list of continues needing patched
1508         BreakOrContinueToPatch[] continuesToPatch;
1509 
1510         /// holds stack variables
1511         Stack!VarTable stackVariables;
1512         
1513         /// for-of depth (this allocated 2 stack slots)
1514         int forOfDepth;
1515     }
1516 
1517     struct BreakOrContinueToPatch
1518     {
1519         this(string lbl, size_t param, int d, int ll)
1520         {
1521             labelName = lbl;
1522             gotoPatchParam = param;
1523             depth = d;
1524             loopLevel = ll;
1525         }
1526         string labelName;
1527         size_t gotoPatchParam;
1528         int depth;
1529         int loopLevel;
1530         bool patched = false;
1531     }
1532 
1533     struct VarMetadata
1534     {
1535         bool isDefined;
1536         int stackLocation; // can be -1 for regular lookup
1537         int funcDepth; // how deep in function calls
1538         bool isConst;
1539         VarDeclarationStatementNode varDecls;
1540     }
1541 
1542     alias VarTable = VarMetadata[string];
1543 
1544     /// when parsing a class expression or statement, if there is a base class it is added and poppped
1545     /// so that super expressions can be processed
1546     ExpressionNode[] _baseClassStack;
1547 
1548     /// the chunk being compiled
1549     Chunk _chunk;
1550 
1551     /// current source to send to each debugInfo
1552     string _currentSource;
1553 
1554     /// debug info stack
1555     Stack!DebugInfo _debugInfoStack;
1556 
1557     Stack!CompilationData _compDataStack;
1558     /**
1559      * The stack is guaranteed to be empty between statements so absolute stack positions for variables
1560      * can be used. The var name and stack ID is stored in the environment. The stack must be manually cleaned up
1561      */
1562     size_t _stackVarCounter = 0;
1563     /// keep track of function depth
1564     size_t _funcDepth;
1565     /// In case of a return statement in a for loop
1566     Stack!size_t _counterStack;
1567 }
1568 
1569 unittest
1570 {
1571     import mildew.environment: Environment;
1572     auto compiler = new Compiler();
1573     // auto chunk = compiler.compile("5 == 5 ? 'ass' : 'titties';");
1574     auto vm = new VirtualMachine(new Environment(null, "<global>"));
1575     // vm.printChunk(chunk);
1576     // vm.run(chunk);
1577 }