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