added "unused locals" and "use before initialized" to analyzer (incomplete)
[gaemu.git] / gmlvm.d
blobcb562bf91977ff57e3b34c981d662a162d6711b8
1 module gmlvm is aliced;
3 import std.stdio : File;
4 import std.traits;
6 import gmlparser;
9 // ////////////////////////////////////////////////////////////////////////// //
10 //alias Real = float;
11 alias Real = double;
14 // value manipulation
15 bool isReal (Real v) {
16 import std.math;
17 return !isNaN(v);
20 bool isString (Real v) {
21 import std.math;
22 return isNaN(v);
25 bool isUndef (Real v) {
26 import std.math;
27 return (isNaN(v) && getNaNPayload(v) < 0);
30 // creates "undefined" value
31 Real undefValue () {
32 import std.math;
33 return NaN(-666);
36 // for invalid strings it returns 0
37 int getStrId (Real v) {
38 import std.math;
39 if (isNaN(v)) {
40 auto res = getNaNPayload(v);
41 static if (Real.sizeof == 4) {
42 return (res < 0 ? 0 : cast(int)res);
43 } else {
44 return (res < 0 || res > int.max ? 0 : cast(int)res);
46 } else {
47 return 0;
51 Real buildStrId (int id) {
52 import std.math;
53 static if (Real.sizeof == 4) {
54 assert(id >= 0 && id <= 0x3F_FFFF);
55 } else {
56 assert(id >= 0);
58 return NaN(id);
62 Real Value(T) (VM vm, T v) {
63 pragma(inline, true);
64 static if (is(T : const(char)[])) return buildStrId(vm.newDynStr(v));
65 else static if (is(T : Real)) return cast(Real)v;
66 else static assert(0, "invalid value type");
70 // ////////////////////////////////////////////////////////////////////////// //
71 enum Op {
72 nop,
73 skip, // skip current instruction; it usually has 3-byte payload
75 copy, // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
77 lnot, //: lognot
78 neg,
79 bneg,
81 add,
82 sub,
83 mul,
84 mod,
85 div,
86 rdiv,
87 bor,
88 bxor,
89 band,
90 shl,
91 shr,
92 lt,
93 le,
94 gt,
95 ge,
96 eq,
97 ne,
98 lor,
99 land,
100 lxor,
102 plit, // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot; if val is 0xffff, next instruction is skip
103 ilit, // dest becomes ilit val (val: short) -- load small integer literal
104 xlit, // dest becomes integer(!) val (val: short) -- load small integer literal
106 jump, // addr: 3 bytes
107 xtrue, // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
108 xfalse, // dest is reg to check; skip next instruction if dest is "gml false" (i.e. fabs(v) >= 0.5`)
110 call, // dest is result; op0: call frame (see below); op1: number of args
111 // call frame is:
112 // new function frame
113 // int scriptid (after op1+3 slots)
114 // note that there should be no used registers after those (as that will be used as new function frame regs)
116 enter, // dest: number of arguments used; op0: number of stack slots used (including result and args); op1: number of locals
117 // any function will ALWAYS starts with this
119 ret, // dest is retvalue; it is copied to reg0; other stack items are discarded
121 //as we are using refloads only in the last stage of assignment, they can create values
122 lref, // load slot reference to dest
123 oref, // load object reference to dest; op0: int reg (obj id; -666: global object)
124 fref, // load field reference; op0: varref; op1: int reg (field id); can't create fields
125 fcrf, // load field reference; op0: varref; op1: int reg (field id); can create field
126 iref, // load indexed reference; op0: varref; op1: int reg (index)
127 mref, // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
129 rload, // load from op0-varref to dest
130 rstore, // store to op0-varref from op1
132 oload, // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
133 iload, // load indexed (as iref)
134 mload, // load indexed (as mref)
137 //`with` is done by copying `self` to another reg, execute the code and restore `self`
139 siter, // start instance iterator; dest: iterid; op0: objid or instid
140 // this is special: it will skip next instruction if iteration has at least one item
141 // next instruction is always jump, which skips the loop
142 niter, // dest is iterreg; do jump (pc is the same as in jump) if iteration is NOT complete
143 kiter, // kill iterator, should be called to prevent memory leaks
145 // so return from `with` should call kiter for all created iterators first
147 // possible iterator management: preallocate slots for each non-overlapped "with";
148 // let VM to free all iterators from those slots on function exit
150 lirint, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
154 // ////////////////////////////////////////////////////////////////////////// //
155 final class VM {
156 public:
157 enum Slot {
158 Self,
159 Other,
160 Argument0,
161 Argument1,
162 Argument2,
163 Argument3,
164 Argument4,
165 Argument5,
166 Argument6,
167 Argument7,
168 Argument8,
169 Argument9,
170 Argument10,
171 Argument11,
172 Argument12,
173 Argument13,
174 Argument14,
175 Argument15,
178 private:
179 alias PrimDg = Real delegate (uint pc, Real* bp, ubyte argc);
181 static struct Str {
182 string val; // string value
183 uint rc; // refcount; <0: persistent string; also serves as free list index with 31 bit set
186 private:
187 uint[] code; // [0] is reserved
188 uint[string] scripts; // name -> number
189 string[uint] scriptNum2Name;
190 int[] scriptPCs; // by number; 0 is reserved; <0: primitive number
191 NodeFunc[] scriptASTs; // by number
192 PrimDg[] prims; // by number
193 // fixuper will not remove fixup chains, so we can replace script with new one
194 Real[] vpool; // pool of values
195 Str[] spool; // pool of strings
196 uint spoolFree = 0x8000_0000; // none
197 Real[] globals;
198 uint[string] fields; // known fields and their offsets in object (and in globals too)
200 public:
201 // has rc of 1
202 uint newDynStr(T) (T str) if (is(T : const(char)[])) {
203 if (str.length == 0) return 0;
204 if (str.length == 1) return cast(uint)str.ptr[0]+1;
205 static if (is(T == string)) alias sv = str; else auto sv = str.idup;
206 if (spoolFree&0x7fff_ffff) {
207 // reuse existing
208 auto sid = spoolFree&0x7fff_ffff;
209 auto ss = spool.ptr+sid;
210 spoolFree = ss.rc;
211 ss.val = sv;
212 ss.rc = 1;
213 return sid;
214 } else {
215 // allocate new
216 auto sid = cast(uint)spool.length;
217 if (sid > 0x3F_FFFF) assert(0, "too many dynamic strings");
218 spool ~= Str(sv, 1);
219 return sid;
223 void dynStrIncRef (uint sid) {
224 pragma(inline, true);
225 if (sid < spool.length && spool.ptr[sid].rc > 0) {
226 assert(spool.ptr[sid].rc < 0x8000_0000);
227 ++spool.ptr[sid].rc;
231 void dynStrDecRef (uint sid) {
232 pragma(inline, true);
233 if (sid < spool.length && spool.ptr[sid].rc > 0) {
234 assert(spool.ptr[sid].rc < 0x8000_0000);
235 if (--spool.ptr[sid].rc == 0) {
236 spool.ptr[sid].rc = spoolFree;
237 spoolFree = sid|0x8000_0000;
242 string getDynStr (uint sid) {
243 pragma(inline, true);
244 return (sid < spool.length && spool.ptr[sid].rc < 0x8000_0000 ? spool.ptr[sid].val : null);
247 public:
248 this () {
249 code.length = 1;
250 scriptPCs.length = 1;
251 scriptASTs.length = 1;
252 prims.length = 1;
253 // preallocate small strings
254 spool ~= Str("", 0);
255 foreach (ubyte c; 0..256) spool ~= Str(""~cast(char)c, 0);
258 void compile (NodeFunc fn) {
259 import std.stdio : stdout;
260 auto spc = code.length;
261 doCompileFunc(fn);
262 while (spc < code.length) spc += dumpInstr(stdout, spc);
265 bool isJump (uint pc) {
266 if (pc < 1 || pc >= code.length) return false;
267 switch (code[pc].opCode) {
268 case Op.jump:
269 return true;
270 default: break;
272 return false;
275 // returns instruction size
276 uint dumpInstr (File fo, uint pc) {
277 fo.writef("%08X: ", pc);
278 if (pc == 0 || pc >= code.length) {
279 fo.writeln("<INVALID>");
280 return 1;
282 auto atp = opargs[code[pc].opCode];
283 if (atp == OpArgs.None) {
284 fo.writefln("%s", cast(Op)code[pc].opCode);
285 return 1;
287 fo.writef("%-8s", cast(Op)code[pc].opCode);
288 switch (atp) with (OpArgs) {
289 case Dest: fo.writefln("dest:%s", code[pc].opDest); break;
290 case DestOp0: fo.writefln("dest:%s, op0:%s", code[pc].opDest, code[pc].opOp0); break;
291 case DestOp0Op1: fo.writefln("dest:%s, op0:%s, op1:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
292 case Dest2Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op2Byte); break;
293 case Dest3Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op3Byte); break;
294 case DestInt: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].opILit); break;
295 case DestJump: fo.writefln("0x%08x", code[pc].op3Byte); break;
296 case DestCall: fo.writefln("dest:%s; frame:%s; args:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
297 case Op0Op1: fo.writefln("op0:%s, op1:%s", code[pc].opOp0, code[pc].opOp1); break;
298 default: assert(0);
300 return 1;
303 private:
304 void doCompileFunc (NodeFunc fn) {
305 import std.bitmanip; // BitArray
307 int argvar (string s) {
308 switch (s) {
309 case "argument0": return 0;
310 case "argument1": return 1;
311 case "argument2": return 2;
312 case "argument3": return 3;
313 case "argument4": return 4;
314 case "argument5": return 5;
315 case "argument6": return 6;
316 case "argument7": return 7;
317 case "argument8": return 8;
318 case "argument9": return 9;
319 case "argument10": return 10;
320 case "argument11": return 11;
321 case "argument12": return 12;
322 case "argument13": return 13;
323 case "argument14": return 14;
324 case "argument15": return 15;
325 default:
327 return -1;
330 void compileError(A...) (Loc loc, A args) {
331 if (fn.pp !is null) {
332 fn.pp.error(loc, args);
333 } else {
334 import std.stdio : stderr;
335 stderr.writeln("ERROR at ", loc, ": ", args);
336 string msg;
337 foreach (immutable a; args) {
338 import std.string : format;
339 msg ~= "%s".format(a);
341 throw new ErrorAt(loc, msg);
345 uint sid4name (string name) {
346 if (auto sptr = name in scripts) {
347 return *sptr;
348 } else {
349 auto sid = cast(uint)scriptPCs.length;
350 if (sid > 32767) compileError(fn.loc, "too many scripts");
351 assert(scriptASTs.length == sid);
352 // reserve slots
353 scriptPCs ~= 0;
354 scriptASTs ~= null;
355 scriptNum2Name[sid] = name;
356 scripts[name] = sid;
357 return sid;
361 uint pc () { return cast(uint)code.length; }
363 uint emit (Op op, ubyte dest=0, ubyte op0=0, ubyte op1=0) {
364 auto res = cast(uint)code.length;
365 code ~= (op1<<24)|(op0<<16)|(dest<<8)|cast(ubyte)op;
366 return res;
369 uint emit3Bytes (Op op, uint val) {
370 assert(val <= 0xffffff);
371 auto res = cast(uint)code.length;
372 code ~= (val<<8)|cast(ubyte)op;
373 return res;
376 uint emit2Bytes (Op op, ubyte dest, short val) {
377 auto res = cast(uint)code.length;
378 code ~= (val<<16)|(dest<<8)|cast(ubyte)op;
379 return res;
382 uint emitJumpTo (Op op, uint addr) {
383 assert(addr <= 0xffffff);
384 auto res = cast(uint)code.length;
385 code ~= cast(uint)op|(addr<<8);
386 return res;
389 // this starts "jump chain", return new chain id
390 uint emitJumpChain (uint chain, Op op=Op.jump) {
391 assert(chain <= 0xffffff);
392 auto res = cast(uint)code.length;
393 code ~= cast(uint)op|(chain<<8);
394 return res;
397 void fixJumpChain (uint chain, uint addr) {
398 assert(chain <= 0xffffff);
399 assert(addr <= 0xffffff);
400 while (chain) {
401 auto nc = op3Byte(code[chain]);
402 code[chain] = (code[chain]&0xff)|(addr<<8);
403 chain = nc;
407 assert(fn !is null);
408 assert(fn.ebody !is null);
409 assert(fn.name.length);
411 bool[256] slots;
412 foreach (immutable idx; 0..Slot.max+1) slots[idx] = true; // used
413 uint firstFreeSlot = Slot.max+1;
414 uint maxUsedSlot = firstFreeSlot-1;
416 ubyte allocSlot (Loc loc, int ddest=-1) {
417 if (ddest >= 0) {
418 assert(ddest < slots.length);
419 return cast(ubyte)ddest;
421 foreach (immutable idx; firstFreeSlot..slots.length) {
422 if (!slots[idx]) {
423 if (idx > maxUsedSlot) maxUsedSlot = cast(uint)idx;
424 slots[idx] = true;
425 return cast(ubyte)idx;
428 compileError(loc, "out of free slots");
429 assert(0);
432 ubyte reserveCallSlots (Loc loc, uint resnum) {
433 foreach_reverse (immutable idx, bool v; slots) {
434 if (v) {
435 if (idx+resnum+1 > slots.length) compileError(loc, "out of free slots");
436 return cast(ubyte)(idx+1);
439 compileError(loc, "out of free slots");
440 assert(0);
443 void freeSlot (ubyte num) {
444 if (num >= firstFreeSlot) {
445 assert(slots[num]);
446 slots[num] = false;
450 ubyte[string] locals;
451 uint[string] globals;
452 Loc[string] vdecls; // for error messages
453 ubyte maxArgUsed; // maximum `argumentX` we've seen
455 // collect var declarations (gml is not properly scoped)
456 visitNodes(fn.ebody, (Node n) {
457 if (auto vd = cast(NodeVarDecl)n) {
458 foreach (immutable idx, string name; vd.names) {
459 if (name in locals) {
460 if (vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
461 } else if (name in globals) {
462 if (!vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
464 vdecls[name] = vd.locs[idx];
465 if (vd.asGlobal) {
466 globals[name] = 0;
467 } else {
468 // don't allocate slots for locals here, we can remove some locals due to arguments aliasing later
469 //firstFreeSlot = allocSlot(vd.locs[idx]);
470 //locals[name] = cast(ubyte)firstFreeSlot;
471 //++firstFreeSlot;
472 locals[name] = 42; // temporary value
476 return VisitRes.Continue;
479 void findUninitialized () {
480 bool[string] inited;
481 bool[string] used;
483 void processExpr (Node n, bool asAss=false) {
484 if (n is null) return;
485 visitNodes(n, (Node nn) {
486 if (auto n = cast(NodeBinaryAss)nn) {
487 if (cast(NodeId)n.el is null && cast(NodeDot)n.el is null && cast(NodeIndex)n.el is null) compileError(nn.loc, "assignment to rvalue");
488 processExpr(n.er); // it is calculated first
489 if (auto did = cast(NodeId)n.el) {
490 inited[did.name] = true;
491 used[did.name] = true;
492 } else {
493 processExpr(n.el, asAss:true);
495 return VisitRes.SkipChildren;
497 if (auto id = cast(NodeId)nn) {
498 if (argvar(id.name) < 0 && id.name != "self" && id.name != "other") {
499 if (!asAss && id.name !in inited) compileError(nn.loc, "assignment to uninitialized variable");
501 inited[id.name] = true;
502 used[id.name] = true;
503 return VisitRes.SkipChildren;
505 if (auto n = cast(NodeFCall)nn) {
506 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
507 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
508 foreach (immutable idx, Node a; n.args) {
509 // no assignments allowed there
510 processExpr(a);
512 return VisitRes.SkipChildren;
514 return VisitRes.Continue;
518 void processStatement (Node nn) {
519 if (nn is null) return;
520 return selectNode!void(nn,
521 (NodeVarDecl n) {},
522 (NodeBlock n) {
523 foreach (Node st; n.stats) {
524 if (cast(NodeStatementBreakCont)st !is null) break;
525 processStatement(st);
526 if (cast(NodeReturn)st !is null) break;
529 (NodeStatementEmpty n) {},
530 (NodeStatementExpr n) { processExpr(n.e); },
531 (NodeReturn n) { processExpr(n.e); },
532 (NodeWith n) {
533 assert(0);
535 (NodeIf n) {
536 processExpr(n.ec);
537 auto before = inited.dup;
538 processStatement(n.et);
539 auto tset = inited.dup;
540 inited = before.dup;
541 processStatement(n.ef);
542 // now copy to `before` all items that are set both in `tset` and in `inited`
543 foreach (string name; inited.byKey) {
544 if (name in tset) before[name] = true;
546 inited = before;
548 (NodeStatementBreakCont n) {},
549 (NodeFor n) {
550 processExpr(n.einit);
551 // "next" and "cond" can't contain assignments, so it's safe here
552 processExpr(n.econd);
553 processExpr(n.enext);
554 // yet body can be executed zero times, so...
555 auto before = inited.dup;
556 processStatement(n.ebody);
557 inited = before;
559 (NodeWhile n) {
560 // "cond" can't contain assignments, so it's safe here
561 processExpr(n.econd);
562 // yet body can be executed zero times, so...
563 auto before = inited.dup;
564 processStatement(n.ebody);
565 inited = before;
567 (NodeDoUntil n) {
568 // "cond" can't contain assignments, so it's safe here
569 processExpr(n.econd);
570 // body is guaranteed to execute at least one time
571 processStatement(n.ebody);
573 (NodeRepeat n) {
574 // "count" can't contain assignments, so it's safe here
575 processExpr(n.ecount);
576 // yet body can be executed zero times, so...
577 auto before = inited.dup;
578 processStatement(n.ebody);
579 inited = before;
581 (NodeSwitch n) {
583 if (auto r = visitNodes(n.e, dg)) return r;
584 foreach (ref ci; n.cases) {
585 if (auto r = visitNodes(ci.e, dg)) return r;
586 if (auto r = visitNodes(ci.st, dg)) return r;
588 return null;
590 assert(0);
592 () { assert(0, "unimplemented node: "~typeid(nn).name); },
596 processStatement(fn.ebody);
597 // now remove unused locals
598 foreach (string name; locals.keys) {
599 if (name !in used) {
600 { import std.stdio; writeln("removing unused local '", name, "'"); }
601 locals.remove(name);
606 findUninitialized();
608 /* here we will do very simple analysis for code like
609 * var m, n;
610 * m = argument0;
611 * n = argument1;
612 * ...no `arument0` and `argument1` usage after this point
613 * we can just alias `m` to `arument0`, and `n` to `argument1` then
616 string[16] aaliases; // argument aliases
618 uint firstBadStatement = 0;
619 foreach (immutable idx, Node st; fn.ebody.stats) {
620 if (cast(NodeStatementEmpty)st || cast(NodeStatementExpr)st || cast(NodeVarDecl)st) {
621 firstBadStatement = cast(uint)idx+1;
622 } else {
623 break;
626 if (firstBadStatement > 0) {
627 bool[string] varsused;
628 // scan statements, find assignments
629 foreach (immutable idx, Node st; fn.ebody.stats[0..firstBadStatement]) {
630 if (auto se = cast(NodeStatementExpr)st) {
631 if (auto ass = cast(NodeBinaryAss)se.e) {
632 // wow, assignment
633 auto lv = cast(NodeId)ass.el;
634 auto rv = cast(NodeId)ass.er;
635 if (lv !is null && rv !is null) {
636 // "a = b"
637 { import std.stdio : stderr; stderr.writeln("found assignment: '", lv.name, "' = '", rv.name, "'"); }
638 if (argvar(rv.name) >= 0 && argvar(lv.name) < 0) {
639 // "a = argumentx"
640 if (lv.name in varsused || rv.name in varsused) continue; // no wai
641 if (lv.name !in locals) continue; // not a local
642 auto ai = argvar(rv.name);
643 if (aaliases[ai].length && aaliases[ai] != lv.name) continue; // already have an alias (TODO)
644 aaliases[ai] = lv.name; // possible alias
645 } else {
646 // check for reassignment
647 if (lv.name !in varsused) {
648 // not used before, but used now; remove it from aliases
649 foreach (ref an; aaliases) if (an == lv.name) an = null;
650 varsused[lv.name] = true;
657 // now check if we have any assignment to aliased argument
658 foreach (immutable idx, string an; aaliases) {
659 if (an.length == 0) continue;
660 visitNodes(fn.ebody, (Node n) {
661 if (auto ass = cast(NodeBinaryAss)n) {
662 if (auto id = cast(NodeId)ass.el) {
663 auto ai = argvar(id.name);
664 if (ai >= 0) aaliases[idx] = null;
665 return VisitRes.Stop;
668 return VisitRes.Continue;
671 // remove aliases from locals (we don't need slots for 'em)
672 foreach (immutable idx, string an; aaliases) {
673 if (an.length == 0) continue;
674 locals.remove(an);
676 // dump aliases
678 import std.stdio : stderr;
679 foreach (immutable idx, string an; aaliases) {
680 if (an.length) stderr.writeln("'argument", idx, "' is aliased to '", an, "'");
686 // now assign slots to locals
687 foreach (string name; locals.keys) {
688 firstFreeSlot = allocSlot(vdecls[name]);
689 locals[name] = cast(ubyte)firstFreeSlot;
690 ++firstFreeSlot;
693 void emitPLit (Loc loc, ubyte dest, Real v) {
694 uint vpidx = uint.max;
695 if (v.isReal) {
696 // number
697 import core.stdc.math : lrint;
698 if (lrint(v) == v && lrint(v) >= short.min && lrint(v) <= short.max) {
699 emit2Bytes(Op.ilit, dest, cast(short)lrint(v));
700 return;
702 //FIXME: speed it up!
703 foreach (immutable idx, Real vp; vpool) if (vp == v) { vpidx = cast(uint)idx; break; }
704 } else if (v.isString) {
705 // string
706 //FIXME: speed it up!
707 auto sid = v.getStrId;
708 foreach (immutable idx, Real vp; vpool) if (vp.isString && vp.getStrId == sid) { vpidx = cast(uint)idx; break; }
709 } else {
710 assert(0, "wtf?!");
712 if (vpidx == uint.max) {
713 vpidx = cast(uint)vpool.length;
714 if (vpidx >= 0xffffff) compileError(loc, "too many constants");
715 vpool ~= v;
717 if (vpidx < ushort.max) {
718 emit2Bytes(Op.plit, dest, cast(ushort)vpidx);
719 } else {
720 // special form
721 emit2Bytes(Op.plit, dest, cast(short)ushort.max);
722 emit3Bytes(Op.skip, vpidx);
726 uint allocStrConst (string s, Loc loc) {
727 if (s.length == 0) return 0;
728 //FIXME: speed it up!
729 foreach (immutable idx, ref ds; spool) {
730 if (ds.val == s) return cast(ushort)idx;
732 auto sidx = cast(uint)spool.length;
733 if (sidx >= 0xffffff) compileError(loc, "too many strings");
734 spool ~= Str(s, 0);
735 return sidx;
738 int varSlot (string name) {
739 auto avn = argvar(name);
740 if (avn >= 0) return Slot.Argument0+avn;
741 switch (name) {
742 case "self": return Slot.Self;
743 case "other": return Slot.Other;
744 default:
746 // argument aliases
747 foreach (immutable idx, string an; aaliases) if (an == name) return cast(int)Slot.Argument0+idx;
748 // locals
749 if (auto v = name in locals) return *v;
750 return -1;
753 // options for expression
754 static struct EOpts {
755 int ddest = -1; // >=0: put result in this slot
756 bool dna; // use `ddest` only if we don't need to allocate more slots
759 // returns dest slot
760 // can put value in desired dest
761 ubyte compileExpr (Node nn, int ddest=-1, bool wantref=false) {
762 ubyte doBinOp (Op op, NodeBinary n) {
763 auto dest = allocSlot(n.loc, ddest);
764 auto o0 = compileExpr(n.el);
765 auto o1 = compileExpr(n.er);
766 emit(op, dest, o0, o1);
767 freeSlot(o0);
768 freeSlot(o1);
769 return dest;
772 ubyte doUnOp (Op op, NodeUnary n) {
773 auto dest = allocSlot(n.loc, ddest);
774 auto o0 = compileExpr(n.e);
775 emit(op, dest, o0);
776 freeSlot(o0);
777 return dest;
780 nn.pcs = pc;
781 scope(exit) nn.pce = pc;
782 return selectNode!ubyte(nn,
783 (NodeLiteralNum n) {
784 auto dest = allocSlot(n.loc, ddest);
785 emitPLit(n.loc, dest, n.val);
786 return dest;
788 (NodeLiteralStr n) {
789 auto dest = allocSlot(n.loc, ddest);
790 auto sid = allocStrConst(n.val, n.loc);
791 emitPLit(n.loc, dest, buildStrId(sid));
792 return dest;
794 (NodeUnaryParens n) => compileExpr(n.e, ddest, wantref),
795 (NodeUnaryNot n) => doUnOp(Op.lnot, n),
796 (NodeUnaryNeg n) => doUnOp(Op.neg, n),
797 (NodeUnaryBitNeg n) => doUnOp(Op.bneg, n),
798 (NodeBinaryAss n) {
799 if (cast(NodeId)n.el is null && cast(NodeDot)n.el is null && cast(NodeIndex)n.el is null) compileError(n.loc, "assignment to rvalue");
800 if (auto did = cast(NodeId)n.el) {
801 auto vdst = varSlot(did.name);
802 assert(vdst >= 0);
803 auto dest = compileExpr(n.er, ddest:vdst);
804 freeSlot(dest);
805 } else {
806 auto src = compileExpr(n.er);
807 auto dest = compileExpr(n.el, wantref:true);
808 emit(Op.rstore, dest, src);
809 freeSlot(src);
810 freeSlot(dest);
812 return 0;
814 (NodeBinaryAdd n) => doBinOp(Op.add, n),
815 (NodeBinarySub n) => doBinOp(Op.sub, n),
816 (NodeBinaryMul n) => doBinOp(Op.mul, n),
817 (NodeBinaryRDiv n) => doBinOp(Op.rdiv, n),
818 (NodeBinaryDiv n) => doBinOp(Op.div, n),
819 (NodeBinaryMod n) => doBinOp(Op.mod, n),
820 (NodeBinaryBitOr n) => doBinOp(Op.bor, n),
821 (NodeBinaryBitAnd n) => doBinOp(Op.band, n),
822 (NodeBinaryBitXor n) => doBinOp(Op.bxor, n),
823 (NodeBinaryLShift n) => doBinOp(Op.shl, n),
824 (NodeBinaryRShift n) => doBinOp(Op.shr, n),
825 (NodeBinaryLess n) => doBinOp(Op.lt, n),
826 (NodeBinaryLessEqu n) => doBinOp(Op.le, n),
827 (NodeBinaryGreat n) => doBinOp(Op.gt, n),
828 (NodeBinaryGreatEqu n) => doBinOp(Op.ge, n),
829 (NodeBinaryEqu n) => doBinOp(Op.eq, n),
830 (NodeBinaryNotEqu n) => doBinOp(Op.ne, n),
831 (NodeBinaryLogOr n) => doBinOp(Op.lor, n),
832 (NodeBinaryLogAnd n) => doBinOp(Op.land, n),
833 (NodeBinaryLogXor n) => doBinOp(Op.lxor, n),
834 (NodeFCall n) {
835 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
836 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
837 auto dest = allocSlot(n.loc, ddest);
838 // preallocate frame
839 // we can do this, as current slot allocation scheme guarantees
840 // that we won't have used slots with higher numbert after compiling
841 // argument expressions
842 // `reserveCallSlots()` won't mark slots as used
843 auto frameSize = cast(uint)n.args.length+Slot.Argument0;
844 auto fcs = reserveCallSlots(n.loc, frameSize+1); // +1 for script id
845 // put arguments where we want 'em to be
846 foreach (immutable idx, Node a; n.args) {
847 // reserve result slot, so it won't be overwritten
848 assert(!slots[fcs+Slot.Argument0+idx]);
849 slots[fcs+Slot.Argument0+idx] = true;
850 auto dp = compileExpr(a, fcs+Slot.Argument0+idx);
851 if (dp != fcs+Slot.Argument0+idx) assert(0, "internal compiler error");
853 // now free result slots
854 foreach (immutable idx; 0..n.args.length) freeSlot(cast(ubyte)(fcs+Slot.Argument0+idx));
855 // make sure that our invariant holds
856 if (reserveCallSlots(n.loc, 1) != fcs) assert(0, "internal compiler error");
857 // put script id
858 // emit call
859 uint sid = sid4name((cast(NodeId)n.fe).name);
860 emit2Bytes(Op.xlit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)sid);
861 emit(Op.call, dest, fcs, cast(ubyte)n.args.length);
862 return dest;
864 (NodeId n) {
865 // keep track of maximum argument we've seen
866 if (maxArgUsed < 15) {
867 if (auto ai = argvar(n.name)) {
868 if (ai > maxArgUsed) maxArgUsed = cast(ubyte)ai;
871 if (wantref) {
872 auto vsl = varSlot(n.name);
873 assert(vsl >= 0);
874 auto dest = allocSlot(n.loc, ddest);
875 emit(Op.lref, dest, cast(ubyte)vsl);
876 return dest;
877 } else {
878 auto vsl = varSlot(n.name);
879 assert(vsl >= 0);
880 if (ddest < 0) return vsl; // just use this slot directly
881 auto dest = allocSlot(n.loc, ddest);
882 if (dest == vsl) return dest;
883 emit(Op.copy, dest, cast(ubyte)vsl, 1);
884 return dest;
886 assert(0);
887 //return 0;
889 (NodeDot n) {
890 assert(0);
892 (NodeIndex n) {
893 //if (auto r = visitNodes(n.ei0, dg)) return r;
894 //if (auto r = visitNodes(n.ei1, dg)) return r;
895 //return visitNodes(n.e, dg);
896 assert(0);
898 () { assert(0, "unimplemented node: "~typeid(nn).name); },
902 uint breakChain; // current jump chain for `break`
903 uint contChain; // current jump chain for `continue`
904 bool contChainIsAddr; // is `contChain` an address, not a chain?
905 bool inSwitch; // are we in `switch` now?
907 void compile (Node nn) {
908 assert(nn !is null);
909 nn.pcs = pc;
910 scope(exit) nn.pce = pc;
911 return selectNode!void(nn,
912 (NodeVarDecl n) {},
913 (NodeBlock n) {
914 foreach (Node st; n.stats) compile(st);
916 (NodeStatementEmpty n) {},
917 (NodeStatementExpr n) {
918 freeSlot(compileExpr(n.e));
920 (NodeReturn n) {
921 if (n.e is null) {
922 emit2Bytes(Op.ilit, 0, 0);
923 emit(Op.ret, 0);
924 } else {
925 auto dest = compileExpr(n.e);
926 emit(Op.ret, dest);
927 freeSlot(dest);
930 (NodeWith n) {
931 assert(0);
933 (NodeIf n) {
934 auto cs = compileExpr(n.ec);
935 freeSlot(cs); // yep, free it here
936 emit(Op.xtrue, cs);
937 uint jfc = 0;
938 // simple optimization
939 jfc = emitJumpChain(0, Op.jump);
940 compile(n.et);
941 if (n.ef !is null) {
942 auto exc = emitJumpChain(0, Op.jump);
943 fixJumpChain(jfc, pc);
944 jfc = exc;
945 compile(n.ef);
947 fixJumpChain(jfc, pc);
949 (NodeStatementBreak n) {
950 breakChain = emitJumpChain(breakChain);
952 (NodeStatementContinue n) {
953 if (contChainIsAddr) {
954 emitJumpTo(Op.jump, contChain);
955 } else {
956 contChain = emitJumpChain(contChain);
959 (NodeFor n) {
960 freeSlot(compileExpr(n.einit));
961 // generate code like this:
962 // jump to "continue"
963 // body
964 // continue:
965 // cond
966 // jumptostart
967 auto obc = breakChain;
968 auto occ = contChain;
969 auto cca = contChainIsAddr;
970 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
971 // jump to "continue"
972 contChain = emitJumpChain(0); // start new chain
973 contChainIsAddr = false;
974 breakChain = 0; // start new chain
975 auto stpc = pc;
976 // increment
977 freeSlot(compileExpr(n.enext));
978 // body
979 compile(n.ebody);
980 // fix "continue"
981 fixJumpChain(contChain, pc);
982 // condition
983 auto dest = compileExpr(n.econd);
984 freeSlot(dest); // yep, right here
985 emit(Op.xfalse, dest); // skip jump on false
986 emitJumpTo(Op.jump, stpc);
987 // "break" is here
988 fixJumpChain(breakChain, pc);
990 (NodeWhile n) {
991 // nothing fancy
992 auto obc = breakChain;
993 auto occ = contChain;
994 auto cca = contChainIsAddr;
995 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
996 // new break chain
997 breakChain = 0;
998 // "continue" is here
999 contChain = pc;
1000 contChainIsAddr = true;
1001 // condition
1002 auto dest = compileExpr(n.econd);
1003 freeSlot(dest); // yep, right here
1004 emit(Op.xfalse, dest); // skip jump on false
1005 breakChain = emitJumpChain(breakChain); // get out of here
1006 // body
1007 compile(n.ebody);
1008 // and again
1009 emitJumpTo(Op.jump, contChain);
1010 // "break" is here
1011 fixJumpChain(breakChain, pc);
1013 (NodeDoUntil n) {
1014 // nothing fancy
1015 auto obc = breakChain;
1016 auto occ = contChain;
1017 auto cca = contChainIsAddr;
1018 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
1019 auto stpc = pc;
1020 // new break chain
1021 breakChain = 0;
1022 // new continue chain
1023 contChain = 0;
1024 contChainIsAddr = false;
1025 // body
1026 compile(n.ebody);
1027 // "continue" is here
1028 fixJumpChain(contChain, pc);
1029 // condition
1030 auto dest = compileExpr(n.econd);
1031 freeSlot(dest); // yep, right here
1032 emit(Op.xfalse, dest); // skip jump on false
1033 // and again
1034 emitJumpTo(Op.jump, stpc);
1035 // "break" is here
1036 fixJumpChain(breakChain, pc);
1038 (NodeRepeat n) {
1039 // allocate node for counter
1040 auto cnt = compileExpr(n.ecount);
1041 // allocate "1" constant (we will need it)
1042 auto one = allocSlot(n.loc);
1043 emit2Bytes(Op.ilit, one, cast(short)1);
1044 // alice in chains
1045 auto obc = breakChain;
1046 auto occ = contChain;
1047 auto cca = contChainIsAddr;
1048 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
1049 // new break chain
1050 breakChain = 0;
1051 // "continue" is here
1052 contChain = pc;
1053 contChainIsAddr = true;
1054 // check and decrement counter
1055 auto ck = allocSlot(n.ecount.loc);
1056 freeSlot(ck); // we don't need that slot anymore, allow body to reuse it
1057 emit(Op.ge, ck, cnt, one);
1058 emit(Op.xtrue, ck);
1059 breakChain = emitJumpChain(breakChain); // get out of here
1060 // decrement counter in-place
1061 emit(Op.sub, cnt, cnt, one);
1062 // body
1063 compile(n.ebody);
1064 // and again
1065 emitJumpTo(Op.jump, contChain);
1066 // "break" is here
1067 fixJumpChain(breakChain, pc);
1068 // free used slots
1069 freeSlot(one);
1070 freeSlot(cnt);
1072 (NodeSwitch n) {
1074 if (auto r = visitNodes(n.e, dg)) return r;
1075 foreach (ref ci; n.cases) {
1076 if (auto r = visitNodes(ci.e, dg)) return r;
1077 if (auto r = visitNodes(ci.st, dg)) return r;
1079 return null;
1081 assert(0);
1083 () { assert(0, "unimplemented node: "~typeid(nn).name); },
1087 if (auto sid = fn.name in scripts) {
1088 if (scriptPCs[*sid] < 0) return; // can't override built-in function
1091 uint sid = sid4name(fn.name);
1092 /*debug(vm_exec)*/ { import std.stdio; writeln("compiling '", fn.name, "' (", sid, ")..."); }
1093 auto startpc = emit(Op.enter);
1094 fn.pcs = pc;
1095 compile(fn.ebody);
1096 emit(Op.ret);
1097 fn.pce = pc;
1098 // patch enter
1099 code[startpc] = (locals.length<<24)|((maxUsedSlot+1)<<16)|(maxArgUsed<<8)|cast(ubyte)Op.enter;
1100 scriptPCs[sid] = startpc;
1101 scriptASTs[sid] = fn;
1104 private:
1105 static struct CallFrame {
1106 uint script; // script id
1107 uint bp; // base pointer (address of the current frame in stack)
1108 uint pc; // current pc; will be set on "call"; it is used by callee
1109 ubyte rval; // slot for return value; will be set on "call"; it is used by callee
1110 @disable this (this);
1112 CallFrame[32768] frames;
1113 CallFrame* curframe;
1114 Real[] stack;
1116 void runtimeError(A...) (uint pc, A args) {
1117 import std.stdio : stderr;
1118 stderr.writef("ERROR at %08X: ", pc);
1119 stderr.writeln(args);
1120 // try to build stack trace
1121 if (curframe !is null) {
1122 curframe.pc = pc;
1123 auto cf = curframe;
1124 for (;;) {
1125 stderr.writefln("%08X: %s", cf.pc, scriptNum2Name[cf.script]);
1126 if (cf is frames.ptr) break; // it's not legal to compare pointers from different regions
1127 --cf;
1130 throw new Exception("fuuuuu");
1133 public void opIndexAssign(DG) (DG dg, string name) if (isCallable!DG) {
1134 assert(name.length > 0);
1135 uint sid;
1136 if (auto sptr = name in scripts) {
1137 sid = *sptr;
1138 } else {
1139 sid = cast(uint)scriptPCs.length;
1140 if (sid > 32767) assert(0, "too many scripts");
1141 assert(scriptASTs.length == sid);
1142 // reserve slots
1143 scriptPCs ~= 0;
1144 scriptASTs ~= null;
1145 scriptNum2Name[sid] = name;
1146 scripts[name] = sid;
1148 auto pnum = cast(uint)prims.length;
1149 assert(pnum);
1150 scriptPCs[sid] = -cast(int)pnum;
1151 prims ~= register(dg);
1154 public Real exec(A...) (string name, A args) {
1155 static assert(A.length < 16, "too many arguments");
1156 auto sid = scripts[name];
1157 assert(curframe is null);
1158 // create frame
1159 if (stack.length < 65536) stack.length = 65536;
1160 curframe = &frames[0];
1161 curframe.bp = 0;
1162 curframe.script = sid;
1163 stack[0..Slot.max+1] = 0;
1164 foreach (immutable idx, immutable a; args) {
1165 static if (is(typeof(a) : const(char)[])) {
1166 //FIXME
1167 assert(0);
1168 } else static if (is(typeof(a) : Real)) {
1169 stack[Slot.Argument0+idx] = cast(Real)a;
1170 } else {
1171 static assert(0, "invalid argument type");
1174 //{ import std.stdio; writeln(scriptPCs[sid]); }
1175 return doExec(scriptPCs[sid]);
1178 // current frame must be properly initialized
1179 Real doExec (uint pc) {
1180 enum BinOpMixin(string op, string ack="") =
1181 "auto dest = opx.opDest;\n"~
1182 "auto o0 = bp[opx.opOp0];\n"~
1183 "auto o1 = bp[opx.opOp1];\n"~
1184 ack~
1185 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1186 "bp[dest] = o0"~op~"o1;\n"~
1187 "break;";
1188 enum BinIOpMixin(string op, string ack="") =
1189 "auto dest = opx.opDest;\n"~
1190 "auto o0 = bp[opx.opOp0];\n"~
1191 "auto o1 = bp[opx.opOp1];\n"~
1192 ack~
1193 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1194 "bp[dest] = lrint(o0)"~op~"lrint(o1);\n"~
1195 "break;";
1197 enum BinCmpMixin(string op) =
1198 "auto dest = opx.opDest;\n"~
1199 "auto o0 = bp[opx.opOp0];\n"~
1200 "auto o1 = bp[opx.opOp1];\n"~
1201 "assert(!o0.isUndef && !o1.isUndef);\n"~
1202 "if (o0.isString) {\n"~
1203 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1204 " string s0 = spool[o0.getStrId].val;\n"~
1205 " string s1 = spool[o1.getStrId].val;\n"~
1206 " bp[dest] = (s0 "~op~" s1 ? 1 : 0);\n"~
1207 "} else {\n"~
1208 " assert(o0.isReal);\n"~
1209 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1210 " bp[dest] = (o0 "~op~" o1 ? 1 : 0);\n"~
1211 "}\n"~
1212 "break;";
1214 enum BinLogMixin(string op) =
1215 "auto dest = opx.opDest;\n"~
1216 "auto o0 = bp[opx.opOp0];\n"~
1217 "auto o1 = bp[opx.opOp1];\n"~
1218 "assert(!o0.isUndef && !o1.isUndef);\n"~
1219 "if (o0.isString) {\n"~
1220 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1221 " string s0 = spool[o0.getStrId].val;\n"~
1222 " string s1 = spool[o1.getStrId].val;\n"~
1223 " bp[dest] = (s0.length "~op~" s1.length ? 1 : 0);\n"~
1224 "} else {\n"~
1225 " assert(o0.isReal);\n"~
1226 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1227 " bp[dest] = (lrint(o0) "~op~" lrint(o1) ? 1 : 0);\n"~
1228 "}\n"~
1229 "break;";
1231 static if (is(Real == float)) {
1232 import core.stdc.math : lrint = lrintf;
1233 } else static if (is(Real == double)) {
1234 import core.stdc.math : lrint;
1235 } else {
1236 static assert(0, "wtf?!");
1238 assert(curframe !is null);
1239 assert(pc > 0 && pc < code.length);
1240 assert(code[pc].opCode == Op.enter);
1241 assert(stack.length > 0);
1242 auto bp = &stack[curframe.bp];
1243 auto origcf = curframe;
1244 auto cptr = code.ptr+pc;
1245 //if (stack.length < 65536) stack.length = 65536;
1246 debug(vm_exec) uint maxslots = Slot.max+1;
1247 for (;;) {
1248 debug(vm_exec) {
1249 import std.stdio : stderr;
1250 foreach (immutable idx; 0..maxslots) stderr.writeln(" ", idx, ": ", bp[idx]);
1251 dumpInstr(stderr, cast(uint)(cptr-code.ptr));
1253 auto opx = *cptr++;
1254 switch (opx.opCode) {
1255 case Op.nop:
1256 break;
1258 case Op.copy: // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
1259 import core.stdc.string : memmove;
1260 auto dest = opx.opDest;
1261 auto first = opx.opOp0;
1262 auto count = opx.opOp1;
1263 if (count) memmove(bp+dest, bp+first, count*Real.sizeof);
1264 break;
1266 case Op.lnot: // lognot
1267 auto dest = opx.opDest;
1268 auto o0 = bp[opx.opOp0];
1269 assert(!o0.isUndef);
1270 if (o0.isString) {
1271 auto s0 = spool[o0.getStrId].val;
1272 bp[dest] = (s0.length ? 0 : 1);
1273 } else {
1274 bp[dest] = (lrint(o0) ? 0 : 1);
1276 break;
1277 case Op.neg:
1278 auto dest = opx.opDest;
1279 auto o0 = bp[opx.opOp0];
1280 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1281 bp[dest] = -o0;
1282 break;
1283 case Op.bneg:
1284 auto dest = opx.opDest;
1285 auto o0 = bp[opx.opOp0];
1286 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1287 bp[dest] = cast(int)(~(cast(int)lrint(o0)));
1288 break;
1290 case Op.add:
1291 auto dest = opx.opDest;
1292 auto o0 = bp[opx.opOp0];
1293 auto o1 = bp[opx.opOp1];
1294 assert(!o0.isUndef && !o1.isUndef);
1295 if (o0.isString) {
1296 if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1297 string s0 = spool[o0.getStrId].val;
1298 string s1 = spool[o1.getStrId].val;
1299 //FIXME
1300 if (s0.length == 0) {
1301 bp[dest] = o1;
1302 } else if (s1.length == 0) {
1303 bp[dest] = o0;
1304 } else {
1305 bp[dest] = buildStrId(newDynStr(s0~s1));
1307 } else {
1308 assert(o0.isReal);
1309 if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1310 bp[dest] = o0+o1;
1312 break;
1313 case Op.sub: mixin(BinOpMixin!"-");
1314 case Op.mul: mixin(BinOpMixin!"*");
1315 case Op.mod: mixin(BinOpMixin!("%", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1316 case Op.div: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1317 case Op.rdiv: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1318 case Op.bor: mixin(BinIOpMixin!"|");
1319 case Op.bxor: mixin(BinIOpMixin!"^");
1320 case Op.band: mixin(BinIOpMixin!"&");
1321 case Op.shl: mixin(BinIOpMixin!"<<");
1322 case Op.shr: mixin(BinIOpMixin!">>");
1324 case Op.lt: mixin(BinCmpMixin!"<");
1325 case Op.le: mixin(BinCmpMixin!"<=");
1326 case Op.gt: mixin(BinCmpMixin!">");
1327 case Op.ge: mixin(BinCmpMixin!">=");
1328 case Op.eq: mixin(BinCmpMixin!"==");
1329 case Op.ne: mixin(BinCmpMixin!"!=");
1331 case Op.lor: mixin(BinLogMixin!"||");
1332 case Op.land: mixin(BinLogMixin!"&&");
1333 case Op.lxor: assert(0);
1335 case Op.plit: // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
1336 auto dest = opx.opDest;
1337 uint idx = cast(ushort)opx.op2Byte;
1338 if (idx == ushort.max) {
1339 assert((*cptr).opCode == Op.skip);
1340 idx = (*cptr++).op3Byte;
1342 bp[dest] = vpool.ptr[idx];
1343 break;
1344 case Op.ilit: // dest becomes ilit val (val: short) -- load small integer literal
1345 auto dest = opx.opDest;
1346 bp[dest] = opx.opILit;
1347 break;
1348 case Op.xlit: // dest becomes integer(!) val (val: short) -- load small integer literal
1349 auto dest = opx.opDest;
1350 *cast(uint*)(bp+dest) = opx.opILit;
1351 break;
1353 case Op.jump: // addr: 3 bytes
1354 cptr = code.ptr+opx.op3Byte;
1355 break;
1356 case Op.xtrue: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
1357 if (lrint(bp[opx.opDest]) != 0) ++cptr;
1358 break;
1359 case Op.xfalse: // dest is reg to check; skip next instruction if dest is "gml false" (i.e. fabs(v) >= 0.5`)
1360 if (lrint(bp[opx.opDest]) == 0) ++cptr;
1361 break;
1363 case Op.call: // dest is result; op0: call frame (see below); op1: number of args
1364 // call frame is:
1365 // new function frame
1366 // int scriptid (after op1+3 slots)
1367 // note that there should be no used registers after those (as that will be used as new function frame regs)
1368 auto sid = *cast(uint*)(bp+opx.opOp0+Slot.Argument0+opx.opOp1);
1369 if (sid >= scriptPCs.length) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid script id");
1370 pc = scriptPCs.ptr[sid];
1371 if (pc < 1 || pc >= code.length) {
1372 if (pc&0x8000_0000) {
1373 // this is primitive
1374 uint pid = -cast(int)pc;
1375 if (pid >= prims.length) assert(0, "wtf?!");
1376 bp[opx.opDest] = prims.ptr[pid](cast(uint)(cptr-code.ptr-1), bp+opx.opOp0, opx.opOp1);
1377 break;
1378 } else {
1379 string scname;
1380 foreach (auto kv; scripts.byKeyValue) if (kv.value == sid) { scname = kv.key; break; }
1381 runtimeError(cast(uint)(cptr-code.ptr-1), "trying to execute undefined script '", scname, "'");
1384 debug(vm_exec) {
1385 import std.stdio : stderr;
1386 stderr.writeln("calling '", scriptNum2Name[sid], "'");
1387 foreach (immutable aidx; 0..opx.opOp1) stderr.writeln(" ", bp[opx.opOp0+Slot.Argument0+aidx]);
1389 // if this is tail call, just do it as tail call then
1390 // but don't optimize out top-level call, heh
1391 if (curframe !is origcf && (*cptr).opCode == Op.ret) {
1392 import core.stdc.string : memcpy;
1393 // yay, it is a tail call!
1394 // copy arguments (it's safe to use `memcpy()` here); `self` and `other` are automatically ok
1395 if (opx.opOp1) memcpy(bp+Slot.Argument0, bp+opx.opOp0+Slot.Argument0, Real.sizeof*opx.opOp1);
1396 // simply replace current frame with new one
1397 } else {
1398 bp[opx.opOp0..opx.opOp0+Slot.Argument0] = bp[0..Slot.Argument0]; // copy `self` and `other`
1399 curframe.pc = cast(uint)(cptr-code.ptr);
1400 curframe.rval = opx.opDest;
1401 ++curframe;
1402 curframe.bp = curframe[-1].bp+opx.opOp0;
1403 bp = &stack[curframe.bp];
1405 curframe.script = sid;
1406 cptr = code.ptr+scriptPCs.ptr[sid];
1407 //assert((*cptr).opCode == Op.enter);
1408 // clear unused arguments, if any
1409 // we know that first instruction is always Op.enter, use that fact
1410 auto aused = (*cptr).opDest+1;
1411 //{ import std.stdio; writeln("aused=", aused, "; op1=", opx.opOp1); }
1412 if (aused > opx.opOp1) bp[Slot.Argument0+opx.opOp1..Slot.Argument0+aused] = 0;
1413 break;
1415 case Op.enter: // dest: number of arguments used; op0: number of stack slots used (including result and args); op1: number of locals
1416 if (curframe.bp+opx.opOp0 > stack.length) {
1417 stack.length = curframe.bp+opx.opOp0;
1418 bp = &stack[curframe.bp];
1420 //foreach (immutable idx; Slot.max+1..Slot.max+1+opx.opOp1) bp[idx] = 0; // clear locals
1421 if (opx.opOp1) bp[Slot.max+1..Slot.max+1+opx.opOp1] = 0; // clear locals
1422 debug(vm_exec) maxslots = opx.opOp0;
1423 debug(vm_exec) { import std.stdio : stderr; foreach (immutable idx; Slot.Argument0..Slot.Argument15+1) stderr.writeln(" :", bp[idx]); }
1424 break;
1426 case Op.ret: // dest is retvalue; it is copied to reg0; other stack items are discarded
1427 if (curframe is origcf) return bp[opx.opDest]; // done
1428 assert(cast(uint)curframe > cast(uint)origcf);
1429 --curframe;
1430 auto rv = bp[opx.opDest];
1431 // remove stack frame
1432 bp = &stack[curframe.bp];
1433 cptr = code.ptr+curframe.pc;
1434 bp[curframe.rval] = rv;
1435 debug(vm_exec) { import std.stdio : stderr; stderr.writeln("RET(", curframe.rval, "): ", rv); }
1436 break;
1438 //as we are using refloads only in the last stage of assignment, they can create values
1439 case Op.lref: // load slot reference to dest
1440 *cast(int*)bp[opx.opDest] = opx.opOp0;
1441 break;
1442 //case Op.oref: // load object reference to dest; op0: int reg (obj id; -666: global object)
1443 //case Op.fref: // load field reference; op0: varref; op1: int reg (field id); can't create fields
1444 //case Op.fcrf: // load field reference; op0: varref; op1: int reg (field id); can create field
1445 //case Op.iref: // load indexed reference; op0: varref; op1: int reg (index)
1446 //case Op.mref: // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
1448 //case Op.rload: // load from op0-varref to dest
1449 case Op.rstore: // store to op0-varref from op1
1450 auto x = *cast(int*)bp[opx.opOp0];
1451 assert(x >= 0 && x <= 255);
1452 bp[x] = bp[opx.opOp1];
1453 break;
1455 //case Op.oload: // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
1456 //case Op.iload: // load indexed (as iref)
1457 //case Op.mload: // load indexed (as mref)
1458 default: assert(0);
1463 private:
1464 // create primitive delegate for D delegate/function
1465 // D function can include special args like:
1466 // Real* -- bp
1467 // VM -- vm instance (should be at the end)
1468 // Real -- unmodified argument value
1469 // one or two args after VM: `self` and `other`
1470 // string, integer, float
1471 // no ref args are supported, sorry
1472 private PrimDg register(DG) (DG dg) @trusted if (isCallable!DG) {
1473 import core.stdc.math : lrint;
1474 assert(dg !is null);
1475 // build call thunk
1476 return delegate (uint pc, Real* bp, ubyte argc) {
1477 // prepare arguments
1478 Parameters!DG arguments;
1479 alias rt = ReturnType!dg;
1480 // (VM self, Real* bp, ubyte argc)
1481 static if (arguments.length == 3 &&
1482 is(typeof(arguments[0]) : VM) &&
1483 is(typeof(arguments[1]) == Real*) &&
1484 is(typeof(arguments[2]) : int))
1486 static if (is(rt == void)) {
1487 cast(void)dg(this, bp, cast(typeof(arguments[2]))argc);
1488 return cast(Real)0;
1489 } else {
1490 return Value(this, dg(this, bp, cast(typeof(arguments[2]))argc));
1492 } else {
1493 foreach (immutable idx, ref arg; arguments) {
1494 // is last argument suitable for `withobj`?
1495 static if (is(typeof(arg) : VM)) {
1496 arg = this;
1497 static if (idx+1 < arguments.length) {
1498 static assert(is(typeof(arguments[idx+1]) == Real), "invalid 'self' argument type");
1499 arguments[idx+1] = bp[Slot.Self];
1500 static if (idx+2 < arguments.length) {
1501 static assert(is(typeof(arguments[idx+2]) == Real), "invalid 'other' argument type");
1502 arguments[idx+2] = bp[Slot.Other];
1503 static assert(idx+3 == arguments.length, "too many extra arguments");
1506 } else {
1507 static assert(idx < 16, "too many arguments required");
1508 static if (is(typeof(arg) == const(char)[]) || is(typeof(arg) == string)) {
1509 auto v = bp[Slot.Argument0+idx];
1510 if (!v.isString) runtimeError(pc, "invalid argument type");
1511 arg = getDynStr(v.getStrId);
1512 } else static if (is(typeof(arg) == bool)) {
1513 auto v = bp[Slot.Argument0+idx];
1514 if (v.isString) arg = (v.getStrId != 0);
1515 else if (v.isReal) arg = (lrint(v) != 0);
1516 else runtimeError(pc, "invalid argument type");
1517 } else static if (is(typeof(arg) : long) || is(typeof(arg) : double)) {
1518 auto v = bp[Slot.Argument0+idx];
1519 if (!v.isReal) runtimeError(pc, "invalid D argument type");
1520 arg = cast(typeof(arg))v;
1524 static if (is(rt == void)) {
1525 cast(void)dg(arguments);
1526 return cast(Real)0;
1527 } else {
1528 return Value(this, dg(arguments));
1534 static:
1535 enum OpArgs {
1536 None,
1537 Dest,
1538 DestOp0,
1539 DestOp0Op1,
1540 Dest2Bytes,
1541 Dest3Bytes,
1542 DestInt,
1543 DestJump,
1544 DestCall,
1545 Op0Op1,
1547 immutable OpArgs[ubyte] opargs;
1548 shared static this () {
1549 with(OpArgs) opargs = [
1550 Op.nop: None,
1551 Op.skip: None,
1552 Op.copy: DestOp0Op1,
1553 Op.lnot: DestOp0, //: lognot
1554 Op.neg: DestOp0,
1555 Op.bneg: DestOp0,
1557 Op.add: DestOp0Op1,
1558 Op.sub: DestOp0Op1,
1559 Op.mul: DestOp0Op1,
1560 Op.mod: DestOp0Op1,
1561 Op.div: DestOp0Op1,
1562 Op.rdiv: DestOp0Op1,
1563 Op.bor: DestOp0Op1,
1564 Op.bxor: DestOp0Op1,
1565 Op.band: DestOp0Op1,
1566 Op.shl: DestOp0Op1,
1567 Op.shr: DestOp0Op1,
1568 Op.lt: DestOp0Op1,
1569 Op.le: DestOp0Op1,
1570 Op.gt: DestOp0Op1,
1571 Op.ge: DestOp0Op1,
1572 Op.eq: DestOp0Op1,
1573 Op.ne: DestOp0Op1,
1574 Op.lor: DestOp0Op1,
1575 Op.land: DestOp0Op1,
1576 Op.lxor: DestOp0Op1,
1578 Op.plit: Dest2Bytes,
1579 Op.ilit: DestInt,
1580 Op.xlit: DestInt,
1582 Op.jump: DestJump,
1583 Op.xtrue: Dest,
1584 Op.xfalse: Dest,
1586 Op.call: DestCall,
1588 Op.enter: DestOp0Op1,
1590 Op.ret: Dest,
1592 Op.lref: DestOp0,
1593 Op.oref: DestOp0,
1594 Op.fref: DestOp0Op1,
1595 Op.fcrf: DestOp0Op1,
1596 Op.iref: DestOp0Op1,
1597 Op.mref: DestOp0Op1,
1599 Op.rload: DestOp0,
1600 Op.rstore: DestOp0,
1602 Op.oload: DestOp0Op1,
1603 Op.iload: DestOp0Op1,
1604 Op.mload: DestOp0Op1,
1607 Op.siter: DestOp0,
1608 Op.niter: DestJump,
1609 Op.kiter: Dest,
1611 Op.lirint: DestOp0, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
1617 // ////////////////////////////////////////////////////////////////////////// //
1618 private:
1619 ubyte opCode (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op&0xff); }
1620 ubyte opDest (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>8)&0xff); }
1621 ubyte opOp0 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>16)&0xff); }
1622 ubyte opOp1 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>24)&0xff); }
1623 short opILit (uint op) pure nothrow @safe @nogc { pragma(inline, true); return cast(short)((op>>16)&0xffff); }
1624 uint op3Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>8); }
1625 uint op2Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>16); }
1627 uint opMakeILit (ubyte op, byte dest, short val) pure nothrow @safe @nogc { pragma(inline, true); return ((val<<16)|((dest&0xff)<<8)|op); }
1628 uint opMake3Byte (ubyte op, uint val) pure nothrow @safe @nogc { pragma(inline, true); assert(val <= 0xffffff); return (val<<8)|op; }