`switch` codegen
[gaemu.git] / gmlvm.d
blob1a0e177d7868912cd19dfbad3a9e714d13eaf4bc
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 (uint addr, Op op=Op.jump) {
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) {
488 compileError(nn.loc, "assignment to rvalue");
489 return VisitRes.SkipChildren;
491 processExpr(n.er); // it is calculated first
492 if (auto did = cast(NodeId)n.el) {
493 inited[did.name] = true;
494 used[did.name] = true;
495 } else {
496 processExpr(n.el, asAss:true);
498 return VisitRes.SkipChildren;
500 if (auto id = cast(NodeId)nn) {
501 if (argvar(id.name) < 0) {
502 if (!asAss && id.name in locals && id.name !in inited) {
503 compileError(nn.loc, "using uninitialized variable; declared at ", vdecls[id.name].toStringNoFile);
506 inited[id.name] = true;
507 used[id.name] = true;
508 return VisitRes.SkipChildren;
510 if (auto n = cast(NodeFCall)nn) {
511 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
512 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
513 foreach (immutable idx, Node a; n.args) {
514 // no assignments allowed there
515 processExpr(a);
517 return VisitRes.SkipChildren;
519 return VisitRes.Continue;
523 void processStatement (Node nn) {
524 if (nn is null) return;
525 return selectNode!void(nn,
526 (NodeVarDecl n) {},
527 (NodeBlock n) {
528 foreach (Node st; n.stats) {
529 if (cast(NodeStatementBreakCont)st !is null) break;
530 processStatement(st);
531 if (cast(NodeReturn)st !is null) break;
534 (NodeStatementEmpty n) {},
535 (NodeStatementExpr n) { processExpr(n.e); },
536 (NodeReturn n) { processExpr(n.e); },
537 (NodeWith n) {
538 processExpr(n.e); // can't contain assignments
539 // body can be executed zero times, so...
540 auto before = inited.dup;
541 processStatement(n.ebody);
542 inited = before;
544 (NodeIf n) {
545 processExpr(n.ec);
546 auto before = inited.dup;
547 processStatement(n.et);
548 auto tset = inited.dup;
549 inited = before.dup;
550 processStatement(n.ef);
551 // now copy to `before` all items that are set both in `tset` and in `inited`
552 foreach (string name; inited.byKey) {
553 if (name in tset) before[name] = true;
555 inited = before;
557 (NodeStatementBreakCont n) {},
558 (NodeFor n) {
559 processExpr(n.einit);
560 // "next" and "cond" can't contain assignments, so it's safe here
561 processExpr(n.econd);
562 processExpr(n.enext);
563 // yet body can be executed zero times, so...
564 auto before = inited.dup;
565 processStatement(n.ebody);
566 inited = before;
568 (NodeWhile n) {
569 // "cond" can't contain assignments, so it's safe here
570 processExpr(n.econd);
571 // yet body can be executed zero times, so...
572 auto before = inited.dup;
573 processStatement(n.ebody);
574 inited = before;
576 (NodeDoUntil n) {
577 // "cond" can't contain assignments, so it's safe here
578 processExpr(n.econd);
579 // body is guaranteed to execute at least one time
580 processStatement(n.ebody);
582 (NodeRepeat n) {
583 // "count" can't contain assignments, so it's safe here
584 processExpr(n.ecount);
585 // yet body can be executed zero times, so...
586 auto before = inited.dup;
587 processStatement(n.ebody);
588 inited = before;
590 (NodeSwitch n) {
591 // "expr" can't contain assignments, so it's safe here
592 processExpr(n.e);
593 auto before = inited.dup;
594 foreach (ref ci; n.cases) {
595 processExpr(ci.e); // can't contain assignments
596 // and this one can
597 if (ci.st !is null) {
598 inited = before.dup;
599 processStatement(ci.st);
602 inited = before;
604 () { assert(0, "unimplemented node: "~typeid(nn).name); },
608 processStatement(fn.ebody);
610 // now show (and remove) unused locals
611 //static struct Info { Loc loc; string name; }
612 //Info[] unusedLocs;
613 foreach (string name; locals.keys) {
614 if (name !in used) {
615 { import std.stdio; writeln("removing unused local '", name, "'"); }
616 //unusedLocs ~= Info(vdecls[name], name);
617 locals.remove(name);
620 //import std.algorithm : sort;
621 //unusedLocs.sort!((ref a, ref b) { if (a.loc.line < b.loc.line) return true; if (a.loc.line > b.loc.line) return false; return (a.loc.col < b.loc.col); });
622 //foreach (ref nfo; unusedLocs) compileError(nfo.loc, "unused local '", nfo.name, "'");
625 findUninitialized();
627 /* here we will do very simple analysis for code like
628 * var m, n;
629 * m = argument0;
630 * n = argument1;
631 * ...no `arument0` and `argument1` usage after this point
632 * we can just alias `m` to `arument0`, and `n` to `argument1` then
635 string[16] aaliases; // argument aliases
637 uint firstBadStatement = 0;
638 foreach (immutable idx, Node st; fn.ebody.stats) {
639 if (cast(NodeStatementEmpty)st || cast(NodeStatementExpr)st || cast(NodeVarDecl)st) {
640 firstBadStatement = cast(uint)idx+1;
641 } else {
642 break;
645 if (firstBadStatement > 0) {
646 bool[string] varsused;
647 // scan statements, find assignments
648 foreach (immutable idx, Node st; fn.ebody.stats[0..firstBadStatement]) {
649 if (auto se = cast(NodeStatementExpr)st) {
650 if (auto ass = cast(NodeBinaryAss)se.e) {
651 // wow, assignment
652 auto lv = cast(NodeId)ass.el;
653 auto rv = cast(NodeId)ass.er;
654 if (lv !is null && rv !is null) {
655 // "a = b"
656 { import std.stdio : stderr; stderr.writeln("found assignment: '", lv.name, "' = '", rv.name, "'"); }
657 if (argvar(rv.name) >= 0 && argvar(lv.name) < 0) {
658 // "a = argumentx"
659 if (lv.name in varsused || rv.name in varsused) continue; // no wai
660 if (lv.name !in locals) continue; // not a local
661 auto ai = argvar(rv.name);
662 if (aaliases[ai].length && aaliases[ai] != lv.name) continue; // already have an alias (TODO)
663 aaliases[ai] = lv.name; // possible alias
664 } else {
665 // check for reassignment
666 if (lv.name !in varsused) {
667 // not used before, but used now; remove it from aliases
668 foreach (ref an; aaliases) if (an == lv.name) an = null;
669 varsused[lv.name] = true;
676 // now check if we have any assignment to aliased argument
677 foreach (immutable idx, string an; aaliases) {
678 if (an.length == 0) continue;
679 visitNodes(fn.ebody, (Node n) {
680 if (auto ass = cast(NodeBinaryAss)n) {
681 if (auto id = cast(NodeId)ass.el) {
682 auto ai = argvar(id.name);
683 if (ai >= 0) aaliases[idx] = null;
684 return VisitRes.Stop;
687 return VisitRes.Continue;
690 // remove aliases from locals (we don't need slots for 'em)
691 foreach (immutable idx, string an; aaliases) {
692 if (an.length == 0) continue;
693 locals.remove(an);
695 // dump aliases
697 import std.stdio : stderr;
698 foreach (immutable idx, string an; aaliases) {
699 if (an.length) stderr.writeln("'argument", idx, "' is aliased to '", an, "'");
705 // now assign slots to locals
706 foreach (string name; locals.keys) {
707 firstFreeSlot = allocSlot(vdecls[name]);
708 locals[name] = cast(ubyte)firstFreeSlot;
709 ++firstFreeSlot;
712 void emitPLit (Loc loc, ubyte dest, Real v) {
713 uint vpidx = uint.max;
714 if (v.isReal) {
715 // number
716 import core.stdc.math : lrint;
717 if (lrint(v) == v && lrint(v) >= short.min && lrint(v) <= short.max) {
718 emit2Bytes(Op.ilit, dest, cast(short)lrint(v));
719 return;
721 //FIXME: speed it up!
722 foreach (immutable idx, Real vp; vpool) if (vp == v) { vpidx = cast(uint)idx; break; }
723 } else if (v.isString) {
724 // string
725 //FIXME: speed it up!
726 auto sid = v.getStrId;
727 foreach (immutable idx, Real vp; vpool) if (vp.isString && vp.getStrId == sid) { vpidx = cast(uint)idx; break; }
728 } else {
729 assert(0, "wtf?!");
731 if (vpidx == uint.max) {
732 vpidx = cast(uint)vpool.length;
733 if (vpidx >= 0xffffff) compileError(loc, "too many constants");
734 vpool ~= v;
736 if (vpidx < ushort.max) {
737 emit2Bytes(Op.plit, dest, cast(ushort)vpidx);
738 } else {
739 // special form
740 emit2Bytes(Op.plit, dest, cast(short)ushort.max);
741 emit3Bytes(Op.skip, vpidx);
745 uint allocStrConst (string s, Loc loc) {
746 if (s.length == 0) return 0;
747 //FIXME: speed it up!
748 foreach (immutable idx, ref ds; spool) {
749 if (ds.val == s) return cast(ushort)idx;
751 auto sidx = cast(uint)spool.length;
752 if (sidx >= 0xffffff) compileError(loc, "too many strings");
753 spool ~= Str(s, 0);
754 return sidx;
757 int varSlot (string name) {
758 auto avn = argvar(name);
759 if (avn >= 0) return Slot.Argument0+avn;
760 switch (name) {
761 case "self": return Slot.Self;
762 case "other": return Slot.Other;
763 default:
765 // argument aliases
766 foreach (immutable idx, string an; aaliases) if (an == name) return cast(int)Slot.Argument0+idx;
767 // locals
768 if (auto v = name in locals) return *v;
769 return -1;
772 // options for expression
773 static struct EOpts {
774 int ddest = -1; // >=0: put result in this slot
775 bool dna; // use `ddest` only if we don't need to allocate more slots
778 // returns dest slot
779 // can put value in desired dest
780 ubyte compileExpr (Node nn, int ddest=-1, bool wantref=false) {
781 ubyte doBinOp (Op op, NodeBinary n) {
782 auto dest = allocSlot(n.loc, ddest);
783 auto o0 = compileExpr(n.el);
784 auto o1 = compileExpr(n.er);
785 emit(op, dest, o0, o1);
786 freeSlot(o0);
787 freeSlot(o1);
788 return dest;
791 ubyte doUnOp (Op op, NodeUnary n) {
792 auto dest = allocSlot(n.loc, ddest);
793 auto o0 = compileExpr(n.e);
794 emit(op, dest, o0);
795 freeSlot(o0);
796 return dest;
799 nn.pcs = pc;
800 scope(exit) nn.pce = pc;
801 return selectNode!ubyte(nn,
802 (NodeLiteralNum n) {
803 auto dest = allocSlot(n.loc, ddest);
804 emitPLit(n.loc, dest, n.val);
805 return dest;
807 (NodeLiteralStr n) {
808 auto dest = allocSlot(n.loc, ddest);
809 auto sid = allocStrConst(n.val, n.loc);
810 emitPLit(n.loc, dest, buildStrId(sid));
811 return dest;
813 (NodeUnaryParens n) => compileExpr(n.e, ddest, wantref),
814 (NodeUnaryNot n) => doUnOp(Op.lnot, n),
815 (NodeUnaryNeg n) => doUnOp(Op.neg, n),
816 (NodeUnaryBitNeg n) => doUnOp(Op.bneg, n),
817 (NodeBinaryAss n) {
818 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");
819 if (auto did = cast(NodeId)n.el) {
820 auto vdst = varSlot(did.name);
821 assert(vdst >= 0);
822 auto dest = compileExpr(n.er, ddest:vdst);
823 freeSlot(dest);
824 } else {
825 auto src = compileExpr(n.er);
826 auto dest = compileExpr(n.el, wantref:true);
827 emit(Op.rstore, dest, src);
828 freeSlot(src);
829 freeSlot(dest);
831 return 0;
833 (NodeBinaryAdd n) => doBinOp(Op.add, n),
834 (NodeBinarySub n) => doBinOp(Op.sub, n),
835 (NodeBinaryMul n) => doBinOp(Op.mul, n),
836 (NodeBinaryRDiv n) => doBinOp(Op.rdiv, n),
837 (NodeBinaryDiv n) => doBinOp(Op.div, n),
838 (NodeBinaryMod n) => doBinOp(Op.mod, n),
839 (NodeBinaryBitOr n) => doBinOp(Op.bor, n),
840 (NodeBinaryBitAnd n) => doBinOp(Op.band, n),
841 (NodeBinaryBitXor n) => doBinOp(Op.bxor, n),
842 (NodeBinaryLShift n) => doBinOp(Op.shl, n),
843 (NodeBinaryRShift n) => doBinOp(Op.shr, n),
844 (NodeBinaryLess n) => doBinOp(Op.lt, n),
845 (NodeBinaryLessEqu n) => doBinOp(Op.le, n),
846 (NodeBinaryGreat n) => doBinOp(Op.gt, n),
847 (NodeBinaryGreatEqu n) => doBinOp(Op.ge, n),
848 (NodeBinaryEqu n) => doBinOp(Op.eq, n),
849 (NodeBinaryNotEqu n) => doBinOp(Op.ne, n),
850 (NodeBinaryLogOr n) => doBinOp(Op.lor, n),
851 (NodeBinaryLogAnd n) => doBinOp(Op.land, n),
852 (NodeBinaryLogXor n) => doBinOp(Op.lxor, n),
853 (NodeFCall n) {
854 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
855 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
856 auto dest = allocSlot(n.loc, ddest);
857 // preallocate frame
858 // we can do this, as current slot allocation scheme guarantees
859 // that we won't have used slots with higher numbert after compiling
860 // argument expressions
861 // `reserveCallSlots()` won't mark slots as used
862 auto frameSize = cast(uint)n.args.length+Slot.Argument0;
863 auto fcs = reserveCallSlots(n.loc, frameSize+1); // +1 for script id
864 // put arguments where we want 'em to be
865 foreach (immutable idx, Node a; n.args) {
866 // reserve result slot, so it won't be overwritten
867 assert(!slots[fcs+Slot.Argument0+idx]);
868 slots[fcs+Slot.Argument0+idx] = true;
869 auto dp = compileExpr(a, fcs+Slot.Argument0+idx);
870 if (dp != fcs+Slot.Argument0+idx) assert(0, "internal compiler error");
872 // now free result slots
873 foreach (immutable idx; 0..n.args.length) freeSlot(cast(ubyte)(fcs+Slot.Argument0+idx));
874 // make sure that our invariant holds
875 if (reserveCallSlots(n.loc, 1) != fcs) assert(0, "internal compiler error");
876 // put script id
877 // emit call
878 uint sid = sid4name((cast(NodeId)n.fe).name);
879 emit2Bytes(Op.xlit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)sid);
880 emit(Op.call, dest, fcs, cast(ubyte)n.args.length);
881 return dest;
883 (NodeId n) {
884 // keep track of maximum argument we've seen
885 if (maxArgUsed < 15) {
886 if (auto ai = argvar(n.name)) {
887 if (ai > maxArgUsed) maxArgUsed = cast(ubyte)ai;
890 if (wantref) {
891 auto vsl = varSlot(n.name);
892 assert(vsl >= 0);
893 auto dest = allocSlot(n.loc, ddest);
894 emit(Op.lref, dest, cast(ubyte)vsl);
895 return dest;
896 } else {
897 auto vsl = varSlot(n.name);
898 assert(vsl >= 0);
899 if (ddest < 0) return vsl; // just use this slot directly
900 auto dest = allocSlot(n.loc, ddest);
901 if (dest == vsl) return dest;
902 emit(Op.copy, dest, cast(ubyte)vsl, 1);
903 return dest;
905 assert(0);
906 //return 0;
908 (NodeDot n) {
909 assert(0);
911 (NodeIndex n) {
912 //if (auto r = visitNodes(n.ei0, dg)) return r;
913 //if (auto r = visitNodes(n.ei1, dg)) return r;
914 //return visitNodes(n.e, dg);
915 assert(0);
917 () { assert(0, "unimplemented node: "~typeid(nn).name); },
921 uint breakChain; // current jump chain for `break`
922 uint contChain; // current jump chain for `continue`
923 bool contChainIsAddr; // is `contChain` an address, not a chain?
925 void compile (Node nn) {
926 assert(nn !is null);
927 nn.pcs = pc;
928 scope(exit) nn.pce = pc;
929 return selectNode!void(nn,
930 (NodeVarDecl n) {},
931 (NodeBlock n) {
932 foreach (Node st; n.stats) compile(st);
934 (NodeStatementEmpty n) {},
935 (NodeStatementExpr n) {
936 freeSlot(compileExpr(n.e));
938 (NodeReturn n) {
939 if (n.e is null) {
940 emit2Bytes(Op.ilit, 0, 0);
941 emit(Op.ret, 0);
942 } else {
943 auto dest = compileExpr(n.e);
944 emit(Op.ret, dest);
945 freeSlot(dest);
948 (NodeWith n) {
949 assert(0);
951 (NodeIf n) {
952 auto cs = compileExpr(n.ec);
953 freeSlot(cs); // yep, free it here
954 emit(Op.xtrue, cs);
955 uint jfc = 0;
956 // simple optimization
957 jfc = emitJumpChain(0, Op.jump);
958 compile(n.et);
959 if (n.ef !is null) {
960 auto exc = emitJumpChain(0, Op.jump);
961 fixJumpChain(jfc, pc);
962 jfc = exc;
963 compile(n.ef);
965 fixJumpChain(jfc, pc);
967 (NodeStatementBreak n) {
968 breakChain = emitJumpChain(breakChain);
970 (NodeStatementContinue n) {
971 if (contChainIsAddr) {
972 emitJumpTo(contChain);
973 } else {
974 contChain = emitJumpChain(contChain);
977 (NodeFor n) {
978 freeSlot(compileExpr(n.einit));
979 // generate code like this:
980 // jump to "continue"
981 // body
982 // continue:
983 // cond
984 // jumptostart
985 auto obc = breakChain;
986 auto occ = contChain;
987 auto cca = contChainIsAddr;
988 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
989 // jump to "continue"
990 contChain = emitJumpChain(0); // start new chain
991 contChainIsAddr = false;
992 breakChain = 0; // start new chain
993 auto stpc = pc;
994 // increment
995 freeSlot(compileExpr(n.enext));
996 // body
997 compile(n.ebody);
998 // fix "continue"
999 fixJumpChain(contChain, pc);
1000 // condition
1001 auto dest = compileExpr(n.econd);
1002 freeSlot(dest); // yep, right here
1003 emit(Op.xfalse, dest); // skip jump on false
1004 emitJumpTo(stpc);
1005 // "break" is here
1006 fixJumpChain(breakChain, pc);
1008 (NodeWhile n) {
1009 // nothing fancy
1010 auto obc = breakChain;
1011 auto occ = contChain;
1012 auto cca = contChainIsAddr;
1013 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
1014 // new break chain
1015 breakChain = 0;
1016 // "continue" is here
1017 contChain = pc;
1018 contChainIsAddr = true;
1019 // condition
1020 auto dest = compileExpr(n.econd);
1021 freeSlot(dest); // yep, right here
1022 emit(Op.xfalse, dest); // skip jump on false
1023 breakChain = emitJumpChain(breakChain); // get out of here
1024 // body
1025 compile(n.ebody);
1026 // and again
1027 emitJumpTo(contChain);
1028 // "break" is here
1029 fixJumpChain(breakChain, pc);
1031 (NodeDoUntil n) {
1032 // nothing fancy
1033 auto obc = breakChain;
1034 auto occ = contChain;
1035 auto cca = contChainIsAddr;
1036 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
1037 auto stpc = pc;
1038 // new break chain
1039 breakChain = 0;
1040 // new continue chain
1041 contChain = 0;
1042 contChainIsAddr = false;
1043 // body
1044 compile(n.ebody);
1045 // "continue" is here
1046 fixJumpChain(contChain, pc);
1047 // condition
1048 auto dest = compileExpr(n.econd);
1049 freeSlot(dest); // yep, right here
1050 emit(Op.xfalse, dest); // skip jump on false
1051 // and again
1052 emitJumpTo(stpc);
1053 // "break" is here
1054 fixJumpChain(breakChain, pc);
1056 (NodeRepeat n) {
1057 // allocate node for counter
1058 auto cnt = compileExpr(n.ecount);
1059 // allocate "1" constant (we will need it)
1060 auto one = allocSlot(n.loc);
1061 emit2Bytes(Op.ilit, one, cast(short)1);
1062 // alice in chains
1063 auto obc = breakChain;
1064 auto occ = contChain;
1065 auto cca = contChainIsAddr;
1066 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
1067 // new break chain
1068 breakChain = 0;
1069 // "continue" is here
1070 contChain = pc;
1071 contChainIsAddr = true;
1072 // check and decrement counter
1073 auto ck = allocSlot(n.ecount.loc);
1074 freeSlot(ck); // we don't need that slot anymore, allow body to reuse it
1075 emit(Op.ge, ck, cnt, one);
1076 emit(Op.xtrue, ck);
1077 breakChain = emitJumpChain(breakChain); // get out of here
1078 // decrement counter in-place
1079 emit(Op.sub, cnt, cnt, one);
1080 // body
1081 compile(n.ebody);
1082 // and again
1083 emitJumpTo(contChain);
1084 // "break" is here
1085 fixJumpChain(breakChain, pc);
1086 // free used slots
1087 freeSlot(one);
1088 freeSlot(cnt);
1090 (NodeSwitch n) {
1091 // switch expression
1092 auto expr = compileExpr(n.e);
1093 if (n.cases.length) {
1094 // has some cases
1095 uint defaultBodyAddr = 0; // address of "default" node body (even if it is empty)
1096 uint lastFalltrhuJump = 0; // this is the address of the Op.jump at the end of the previous case node
1097 uint lastCaseSkipJumpAddr = 0; // this is the address of the Op.jump at the failed condition of the previous case node
1098 // new "break" chain
1099 auto obc = breakChain;
1100 scope(exit) breakChain = obc;
1101 breakChain = 0;
1102 // now generate code for case nodes, skipping "default" by the way
1103 foreach (immutable idx, ref ci; n.cases) {
1104 uint nodeSkipChain = 0;
1105 // check condition
1106 if (ci.e !is null) {
1107 // jump here from the last failed condition
1108 fixJumpChain(lastCaseSkipJumpAddr, pc);
1109 auto cond = compileExpr(ci.e);
1110 // trick: reuse "cond" slot
1111 freeSlot(cond);
1112 emit(Op.eq, cond, cond, expr);
1113 emit(Op.xtrue, cond);
1114 // new skip chain
1115 lastCaseSkipJumpAddr = emitJumpChain(0);
1116 } else {
1117 // this is default node, jump over it
1118 nodeSkipChain = emitJumpChain(0);
1119 // and save info
1120 defaultBodyAddr = pc;
1122 // fix fallthru jump
1123 fixJumpChain(lastFalltrhuJump, pc);
1124 // the body is here
1125 compile(ci.st);
1126 // new fallthru chain
1127 lastFalltrhuJump = (idx < n.cases.length-1 ? emitJumpChain(0) : 0);
1128 // fix "default skip" chain
1129 fixJumpChain(nodeSkipChain, pc);
1131 // we can free expression slot right here
1132 freeSlot(expr);
1133 // do we have default node?
1134 if (defaultBodyAddr) {
1135 // jump there from the last failed condition
1136 fixJumpChain(lastCaseSkipJumpAddr, defaultBodyAddr);
1137 } else {
1138 // jump here from the last failed condition
1139 fixJumpChain(lastCaseSkipJumpAddr, pc);
1141 // fix last fallthru jump
1142 fixJumpChain(lastFalltrhuJump, pc);
1143 // fix "break" chain
1144 fixJumpChain(breakChain, pc);
1145 } else {
1146 freeSlot(expr);
1149 () { assert(0, "unimplemented node: "~typeid(nn).name); },
1153 if (auto sid = fn.name in scripts) {
1154 if (scriptPCs[*sid] < 0) return; // can't override built-in function
1157 uint sid = sid4name(fn.name);
1158 /*debug(vm_exec)*/ { import std.stdio; writeln("compiling '", fn.name, "' (", sid, ")..."); }
1159 auto startpc = emit(Op.enter);
1160 fn.pcs = pc;
1161 compile(fn.ebody);
1162 emit(Op.ret);
1163 fn.pce = pc;
1164 // patch enter
1165 code[startpc] = (locals.length<<24)|((maxUsedSlot+1)<<16)|(maxArgUsed<<8)|cast(ubyte)Op.enter;
1166 scriptPCs[sid] = startpc;
1167 scriptASTs[sid] = fn;
1170 private:
1171 static struct CallFrame {
1172 uint script; // script id
1173 uint bp; // base pointer (address of the current frame in stack)
1174 uint pc; // current pc; will be set on "call"; it is used by callee
1175 ubyte rval; // slot for return value; will be set on "call"; it is used by callee
1176 @disable this (this);
1178 CallFrame[32768] frames;
1179 CallFrame* curframe;
1180 Real[] stack;
1182 void runtimeError(A...) (uint pc, A args) {
1183 import std.stdio : stderr;
1184 stderr.writef("ERROR at %08X: ", pc);
1185 stderr.writeln(args);
1186 // try to build stack trace
1187 if (curframe !is null) {
1188 curframe.pc = pc;
1189 auto cf = curframe;
1190 for (;;) {
1191 stderr.writefln("%08X: %s", cf.pc, scriptNum2Name[cf.script]);
1192 if (cf is frames.ptr) break; // it's not legal to compare pointers from different regions
1193 --cf;
1196 throw new Exception("fuuuuu");
1199 public void opIndexAssign(DG) (DG dg, string name) if (isCallable!DG) {
1200 assert(name.length > 0);
1201 uint sid;
1202 if (auto sptr = name in scripts) {
1203 sid = *sptr;
1204 } else {
1205 sid = cast(uint)scriptPCs.length;
1206 if (sid > 32767) assert(0, "too many scripts");
1207 assert(scriptASTs.length == sid);
1208 // reserve slots
1209 scriptPCs ~= 0;
1210 scriptASTs ~= null;
1211 scriptNum2Name[sid] = name;
1212 scripts[name] = sid;
1214 auto pnum = cast(uint)prims.length;
1215 assert(pnum);
1216 scriptPCs[sid] = -cast(int)pnum;
1217 prims ~= register(dg);
1220 public Real exec(A...) (string name, A args) {
1221 static assert(A.length < 16, "too many arguments");
1222 auto sid = scripts[name];
1223 assert(curframe is null);
1224 // create frame
1225 if (stack.length < 65536) stack.length = 65536;
1226 curframe = &frames[0];
1227 curframe.bp = 0;
1228 curframe.script = sid;
1229 stack[0..Slot.max+1] = 0;
1230 foreach (immutable idx, immutable a; args) {
1231 static if (is(typeof(a) : const(char)[])) {
1232 //FIXME
1233 assert(0);
1234 } else static if (is(typeof(a) : Real)) {
1235 stack[Slot.Argument0+idx] = cast(Real)a;
1236 } else {
1237 static assert(0, "invalid argument type");
1240 //{ import std.stdio; writeln(scriptPCs[sid]); }
1241 return doExec(scriptPCs[sid]);
1244 // current frame must be properly initialized
1245 Real doExec (uint pc) {
1246 enum BinOpMixin(string op, string ack="") =
1247 "auto dest = opx.opDest;\n"~
1248 "auto o0 = bp[opx.opOp0];\n"~
1249 "auto o1 = bp[opx.opOp1];\n"~
1250 ack~
1251 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1252 "bp[dest] = o0"~op~"o1;\n"~
1253 "break;";
1254 enum BinIOpMixin(string op, string ack="") =
1255 "auto dest = opx.opDest;\n"~
1256 "auto o0 = bp[opx.opOp0];\n"~
1257 "auto o1 = bp[opx.opOp1];\n"~
1258 ack~
1259 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1260 "bp[dest] = lrint(o0)"~op~"lrint(o1);\n"~
1261 "break;";
1263 enum BinCmpMixin(string op) =
1264 "auto dest = opx.opDest;\n"~
1265 "auto o0 = bp[opx.opOp0];\n"~
1266 "auto o1 = bp[opx.opOp1];\n"~
1267 "assert(!o0.isUndef && !o1.isUndef);\n"~
1268 "if (o0.isString) {\n"~
1269 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1270 " string s0 = spool[o0.getStrId].val;\n"~
1271 " string s1 = spool[o1.getStrId].val;\n"~
1272 " bp[dest] = (s0 "~op~" s1 ? 1 : 0);\n"~
1273 "} else {\n"~
1274 " assert(o0.isReal);\n"~
1275 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1276 " bp[dest] = (o0 "~op~" o1 ? 1 : 0);\n"~
1277 "}\n"~
1278 "break;";
1280 enum BinLogMixin(string op) =
1281 "auto dest = opx.opDest;\n"~
1282 "auto o0 = bp[opx.opOp0];\n"~
1283 "auto o1 = bp[opx.opOp1];\n"~
1284 "assert(!o0.isUndef && !o1.isUndef);\n"~
1285 "if (o0.isString) {\n"~
1286 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1287 " string s0 = spool[o0.getStrId].val;\n"~
1288 " string s1 = spool[o1.getStrId].val;\n"~
1289 " bp[dest] = (s0.length "~op~" s1.length ? 1 : 0);\n"~
1290 "} else {\n"~
1291 " assert(o0.isReal);\n"~
1292 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1293 " bp[dest] = (lrint(o0) "~op~" lrint(o1) ? 1 : 0);\n"~
1294 "}\n"~
1295 "break;";
1297 static if (is(Real == float)) {
1298 import core.stdc.math : lrint = lrintf;
1299 } else static if (is(Real == double)) {
1300 import core.stdc.math : lrint;
1301 } else {
1302 static assert(0, "wtf?!");
1304 assert(curframe !is null);
1305 assert(pc > 0 && pc < code.length);
1306 assert(code[pc].opCode == Op.enter);
1307 assert(stack.length > 0);
1308 auto bp = &stack[curframe.bp];
1309 auto origcf = curframe;
1310 auto cptr = code.ptr+pc;
1311 //if (stack.length < 65536) stack.length = 65536;
1312 debug(vm_exec) uint maxslots = Slot.max+1;
1313 for (;;) {
1314 debug(vm_exec) {
1315 import std.stdio : stderr;
1316 foreach (immutable idx; 0..maxslots) stderr.writeln(" ", idx, ": ", bp[idx]);
1317 dumpInstr(stderr, cast(uint)(cptr-code.ptr));
1319 auto opx = *cptr++;
1320 switch (opx.opCode) {
1321 case Op.nop:
1322 break;
1324 case Op.copy: // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
1325 import core.stdc.string : memmove;
1326 auto dest = opx.opDest;
1327 auto first = opx.opOp0;
1328 auto count = opx.opOp1;
1329 if (count) memmove(bp+dest, bp+first, count*Real.sizeof);
1330 break;
1332 case Op.lnot: // lognot
1333 auto dest = opx.opDest;
1334 auto o0 = bp[opx.opOp0];
1335 assert(!o0.isUndef);
1336 if (o0.isString) {
1337 auto s0 = spool[o0.getStrId].val;
1338 bp[dest] = (s0.length ? 0 : 1);
1339 } else {
1340 bp[dest] = (lrint(o0) ? 0 : 1);
1342 break;
1343 case Op.neg:
1344 auto dest = opx.opDest;
1345 auto o0 = bp[opx.opOp0];
1346 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1347 bp[dest] = -o0;
1348 break;
1349 case Op.bneg:
1350 auto dest = opx.opDest;
1351 auto o0 = bp[opx.opOp0];
1352 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1353 bp[dest] = cast(int)(~(cast(int)lrint(o0)));
1354 break;
1356 case Op.add:
1357 auto dest = opx.opDest;
1358 auto o0 = bp[opx.opOp0];
1359 auto o1 = bp[opx.opOp1];
1360 assert(!o0.isUndef && !o1.isUndef);
1361 if (o0.isString) {
1362 if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1363 string s0 = spool[o0.getStrId].val;
1364 string s1 = spool[o1.getStrId].val;
1365 //FIXME
1366 if (s0.length == 0) {
1367 bp[dest] = o1;
1368 } else if (s1.length == 0) {
1369 bp[dest] = o0;
1370 } else {
1371 bp[dest] = buildStrId(newDynStr(s0~s1));
1373 } else {
1374 assert(o0.isReal);
1375 if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1376 bp[dest] = o0+o1;
1378 break;
1379 case Op.sub: mixin(BinOpMixin!"-");
1380 case Op.mul: mixin(BinOpMixin!"*");
1381 case Op.mod: mixin(BinOpMixin!("%", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1382 case Op.div: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1383 case Op.rdiv: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1384 case Op.bor: mixin(BinIOpMixin!"|");
1385 case Op.bxor: mixin(BinIOpMixin!"^");
1386 case Op.band: mixin(BinIOpMixin!"&");
1387 case Op.shl: mixin(BinIOpMixin!"<<");
1388 case Op.shr: mixin(BinIOpMixin!">>");
1390 case Op.lt: mixin(BinCmpMixin!"<");
1391 case Op.le: mixin(BinCmpMixin!"<=");
1392 case Op.gt: mixin(BinCmpMixin!">");
1393 case Op.ge: mixin(BinCmpMixin!">=");
1394 case Op.eq: mixin(BinCmpMixin!"==");
1395 case Op.ne: mixin(BinCmpMixin!"!=");
1397 case Op.lor: mixin(BinLogMixin!"||");
1398 case Op.land: mixin(BinLogMixin!"&&");
1399 case Op.lxor: assert(0);
1401 case Op.plit: // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
1402 auto dest = opx.opDest;
1403 uint idx = cast(ushort)opx.op2Byte;
1404 if (idx == ushort.max) {
1405 assert((*cptr).opCode == Op.skip);
1406 idx = (*cptr++).op3Byte;
1408 bp[dest] = vpool.ptr[idx];
1409 break;
1410 case Op.ilit: // dest becomes ilit val (val: short) -- load small integer literal
1411 auto dest = opx.opDest;
1412 bp[dest] = opx.opILit;
1413 break;
1414 case Op.xlit: // dest becomes integer(!) val (val: short) -- load small integer literal
1415 auto dest = opx.opDest;
1416 *cast(uint*)(bp+dest) = opx.opILit;
1417 break;
1419 case Op.jump: // addr: 3 bytes
1420 cptr = code.ptr+opx.op3Byte;
1421 break;
1422 case Op.xtrue: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
1423 if (lrint(bp[opx.opDest]) != 0) ++cptr;
1424 break;
1425 case Op.xfalse: // dest is reg to check; skip next instruction if dest is "gml false" (i.e. fabs(v) >= 0.5`)
1426 if (lrint(bp[opx.opDest]) == 0) ++cptr;
1427 break;
1429 case Op.call: // dest is result; op0: call frame (see below); op1: number of args
1430 // call frame is:
1431 // new function frame
1432 // int scriptid (after op1+3 slots)
1433 // note that there should be no used registers after those (as that will be used as new function frame regs)
1434 auto sid = *cast(uint*)(bp+opx.opOp0+Slot.Argument0+opx.opOp1);
1435 if (sid >= scriptPCs.length) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid script id");
1436 pc = scriptPCs.ptr[sid];
1437 if (pc < 1 || pc >= code.length) {
1438 if (pc&0x8000_0000) {
1439 // this is primitive
1440 uint pid = -cast(int)pc;
1441 if (pid >= prims.length) assert(0, "wtf?!");
1442 bp[opx.opDest] = prims.ptr[pid](cast(uint)(cptr-code.ptr-1), bp+opx.opOp0, opx.opOp1);
1443 break;
1444 } else {
1445 string scname;
1446 foreach (auto kv; scripts.byKeyValue) if (kv.value == sid) { scname = kv.key; break; }
1447 runtimeError(cast(uint)(cptr-code.ptr-1), "trying to execute undefined script '", scname, "'");
1450 debug(vm_exec) {
1451 import std.stdio : stderr;
1452 stderr.writeln("calling '", scriptNum2Name[sid], "'");
1453 foreach (immutable aidx; 0..opx.opOp1) stderr.writeln(" ", bp[opx.opOp0+Slot.Argument0+aidx]);
1455 // if this is tail call, just do it as tail call then
1456 // but don't optimize out top-level call, heh
1457 if (curframe !is origcf && (*cptr).opCode == Op.ret) {
1458 import core.stdc.string : memcpy;
1459 // yay, it is a tail call!
1460 // copy arguments (it's safe to use `memcpy()` here); `self` and `other` are automatically ok
1461 if (opx.opOp1) memcpy(bp+Slot.Argument0, bp+opx.opOp0+Slot.Argument0, Real.sizeof*opx.opOp1);
1462 // simply replace current frame with new one
1463 } else {
1464 bp[opx.opOp0..opx.opOp0+Slot.Argument0] = bp[0..Slot.Argument0]; // copy `self` and `other`
1465 curframe.pc = cast(uint)(cptr-code.ptr);
1466 curframe.rval = opx.opDest;
1467 ++curframe;
1468 curframe.bp = curframe[-1].bp+opx.opOp0;
1469 bp = &stack[curframe.bp];
1471 curframe.script = sid;
1472 cptr = code.ptr+scriptPCs.ptr[sid];
1473 //assert((*cptr).opCode == Op.enter);
1474 // clear unused arguments, if any
1475 // we know that first instruction is always Op.enter, use that fact
1476 auto aused = (*cptr).opDest+1;
1477 //{ import std.stdio; writeln("aused=", aused, "; op1=", opx.opOp1); }
1478 if (aused > opx.opOp1) bp[Slot.Argument0+opx.opOp1..Slot.Argument0+aused] = 0;
1479 break;
1481 case Op.enter: // dest: number of arguments used; op0: number of stack slots used (including result and args); op1: number of locals
1482 if (curframe.bp+opx.opOp0 > stack.length) {
1483 stack.length = curframe.bp+opx.opOp0;
1484 bp = &stack[curframe.bp];
1486 //foreach (immutable idx; Slot.max+1..Slot.max+1+opx.opOp1) bp[idx] = 0; // clear locals
1487 if (opx.opOp1) bp[Slot.max+1..Slot.max+1+opx.opOp1] = 0; // clear locals
1488 debug(vm_exec) maxslots = opx.opOp0;
1489 debug(vm_exec) { import std.stdio : stderr; foreach (immutable idx; Slot.Argument0..Slot.Argument15+1) stderr.writeln(" :", bp[idx]); }
1490 break;
1492 case Op.ret: // dest is retvalue; it is copied to reg0; other stack items are discarded
1493 if (curframe is origcf) return bp[opx.opDest]; // done
1494 assert(cast(uint)curframe > cast(uint)origcf);
1495 --curframe;
1496 auto rv = bp[opx.opDest];
1497 // remove stack frame
1498 bp = &stack[curframe.bp];
1499 cptr = code.ptr+curframe.pc;
1500 bp[curframe.rval] = rv;
1501 debug(vm_exec) { import std.stdio : stderr; stderr.writeln("RET(", curframe.rval, "): ", rv); }
1502 break;
1504 //as we are using refloads only in the last stage of assignment, they can create values
1505 case Op.lref: // load slot reference to dest
1506 *cast(int*)bp[opx.opDest] = opx.opOp0;
1507 break;
1508 //case Op.oref: // load object reference to dest; op0: int reg (obj id; -666: global object)
1509 //case Op.fref: // load field reference; op0: varref; op1: int reg (field id); can't create fields
1510 //case Op.fcrf: // load field reference; op0: varref; op1: int reg (field id); can create field
1511 //case Op.iref: // load indexed reference; op0: varref; op1: int reg (index)
1512 //case Op.mref: // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
1514 //case Op.rload: // load from op0-varref to dest
1515 case Op.rstore: // store to op0-varref from op1
1516 auto x = *cast(int*)bp[opx.opOp0];
1517 assert(x >= 0 && x <= 255);
1518 bp[x] = bp[opx.opOp1];
1519 break;
1521 //case Op.oload: // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
1522 //case Op.iload: // load indexed (as iref)
1523 //case Op.mload: // load indexed (as mref)
1524 default: assert(0);
1529 private:
1530 // create primitive delegate for D delegate/function
1531 // D function can include special args like:
1532 // Real* -- bp
1533 // VM -- vm instance (should be at the end)
1534 // Real -- unmodified argument value
1535 // one or two args after VM: `self` and `other`
1536 // string, integer, float
1537 // no ref args are supported, sorry
1538 private PrimDg register(DG) (DG dg) @trusted if (isCallable!DG) {
1539 import core.stdc.math : lrint;
1540 assert(dg !is null);
1541 // build call thunk
1542 return delegate (uint pc, Real* bp, ubyte argc) {
1543 // prepare arguments
1544 Parameters!DG arguments;
1545 alias rt = ReturnType!dg;
1546 // (VM self, Real* bp, ubyte argc)
1547 static if (arguments.length == 3 &&
1548 is(typeof(arguments[0]) : VM) &&
1549 is(typeof(arguments[1]) == Real*) &&
1550 is(typeof(arguments[2]) : int))
1552 static if (is(rt == void)) {
1553 cast(void)dg(this, bp, cast(typeof(arguments[2]))argc);
1554 return cast(Real)0;
1555 } else {
1556 return Value(this, dg(this, bp, cast(typeof(arguments[2]))argc));
1558 } else {
1559 foreach (immutable idx, ref arg; arguments) {
1560 // is last argument suitable for `withobj`?
1561 static if (is(typeof(arg) : VM)) {
1562 arg = this;
1563 static if (idx+1 < arguments.length) {
1564 static assert(is(typeof(arguments[idx+1]) == Real), "invalid 'self' argument type");
1565 arguments[idx+1] = bp[Slot.Self];
1566 static if (idx+2 < arguments.length) {
1567 static assert(is(typeof(arguments[idx+2]) == Real), "invalid 'other' argument type");
1568 arguments[idx+2] = bp[Slot.Other];
1569 static assert(idx+3 == arguments.length, "too many extra arguments");
1572 } else {
1573 static assert(idx < 16, "too many arguments required");
1574 static if (is(typeof(arg) == const(char)[]) || is(typeof(arg) == string)) {
1575 auto v = bp[Slot.Argument0+idx];
1576 if (!v.isString) runtimeError(pc, "invalid argument type");
1577 arg = getDynStr(v.getStrId);
1578 } else static if (is(typeof(arg) == bool)) {
1579 auto v = bp[Slot.Argument0+idx];
1580 if (v.isString) arg = (v.getStrId != 0);
1581 else if (v.isReal) arg = (lrint(v) != 0);
1582 else runtimeError(pc, "invalid argument type");
1583 } else static if (is(typeof(arg) : long) || is(typeof(arg) : double)) {
1584 auto v = bp[Slot.Argument0+idx];
1585 if (!v.isReal) runtimeError(pc, "invalid D argument type");
1586 arg = cast(typeof(arg))v;
1590 static if (is(rt == void)) {
1591 cast(void)dg(arguments);
1592 return cast(Real)0;
1593 } else {
1594 return Value(this, dg(arguments));
1600 static:
1601 enum OpArgs {
1602 None,
1603 Dest,
1604 DestOp0,
1605 DestOp0Op1,
1606 Dest2Bytes,
1607 Dest3Bytes,
1608 DestInt,
1609 DestJump,
1610 DestCall,
1611 Op0Op1,
1613 immutable OpArgs[ubyte] opargs;
1614 shared static this () {
1615 with(OpArgs) opargs = [
1616 Op.nop: None,
1617 Op.skip: None,
1618 Op.copy: DestOp0Op1,
1619 Op.lnot: DestOp0, //: lognot
1620 Op.neg: DestOp0,
1621 Op.bneg: DestOp0,
1623 Op.add: DestOp0Op1,
1624 Op.sub: DestOp0Op1,
1625 Op.mul: DestOp0Op1,
1626 Op.mod: DestOp0Op1,
1627 Op.div: DestOp0Op1,
1628 Op.rdiv: DestOp0Op1,
1629 Op.bor: DestOp0Op1,
1630 Op.bxor: DestOp0Op1,
1631 Op.band: DestOp0Op1,
1632 Op.shl: DestOp0Op1,
1633 Op.shr: DestOp0Op1,
1634 Op.lt: DestOp0Op1,
1635 Op.le: DestOp0Op1,
1636 Op.gt: DestOp0Op1,
1637 Op.ge: DestOp0Op1,
1638 Op.eq: DestOp0Op1,
1639 Op.ne: DestOp0Op1,
1640 Op.lor: DestOp0Op1,
1641 Op.land: DestOp0Op1,
1642 Op.lxor: DestOp0Op1,
1644 Op.plit: Dest2Bytes,
1645 Op.ilit: DestInt,
1646 Op.xlit: DestInt,
1648 Op.jump: DestJump,
1649 Op.xtrue: Dest,
1650 Op.xfalse: Dest,
1652 Op.call: DestCall,
1654 Op.enter: DestOp0Op1,
1656 Op.ret: Dest,
1658 Op.lref: DestOp0,
1659 Op.oref: DestOp0,
1660 Op.fref: DestOp0Op1,
1661 Op.fcrf: DestOp0Op1,
1662 Op.iref: DestOp0Op1,
1663 Op.mref: DestOp0Op1,
1665 Op.rload: DestOp0,
1666 Op.rstore: DestOp0,
1668 Op.oload: DestOp0Op1,
1669 Op.iload: DestOp0Op1,
1670 Op.mload: DestOp0Op1,
1673 Op.siter: DestOp0,
1674 Op.niter: DestJump,
1675 Op.kiter: Dest,
1677 Op.lirint: DestOp0, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
1683 // ////////////////////////////////////////////////////////////////////////// //
1684 private:
1685 ubyte opCode (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op&0xff); }
1686 ubyte opDest (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>8)&0xff); }
1687 ubyte opOp0 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>16)&0xff); }
1688 ubyte opOp1 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>24)&0xff); }
1689 short opILit (uint op) pure nothrow @safe @nogc { pragma(inline, true); return cast(short)((op>>16)&0xffff); }
1690 uint op3Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>8); }
1691 uint op2Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>16); }
1693 uint opMakeILit (ubyte op, byte dest, short val) pure nothrow @safe @nogc { pragma(inline, true); return ((val<<16)|((dest&0xff)<<8)|op); }
1694 uint opMake3Byte (ubyte op, uint val) pure nothrow @safe @nogc { pragma(inline, true); assert(val <= 0xffffff); return (val<<8)|op; }