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);
147         else
148             func = new ScriptFunction(
149                 flnode.optionalName == "" ? "<anonymous class>" : flnode.optionalName,
150                 flnode.argList, _chunk.bytecode, true);
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 
585             // is it a validated binop node
586             if(auto bopnode = cast(BinaryOpNode)expr)
587             {
588                 // if the right hand side is a function literal, we can rename it
589                 if(auto flnode = cast(FunctionLiteralNode)bopnode.rightNode)
590                     flnode.optionalName = bopnode.leftNode.toString();
591                 else if(auto clsnode = cast(ClassLiteralNode)bopnode.rightNode)
592                 {
593                     clsnode.classDefinition.constructor.optionalName = bopnode.leftNode.toString();
594                     clsnode.classDefinition.className = bopnode.leftNode.toString();
595                 }
596                 auto van = cast(VarAccessNode)bopnode.leftNode;
597                 bopnode.rightNode.accept(this); // push value to stack
598                 varName = van.varToken.text;
599             }
600             else if(auto van = cast(VarAccessNode)expr)
601             {
602                 _chunk.bytecode ~= OpCode.STACK_1; // push undefined
603                 varName = van.varToken.text;
604             }
605             else
606                 throw new Exception("Parser failure or unimplemented feature: " ~ vdsnode.toString());
607 
608             // make sure it's not overwriting a stack value
609             if(vdsnode.qualifier.text != "var")
610             {
611                 immutable lookup = cast(immutable)lookupVar(varName);
612                 if(lookup.isDefined && lookup.stackLocation != -1)
613                     throw new ScriptCompileException("Attempt to redeclare stack variable " ~ varName, 
614                             vdsnode.qualifier);
615                 defineVar(varName, VarMetadata(true, -1, cast(int)_funcDepth, vdsnode.qualifier.text == "const"));
616             }
617             
618             if(vdsnode.qualifier.text == "var")
619                 _chunk.bytecode ~= OpCode.DECLVAR ~ encodeConst(varName);
620             else if(vdsnode.qualifier.text == "let")
621                 _chunk.bytecode ~= OpCode.DECLLET ~ encodeConst(varName);
622             else if(vdsnode.qualifier.text == "const")
623                 _chunk.bytecode ~= OpCode.DECLCONST ~ encodeConst(varName);
624             else
625                 throw new Exception("Catastrophic parser fail: " ~ vdsnode.toString());
626         }
627         return Variant(null);
628     }
629 
630     /// handle {} braces
631 	Variant visitBlockStatementNode(BlockStatementNode bsnode)
632     {
633         import std.conv: to;
634         _debugInfoStack.top.addLine(_chunk.bytecode.length, bsnode.line);
635         // if there are no declarations at the top level the scope op can be omitted
636         bool omitScope = true;
637         foreach(stmt ; bsnode.statementNodes)
638         {
639             if(cast(VarDeclarationStatementNode)stmt
640             || cast(FunctionDeclarationStatementNode)stmt 
641             || cast(ClassDeclarationStatementNode)stmt)
642             {
643                 omitScope = false;
644                 break;
645             }
646         }
647         if(!omitScope)
648         {
649             ++_compDataStack.top.depthCounter;
650             _compDataStack.top.stackVariables.push(VarTable.init);
651 
652             _chunk.bytecode ~= OpCode.OPENSCOPE;
653         }
654         foreach(stmt ; bsnode.statementNodes)
655             stmt.accept(this);
656         
657         if(!omitScope)
658         {
659             _chunk.bytecode ~= OpCode.CLOSESCOPE;
660 
661             _compDataStack.top.stackVariables.pop();
662             --_compDataStack.top.depthCounter;
663         }
664         return Variant(null);
665     }
666 
667     /// emit if statements
668 	Variant visitIfStatementNode(IfStatementNode isnode)
669     {
670         _debugInfoStack.top.addLine(_chunk.bytecode.length, isnode.line);
671         isnode.onTrueStatement = new BlockStatementNode(isnode.onTrueStatement.line, [isnode.onTrueStatement]);
672         if(isnode.onFalseStatement)
673             isnode.onFalseStatement = new BlockStatementNode(isnode.onFalseStatement.line, [isnode.onFalseStatement]);
674         if(isnode.onFalseStatement)
675         {
676             if(cast(VarDeclarationStatementNode)isnode.onFalseStatement)
677                 isnode.onFalseStatement = new BlockStatementNode(isnode.onFalseStatement.line, 
678                         [isnode.onFalseStatement]);
679         }
680         isnode.conditionNode.accept(this);
681         auto length = cast(int)_chunk.bytecode.length;
682         auto jmpFalseToPatch = genJmpFalse();
683         isnode.onTrueStatement.accept(this);
684         auto length2 = cast(int)_chunk.bytecode.length;
685         auto jmpOverToPatch = genJmp();
686         *cast(int*)(_chunk.bytecode.ptr + jmpFalseToPatch) = cast(int)_chunk.bytecode.length - length;
687         length = cast(int)_chunk.bytecode.length;
688         if(isnode.onFalseStatement !is null)
689         {
690             isnode.onFalseStatement.accept(this);
691         }
692         *cast(int*)(_chunk.bytecode.ptr + jmpOverToPatch) = cast(int)_chunk.bytecode.length - length2;
693 
694         return Variant(null);
695     }
696 
697     /// Switch statements
698 	Variant visitSwitchStatementNode(SwitchStatementNode ssnode)
699     {
700         _debugInfoStack.top.addLine(_chunk.bytecode.length, ssnode.line);
701 
702         size_t[ScriptAny] unpatchedJumpTbl;
703         size_t statementCounter = 0;        
704         
705         ++_compDataStack.top.loopOrSwitchStack;
706         // generate unpatched jump array
707         foreach(key, value ; ssnode.switchBody.jumpTable)
708         {
709             unpatchedJumpTbl[key] = genJmpTableEntry(key);
710         }
711         _chunk.bytecode ~= OpCode.ARRAY ~ encode!uint(cast(uint)ssnode.switchBody.jumpTable.length);
712         // generate expression to test
713         ssnode.expressionNode.accept(this);
714         // generate switch statement
715         immutable unpatchedSwitchParam = genSwitchStatement();
716         bool patched = false;
717         // generate each statement, patching along the way
718         ++_compDataStack.top.depthCounter;
719         _compDataStack.top.stackVariables.push(VarTable.init);
720         _chunk.bytecode ~= OpCode.OPENSCOPE;
721         foreach(stmt ; ssnode.switchBody.statementNodes)
722         {
723             uint patchData = cast(uint)_chunk.bytecode.length;
724             foreach(k, v ; ssnode.switchBody.jumpTable)
725             {
726                 if(v == statementCounter)
727                 {
728                     immutable ptr = unpatchedJumpTbl[k];
729                     _chunk.bytecode[ptr .. ptr + 4] = encodeConst(patchData)[0..4];
730                 }
731             }
732             // could also be default in which case we patch the switch
733             if(statementCounter == ssnode.switchBody.defaultStatementID)
734             {
735                 *cast(uint*)(_chunk.bytecode.ptr + unpatchedSwitchParam) = patchData;
736                 patched = true;
737             }
738             stmt.accept(this);
739             ++statementCounter;
740         }
741         _chunk.bytecode ~= OpCode.CLOSESCOPE;
742         _compDataStack.top.stackVariables.pop();
743         --_compDataStack.top.depthCounter;
744         immutable breakLocation = _chunk.bytecode.length;
745         if(!patched)
746         {
747             *cast(uint*)(_chunk.bytecode.ptr + unpatchedSwitchParam) = cast(uint)breakLocation;
748         }
749         --_compDataStack.top.loopOrSwitchStack;
750 
751         patchBreaksAndContinues("", breakLocation, breakLocation, _compDataStack.top.depthCounter, 
752                 _compDataStack.top.loopOrSwitchStack);
753         removePatches();
754 
755         return Variant(null);
756     }
757 
758     /// Handle while loops
759 	Variant visitWhileStatementNode(WhileStatementNode wsnode)
760     {
761         _debugInfoStack.top.addLine(_chunk.bytecode.length, wsnode.line);
762         ++_compDataStack.top.loopOrSwitchStack;
763         immutable length0 = _chunk.bytecode.length;
764         immutable continueLocation = length0;
765         wsnode.conditionNode.accept(this);
766         immutable length1 = _chunk.bytecode.length;
767         immutable jmpFalse = genJmpFalse();
768         wsnode.bodyNode.accept(this);
769         immutable length2 = _chunk.bytecode.length;
770         immutable jmp = genJmp();
771         immutable breakLocation = _chunk.bytecode.length;
772         *cast(int*)(_chunk.bytecode.ptr + jmp) = -cast(int)(length2 - length0);
773         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = cast(int)(_chunk.bytecode.length - length1);
774         // patch gotos
775         patchBreaksAndContinues(wsnode.label, breakLocation, continueLocation,
776                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
777         --_compDataStack.top.loopOrSwitchStack;
778         removePatches();
779         return Variant(null);
780     }
781 
782     /// do-while loops
783 	Variant visitDoWhileStatementNode(DoWhileStatementNode dwsnode)
784     {
785         _debugInfoStack.top.addLine(_chunk.bytecode.length, dwsnode.line);
786         ++_compDataStack.top.loopOrSwitchStack;
787         immutable doWhile = _chunk.bytecode.length;
788         dwsnode.bodyNode.accept(this);
789         immutable continueLocation = _chunk.bytecode.length;
790         dwsnode.conditionNode.accept(this);
791         _chunk.bytecode ~= OpCode.NOT;
792         immutable whileCondition = _chunk.bytecode.length;
793         immutable jmpFalse = genJmpFalse();
794         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = -cast(int)(whileCondition - doWhile);
795         immutable breakLocation = _chunk.bytecode.length;
796         patchBreaksAndContinues(dwsnode.label, breakLocation, continueLocation, _compDataStack.top.depthCounter,
797                 _compDataStack.top.loopOrSwitchStack);
798         --_compDataStack.top.loopOrSwitchStack;
799         removePatches();
800         return Variant(null);
801     }
802 
803     /// handle regular for loops
804 	Variant visitForStatementNode(ForStatementNode fsnode)
805     {
806         _debugInfoStack.top.addLine(_chunk.bytecode.length, fsnode.line);
807         ++_compDataStack.top.loopOrSwitchStack;
808         // set up stack variables
809         // handleStackDeclaration(fsnode.varDeclarationStatement);
810         ++_compDataStack.top.depthCounter;
811         _chunk.bytecode ~= OpCode.OPENSCOPE;
812         if(fsnode.varDeclarationStatement)
813             fsnode.varDeclarationStatement.accept(this);
814         immutable length0 = _chunk.bytecode.length;
815         fsnode.conditionNode.accept(this);
816         immutable length1 = _chunk.bytecode.length;
817         immutable jmpFalse = genJmpFalse();
818         fsnode.bodyNode.accept(this);
819         immutable continueLocation = _chunk.bytecode.length;
820         // increment is a single expression not a statement so we must add a pop
821         fsnode.incrementNode.accept(this);
822         _chunk.bytecode ~= OpCode.POP;
823         immutable length2 = _chunk.bytecode.length;
824         immutable jmp = genJmp();
825         immutable breakLocation = _chunk.bytecode.length;
826         // handleStackCleanup(fsnode.varDeclarationStatement);
827         _chunk.bytecode ~= OpCode.CLOSESCOPE;
828         // patch jmps
829         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = cast(int)(breakLocation - length1);
830         *cast(int*)(_chunk.bytecode.ptr + jmp) = -cast(int)(length2 - length0);
831         patchBreaksAndContinues(fsnode.label, breakLocation, continueLocation, _compDataStack.top.depthCounter,
832                 _compDataStack.top.loopOrSwitchStack);
833         --_compDataStack.top.loopOrSwitchStack;
834         --_compDataStack.top.depthCounter;
835         removePatches();
836         return Variant(null);
837     }
838 
839     /// TODO
840 	Variant visitForOfStatementNode(ForOfStatementNode fosnode)
841     {
842         _debugInfoStack.top.addLine(_chunk.bytecode.length, fosnode.line);
843         string[] varNames;
844         foreach(van ; fosnode.varAccessNodes)
845             varNames ~= van.varToken.text;
846         fosnode.objectToIterateNode.accept(this);
847         _chunk.bytecode ~= OpCode.ITER;
848         ++_stackVarCounter;
849         _chunk.bytecode ~= OpCode.STACK_1;
850         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-2);
851         _chunk.bytecode ~= OpCode.CALL ~ encode!uint(0);
852         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
853         ++_stackVarCounter;
854         ++_compDataStack.top.forOfDepth;
855         _chunk.bytecode ~= OpCode.CONST ~ encodeConst("done");
856         _chunk.bytecode ~= OpCode.OBJGET;
857         _chunk.bytecode ~= OpCode.NOT;
858         immutable loop = _chunk.bytecode.length;
859         immutable jmpFalse = genJmpFalse();
860         _chunk.bytecode ~= OpCode.OPENSCOPE;
861         if(varNames.length == 1)
862         {
863             _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
864             _chunk.bytecode ~= OpCode.CONST ~ encodeConst("value");
865             _chunk.bytecode ~= OpCode.OBJGET;
866             _chunk.bytecode ~= (fosnode.qualifierToken.text == "let" ? OpCode.DECLLET : OpCode.DECLCONST)
867                 ~ encodeConst(varNames[0]);
868         }
869         else if(varNames.length == 2)
870         {
871             _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
872             _chunk.bytecode ~= OpCode.CONST ~ encodeConst("key");
873             _chunk.bytecode ~= OpCode.OBJGET;
874             _chunk.bytecode ~= (fosnode.qualifierToken.text == "let" ? OpCode.DECLLET : OpCode.DECLCONST)
875                 ~ encodeConst(varNames[0]);
876             _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
877             _chunk.bytecode ~= OpCode.CONST ~ encodeConst("value");
878             _chunk.bytecode ~= OpCode.OBJGET;
879             _chunk.bytecode ~= (fosnode.qualifierToken.text == "let" ? OpCode.DECLLET : OpCode.DECLCONST)
880                 ~ encodeConst(varNames[1]);
881         }
882         ++_compDataStack.top.loopOrSwitchStack;
883         fosnode.bodyNode.accept(this);
884         immutable continueLocation = _chunk.bytecode.length;
885         _chunk.bytecode ~= OpCode.POP;
886         _chunk.bytecode ~= OpCode.STACK_1;
887         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-2);
888         _chunk.bytecode ~= OpCode.CALL ~ encode!uint(0);
889         _chunk.bytecode ~= OpCode.PUSH ~ encode!int(-1);
890         _chunk.bytecode ~= OpCode.CONST ~ encodeConst("done");
891         _chunk.bytecode ~= OpCode.OBJGET;
892         _chunk.bytecode ~= OpCode.NOT;
893         _chunk.bytecode ~= OpCode.CLOSESCOPE;
894         immutable loopAgain = _chunk.bytecode.length;
895         immutable jmp = genJmp();
896         *cast(int*)(_chunk.bytecode.ptr + jmp) = -cast(int)(loopAgain - loop);
897         immutable breakLocation = _chunk.bytecode.length;
898         _chunk.bytecode ~= OpCode.CLOSESCOPE;
899         immutable endLoop = _chunk.bytecode.length;
900         _chunk.bytecode ~= OpCode.POPN ~ encode!uint(2);
901         --_compDataStack.top.forOfDepth;
902         _stackVarCounter -= 2;
903         *cast(int*)(_chunk.bytecode.ptr + jmpFalse) = cast(int)(endLoop - loop);
904         patchBreaksAndContinues(fosnode.label, breakLocation, continueLocation, 
905                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
906         --_compDataStack.top.loopOrSwitchStack;
907         removePatches();
908         return Variant(null);
909     }
910 
911     /// TODO
912 	Variant visitBreakStatementNode(BreakStatementNode bsnode)
913     {
914         _debugInfoStack.top.addLine(_chunk.bytecode.length, bsnode.line);
915         immutable patchLocation = _chunk.bytecode.length + 1;
916         _chunk.bytecode ~= OpCode.GOTO ~ encode(uint.max) ~ cast(ubyte)0;
917         _compDataStack.top.breaksToPatch ~= BreakOrContinueToPatch(bsnode.label, patchLocation,
918                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
919         return Variant(null);
920     }
921 
922     /// TODO
923 	Variant visitContinueStatementNode(ContinueStatementNode csnode)
924     {
925         _debugInfoStack.top.addLine(_chunk.bytecode.length, csnode.line);
926         immutable patchLocation = _chunk.bytecode.length + 1;
927         _chunk.bytecode ~= OpCode.GOTO ~ encode(uint.max - 1) ~ cast(ubyte)0;
928         _compDataStack.top.continuesToPatch ~= BreakOrContinueToPatch(csnode.label, patchLocation,
929                 _compDataStack.top.depthCounter, _compDataStack.top.loopOrSwitchStack);
930         return Variant(null);
931     }
932 
933     /// Return statements
934 	Variant visitReturnStatementNode(ReturnStatementNode rsnode)
935     {
936         _debugInfoStack.top.addLine(_chunk.bytecode.length, rsnode.line);
937         immutable numPops = _compDataStack.top.forOfDepth * 2;
938         if(numPops == 1)
939             _chunk.bytecode ~= OpCode.POP;
940         else if(numPops > 1)
941             _chunk.bytecode ~= OpCode.POPN ~ encode!uint(numPops);
942         if(rsnode.expressionNode !is null)
943             rsnode.expressionNode.accept(this);
944         else
945             _chunk.bytecode ~= OpCode.STACK_1;
946         _chunk.bytecode ~= OpCode.RETURN;
947         return Variant(null);
948     }
949 
950     /// function declarations
951 	Variant visitFunctionDeclarationStatementNode(FunctionDeclarationStatementNode fdsnode)
952     {
953         _debugInfoStack.top.addLine(_chunk.bytecode.length, fdsnode.line);
954         // easy, reduce it to a let fname = function(){...} VarDeclarationStatement
955         auto vdsn = new VarDeclarationStatementNode(
956             fdsnode.line,
957             Token.createFakeToken(Token.Type.KEYWORD, "let"), [
958                 new BinaryOpNode(
959                     Token.createFakeToken(Token.Type.ASSIGN, ""),
960                     new VarAccessNode(Token.createFakeToken(Token.Type.IDENTIFIER, fdsnode.name)),
961                     new FunctionLiteralNode(
962                         fdsnode.argNames, fdsnode.statementNodes, fdsnode.name, false, fdsnode.isGenerator
963                     )
964                 )
965             ]
966         );
967         vdsn.accept(this);
968         return Variant(null);
969     }
970 
971     /// Throw statement
972 	Variant visitThrowStatementNode(ThrowStatementNode tsnode)
973     {
974         _debugInfoStack.top.addLine(_chunk.bytecode.length, tsnode.line);
975         tsnode.expressionNode.accept(this);
976         _chunk.bytecode ~= OpCode.THROW;
977         return Variant(null);
978     }
979 
980     /// Try catch
981 	Variant visitTryCatchBlockStatementNode(TryCatchBlockStatementNode tcbsnode)
982     {
983         _debugInfoStack.top.addLine(_chunk.bytecode.length, tcbsnode.line);
984         // emit try block
985         immutable tryToPatch = genTry();
986         tcbsnode.tryBlockNode.accept(this);
987         _chunk.bytecode ~= OpCode.ENDTRY;
988         immutable length0 = cast(int)_chunk.bytecode.length;
989         immutable jmpToPatch = genJmp();
990         *cast(uint*)(_chunk.bytecode.ptr + tryToPatch) = cast(uint)_chunk.bytecode.length;
991         // emit catch block
992         immutable omitScope = tcbsnode.exceptionName == ""? true: false;
993         if(!omitScope)
994         {
995             ++_compDataStack.top.depthCounter;
996             _compDataStack.top.stackVariables.push(VarTable.init);
997             _chunk.bytecode ~= OpCode.OPENSCOPE;
998         }
999         if(tcbsnode.catchBlockNode)
1000         {
1001             _chunk.bytecode ~= OpCode.LOADEXC;
1002             if(!omitScope)
1003                 _chunk.bytecode ~= OpCode.DECLLET ~ encodeConst(tcbsnode.exceptionName);
1004             else
1005                 _chunk.bytecode ~= OpCode.POP;
1006             tcbsnode.catchBlockNode.accept(this);
1007         }
1008         if(!omitScope)
1009         {
1010             --_compDataStack.top.depthCounter;
1011             _compDataStack.top.stackVariables.pop();
1012             _chunk.bytecode ~= OpCode.CLOSESCOPE;
1013         }
1014         *cast(int*)(_chunk.bytecode.ptr + jmpToPatch) = cast(int)_chunk.bytecode.length - length0;
1015         // emit finally block
1016         if(tcbsnode.finallyBlockNode)
1017         {
1018             tcbsnode.finallyBlockNode.accept(this);
1019             if(tcbsnode.catchBlockNode is null)
1020                 _chunk.bytecode ~= OpCode.RETHROW;
1021         }
1022         return Variant(null);
1023     }
1024 
1025     /// delete statement. can be used on ArrayIndexNode or MemberAccessNode
1026 	Variant visitDeleteStatementNode(DeleteStatementNode dsnode)
1027     {
1028         _debugInfoStack.top.addLine(_chunk.bytecode.length, dsnode.line);
1029         if(auto ain = cast(ArrayIndexNode)dsnode.memberAccessOrArrayIndexNode)
1030         {
1031             ain.objectNode.accept(this);
1032             ain.indexValueNode.accept(this);
1033         }
1034         else if(auto man = cast(MemberAccessNode)dsnode.memberAccessOrArrayIndexNode)
1035         {
1036             man.objectNode.accept(this);
1037             auto van = cast(VarAccessNode)man.memberNode;
1038             if(van is null)
1039                 throw new Exception("Parser failure in delete statement");
1040             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(van.varToken.text);
1041         }
1042         else
1043             throw new ScriptCompileException("Invalid operand to delete", dsnode.deleteToken);
1044         _chunk.bytecode ~= OpCode.DEL;
1045         return Variant(null);
1046     }
1047 
1048     /// Class declarations. Reduce to let leftHand = classExpression
1049 	Variant visitClassDeclarationStatementNode(ClassDeclarationStatementNode cdsnode)
1050     {
1051         _debugInfoStack.top.addLine(_chunk.bytecode.length, cdsnode.line);
1052         auto reduction = new VarDeclarationStatementNode(
1053             Token.createFakeToken(Token.Type.KEYWORD, "let"),
1054             [
1055                 new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, "="),
1056                     new VarAccessNode(Token.createFakeToken(Token.Type.IDENTIFIER, cdsnode.classDefinition.className)),
1057                     new ClassLiteralNode(cdsnode.classToken, cdsnode.classDefinition))
1058             ]);
1059         reduction.accept(this);
1060         return Variant(null);
1061     }
1062 
1063     /// handle expression statements
1064 	Variant visitExpressionStatementNode(ExpressionStatementNode esnode)
1065     {
1066         _debugInfoStack.top.addLine(_chunk.bytecode.length, esnode.line);
1067         if(esnode.expressionNode is null)
1068             return Variant(null);
1069         esnode.expressionNode.accept(this);
1070         _chunk.bytecode ~= OpCode.POP;
1071         return Variant(null);
1072     }
1073 
1074 private:
1075     static const int UNPATCHED_JMP = 262_561_909;
1076     static const uint UNPATCHED_JMPENTRY = 3_735_890_861;
1077     static const uint UNPATCHED_TRY_GOTO = uint.max;
1078 
1079     size_t addStackVar(string name, bool isConst)
1080     {
1081         size_t id = _stackVarCounter++;
1082         defineVar(name, VarMetadata(true, cast(int)id, cast(int)_funcDepth, isConst));
1083         return id;
1084     }
1085 
1086     void defineVar(string name, VarMetadata vmeta)
1087     {
1088         _compDataStack.top.stackVariables.top[name] = vmeta;
1089     }
1090 
1091     ubyte[] encodeConst(T)(T value)
1092     {
1093         return encode(_chunk.constTable.addValueUint(ScriptAny(value)));
1094     }
1095 
1096     ubyte[] encodeConst(T : ScriptAny)(T value)
1097     {
1098         return encode(_chunk.constTable.addValueUint(value));
1099     }
1100 
1101     /// The return value MUST BE USED
1102     size_t genSwitchStatement()
1103     {
1104         immutable switchParam = _chunk.bytecode.length + 1;
1105         _chunk.bytecode ~= OpCode.SWITCH ~ encode!uint(UNPATCHED_JMPENTRY);
1106         return switchParam;
1107     }
1108 
1109     /// The return value MUST BE USED
1110     size_t genJmp()
1111     {
1112         _chunk.bytecode ~= OpCode.JMP ~ encode!int(UNPATCHED_JMP);
1113         return _chunk.bytecode.length - int.sizeof;
1114     }
1115 
1116     /// The return value MUST BE USED
1117     size_t genJmpFalse()
1118     {
1119         _chunk.bytecode ~= OpCode.JMPFALSE ~ encode!int(UNPATCHED_JMP);
1120         return _chunk.bytecode.length - int.sizeof;
1121     }
1122 
1123     /// The return value MUST BE USED
1124     size_t genJmpTableEntry(ScriptAny value)
1125     {
1126         _chunk.bytecode ~= OpCode.CONST ~ encodeConst(value);
1127         immutable constEntry = _chunk.bytecode.length + 1;
1128         _chunk.bytecode ~= OpCode.CONST ~ encode!uint(UNPATCHED_JMPENTRY);
1129         _chunk.bytecode ~= OpCode.ARRAY ~ encode!uint(2);
1130         return constEntry;
1131     }
1132 
1133     /// The return value MUST BE USED
1134     size_t genTry()
1135     {
1136         _chunk.bytecode ~= OpCode.TRY ~ encode!uint(uint.max);
1137         return _chunk.bytecode.length - uint.sizeof;
1138     }
1139 
1140     void handleAssignment(ExpressionNode leftExpr, Token opToken, ExpressionNode rightExpr)
1141     {
1142         // in case we are assigning to object access expressions
1143         if(auto classExpr = cast(ClassLiteralNode)rightExpr)
1144         {
1145             if(classExpr.classDefinition.className == ""
1146             || classExpr.classDefinition.className == "<anonymous class>")
1147                 classExpr.classDefinition.constructor.optionalName = leftExpr.toString();
1148         }
1149         else if(auto funcLit = cast(FunctionLiteralNode)rightExpr)
1150         {
1151             if(funcLit.optionalName == "" || funcLit.optionalName == "<anonymous function>")
1152                 funcLit.optionalName = leftExpr.toString();
1153         }
1154         if(auto van = cast(VarAccessNode)leftExpr)
1155         {
1156             rightExpr.accept(this);
1157             if(varExists(van.varToken.text))
1158             {
1159                 bool isConst; // @suppress(dscanner.suspicious.unmodified)
1160                 immutable varMeta = cast(immutable)lookupVar(van.varToken.text);
1161                 if(varMeta.stackLocation != -1)
1162                 {
1163                     if(varMeta.isConst)
1164                         throw new ScriptCompileException("Cannot reassign stack const " ~ van.varToken.text, 
1165                                 van.varToken);
1166                     _chunk.bytecode ~= OpCode.SET ~ encode!uint(cast(uint)varMeta.stackLocation);
1167                     return;
1168                 }
1169             }
1170             _chunk.bytecode ~= OpCode.SETVAR ~ encodeConst(van.varToken.text);
1171         }
1172         else if(auto man = cast(MemberAccessNode)leftExpr)
1173         {
1174             man.objectNode.accept(this);
1175             auto van = cast(VarAccessNode)man.memberNode;
1176             _chunk.bytecode ~= OpCode.CONST ~ encodeConst(van.varToken.text);
1177             rightExpr.accept(this);
1178             _chunk.bytecode ~= OpCode.OBJSET;
1179         }
1180         else if(auto ain = cast(ArrayIndexNode)leftExpr)
1181         {
1182             ain.objectNode.accept(this);
1183             ain.indexValueNode.accept(this);
1184             rightExpr.accept(this);
1185             _chunk.bytecode ~= OpCode.OBJSET;
1186         }
1187         else
1188             throw new Exception("Another parser fail");
1189     }
1190 
1191     void handleStackCleanup(VarDeclarationStatementNode vdsnode)
1192     {
1193         if(vdsnode is null)
1194             return;
1195         uint numToPop = 0;
1196         foreach(node ; vdsnode.varAccessOrAssignmentNodes)
1197         {
1198             ++numToPop;
1199         }
1200         if(numToPop == 1)
1201             _chunk.bytecode ~= OpCode.POP;
1202         else
1203             _chunk.bytecode ~= OpCode.POPN ~ encode!uint(numToPop);
1204         _stackVarCounter -= numToPop;
1205         _counterStack.pop();
1206         _compDataStack.top.stackVariables.pop();
1207     }
1208 
1209     void handleStackDeclaration(VarDeclarationStatementNode vdsnode)
1210     {
1211         if(vdsnode is null)
1212             return;
1213         _compDataStack.top.stackVariables.push(VarTable.init);
1214         foreach(node ; vdsnode.varAccessOrAssignmentNodes)
1215         {
1216             if(auto bopnode = cast(BinaryOpNode)node)
1217             {
1218                 if(bopnode.opToken.type != Token.Type.ASSIGN)
1219                     throw new ScriptCompileException("Invalid declaration in for loop", bopnode.opToken);
1220                 auto van = cast(VarAccessNode)bopnode.leftNode;
1221                 auto id = addStackVar(van.varToken.text, vdsnode.qualifier.text == "const");
1222                 _chunk.bytecode ~= OpCode.STACK_1;
1223                 bopnode.rightNode.accept(this);
1224                 _chunk.bytecode ~= OpCode.SET ~ encode!int(cast(int)id);
1225                 _chunk.bytecode ~= OpCode.POP;
1226             }
1227             else if(auto van = cast(VarAccessNode)node)
1228             {
1229                 addStackVar(van.varToken.text, vdsnode.qualifier.text == "const");
1230                 _chunk.bytecode ~= OpCode.STACK_1;
1231             }
1232             else
1233                 throw new Exception("Not sure what happened here");
1234         }
1235         _counterStack.push(_stackVarCounter);
1236     }
1237 
1238     VarMetadata lookupVar(string name)
1239     {
1240         for(auto n = _compDataStack.size; n > 0; --n)
1241         {
1242             for(auto i = 0; i < _compDataStack.array[n-1].stackVariables.array.length; ++i)
1243             {
1244                 if(name in _compDataStack.array[n-1].stackVariables.array[$-i-1])
1245                     return _compDataStack.array[n-1].stackVariables.array[$-i-1][name];
1246             }
1247         }
1248         return VarMetadata(false, -1, 0, false);
1249     }
1250 
1251     bool nodeIsAssignable(ExpressionNode node)
1252     {
1253         if(cast(VarAccessNode)node)
1254             return true;
1255         if(cast(ArrayIndexNode)node)
1256             return true;
1257         if(cast(MemberAccessNode)node)
1258             return true;
1259         return false;
1260     }
1261 
1262     void patchBreaksAndContinues(string label, size_t breakGoto, size_t continueGoto, int depthCounter, int loopLevel)
1263     {
1264         for(size_t i = 0; i < _compDataStack.top.breaksToPatch.length; ++i)
1265         {
1266             BreakOrContinueToPatch* brk = &_compDataStack.top.breaksToPatch[i];
1267             if(!brk.patched)
1268             {
1269                 if((brk.labelName == label) || (brk.labelName == "" && brk.loopLevel == loopLevel))
1270                 {
1271                     *cast(uint*)(_chunk.bytecode.ptr + brk.gotoPatchParam) = cast(uint)breakGoto;
1272                     immutable depthSize = brk.depth - depthCounter;
1273                     if(depthSize > ubyte.max)
1274                         throw new ScriptCompileException("Break depth exceeds ubyte.max",
1275                             Token.createFakeToken(Token.Type.KEYWORD, "break"));
1276                     _chunk.bytecode[brk.gotoPatchParam + uint.sizeof] = cast(ubyte)depthSize;
1277                     brk.patched = true;
1278                 }
1279             }
1280         }
1281 
1282         for(size_t i = 0; i < _compDataStack.top.continuesToPatch.length; ++i)
1283         {
1284             BreakOrContinueToPatch* cont = &_compDataStack.top.continuesToPatch[i];
1285             if(!cont.patched)
1286             {
1287                 if((cont.labelName == label) || (cont.labelName == "" && cont.loopLevel == loopLevel))
1288                 {
1289                     *cast(uint*)(_chunk.bytecode.ptr + cont.gotoPatchParam) = cast(uint)continueGoto;
1290                     immutable depthSize = cont.depth - depthCounter;
1291                     if(depthSize > ubyte.max)
1292                         throw new ScriptCompileException("Continue depth exceeds ubyte.max",
1293                             Token.createFakeToken(Token.Type.KEYWORD, "continue"));
1294                     _chunk.bytecode[cont.gotoPatchParam + uint.sizeof] = cast(ubyte)depthSize;
1295                     cont.patched = true;
1296                 }
1297             }
1298         }
1299 
1300     }
1301 
1302     BinaryOpNode reduceAssignment(BinaryOpNode original)
1303     {
1304         switch(original.opToken.type)
1305         {
1306         case Token.Type.ASSIGN:
1307             return original; // nothing to do
1308         case Token.Type.PLUS_ASSIGN:
1309             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1310                     original.leftNode, 
1311                     new BinaryOpNode(Token.createFakeToken(Token.Type.PLUS,""),
1312                             original.leftNode, original.rightNode)
1313             );
1314         case Token.Type.DASH_ASSIGN:
1315             return new BinaryOpNode(Token.createFakeToken(Token.Type.ASSIGN, ""), 
1316                     original.leftNode, 
1317                     new BinaryOpNode(Token.createFakeToken(Token.Type.DASH,""),
1318                             original.leftNode, original.rightNode)
1319             );
1320         default:
1321             throw new Exception("Misuse of reduce assignment");
1322         }
1323     }
1324 
1325     void removePatches()
1326     {
1327         if(_compDataStack.top.loopOrSwitchStack == 0)
1328         {
1329             bool unresolved = false;
1330             if(_compDataStack.top.loopOrSwitchStack == 0)
1331             {
1332                 foreach(brk ; _compDataStack.top.breaksToPatch)
1333                 {
1334                     if(!brk.patched)
1335                     {
1336                         unresolved = true;
1337                         break;
1338                     }
1339                 }
1340 
1341                 foreach(cont ; _compDataStack.top.continuesToPatch)
1342                 {
1343                     if(!cont.patched)
1344                     {
1345                         unresolved = true;
1346                         break;
1347                     }
1348                 }
1349             }
1350             if(unresolved)
1351                 throw new ScriptCompileException("Unresolvable break or continue statement", 
1352                         Token.createInvalidToken(Position(0,0), "break/continue"));
1353             _compDataStack.top.breaksToPatch = [];
1354             _compDataStack.top.continuesToPatch = [];
1355         }
1356     }
1357 
1358     void throwUnimplemented(ExpressionNode expr)
1359     {
1360         throw new UnimplementedException("Unimplemented: " ~ expr.toString());
1361     }
1362 
1363     void throwUnimplemented(StatementNode stmt)
1364     {
1365         throw new UnimplementedException("Unimplemented: " ~ stmt.toString());
1366     }
1367 
1368     bool varExists(string name)
1369     {
1370         for(auto n = _compDataStack.size; n > 0; --n)
1371         {
1372             for(auto i = 1; i <= _compDataStack.array[n-1].stackVariables.array.length; ++i)
1373             {
1374                 if(name in _compDataStack.array[n-1].stackVariables.array[$-i])
1375                     return true;
1376             }
1377         }
1378         return false;
1379     }
1380 
1381     struct CompilationData
1382     {
1383         /// environment depth counter
1384         int depthCounter;
1385         /// how many loops nested
1386         int loopOrSwitchStack = 0;
1387         /// list of breaks needing patched
1388         BreakOrContinueToPatch[] breaksToPatch;
1389         /// list of continues needing patched
1390         BreakOrContinueToPatch[] continuesToPatch;
1391 
1392         /// holds stack variables
1393         Stack!VarTable stackVariables;
1394         
1395         /// for-of depth (this allocated 2 stack slots)
1396         int forOfDepth;
1397     }
1398 
1399     struct BreakOrContinueToPatch
1400     {
1401         this(string lbl, size_t param, int d, int ll)
1402         {
1403             labelName = lbl;
1404             gotoPatchParam = param;
1405             depth = d;
1406             loopLevel = ll;
1407         }
1408         string labelName;
1409         size_t gotoPatchParam;
1410         int depth;
1411         int loopLevel;
1412         bool patched = false;
1413     }
1414 
1415     struct VarMetadata
1416     {
1417         bool isDefined;
1418         int stackLocation; // can be -1 for regular lookup
1419         int funcDepth; // how deep in function calls
1420         bool isConst;
1421         VarDeclarationStatementNode varDecls;
1422     }
1423 
1424     alias VarTable = VarMetadata[string];
1425 
1426     /// when parsing a class expression or statement, if there is a base class it is added and poppped
1427     /// so that super expressions can be processed
1428     ExpressionNode[] _baseClassStack;
1429 
1430     /// the chunk being compiled
1431     Chunk _chunk;
1432 
1433     /// current source to send to each debugInfo
1434     string _currentSource;
1435 
1436     /// debug info stack
1437     Stack!DebugInfo _debugInfoStack;
1438 
1439     Stack!CompilationData _compDataStack;
1440     /**
1441      * The stack is guaranteed to be empty between statements so absolute stack positions for variables
1442      * can be used. The var name and stack ID is stored in the environment. The stack must be manually cleaned up
1443      */
1444     size_t _stackVarCounter = 0;
1445     /// keep track of function depth
1446     size_t _funcDepth;
1447     /// In case of a return statement in a for loop
1448     Stack!size_t _counterStack;
1449 }
1450 
1451 unittest
1452 {
1453     import mildew.environment: Environment;
1454     auto compiler = new Compiler();
1455     // auto chunk = compiler.compile("5 == 5 ? 'ass' : 'titties';");
1456     auto vm = new VirtualMachine(new Environment(null, "<global>"));
1457     // vm.printChunk(chunk);
1458     // vm.run(chunk);
1459 }