it is now possible to register buildins in VM
[gaemu.git] / gmlvm.d
blobeb67e5507afae67f29a0c3b938c0c214ce491c41
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 int argvar (string s) {
306 switch (s) {
307 case "argument0": return 0;
308 case "argument1": return 1;
309 case "argument2": return 2;
310 case "argument3": return 3;
311 case "argument4": return 4;
312 case "argument5": return 5;
313 case "argument6": return 6;
314 case "argument7": return 7;
315 case "argument8": return 8;
316 case "argument9": return 9;
317 case "argument10": return 10;
318 case "argument11": return 11;
319 case "argument12": return 12;
320 case "argument13": return 13;
321 case "argument14": return 14;
322 case "argument15": return 15;
323 default:
325 return -1;
328 void compileError(A...) (Loc loc, A args) {
329 if (fn.pp !is null) {
330 fn.pp.error(loc, args);
331 } else {
332 import std.stdio : stderr;
333 stderr.writeln("ERROR at ", loc, ": ", args);
334 string msg;
335 foreach (immutable a; args) {
336 import std.string : format;
337 msg ~= "%s".format(a);
339 throw new ErrorAt(loc, msg);
343 uint sid4name (string name) {
344 if (auto sptr = name in scripts) {
345 return *sptr;
346 } else {
347 auto sid = cast(uint)scriptPCs.length;
348 if (sid > 32767) compileError(fn.loc, "too many scripts");
349 assert(scriptASTs.length == sid);
350 // reserve slots
351 scriptPCs ~= 0;
352 scriptASTs ~= null;
353 scriptNum2Name[sid] = name;
354 scripts[name] = sid;
355 return sid;
359 uint pc () { return cast(uint)code.length; }
361 uint emit (Op op, ubyte dest=0, ubyte op0=0, ubyte op1=0) {
362 auto res = cast(uint)code.length;
363 code ~= (op1<<24)|(op0<<16)|(dest<<8)|cast(ubyte)op;
364 return res;
367 uint emit3Bytes (Op op, uint val) {
368 assert(val <= 0xffffff);
369 auto res = cast(uint)code.length;
370 code ~= (val<<8)|cast(ubyte)op;
371 return res;
374 uint emit2Bytes (Op op, ubyte dest, short val) {
375 auto res = cast(uint)code.length;
376 code ~= (val<<16)|(dest<<8)|cast(ubyte)op;
377 return res;
380 uint emitJumpTo (Op op, uint addr) {
381 assert(addr <= 0xffffff);
382 auto res = cast(uint)code.length;
383 code ~= cast(uint)op|(addr<<8);
384 return res;
387 // this starts "jump chain", return new chain id
388 uint emitJumpChain (uint chain, Op op=Op.jump) {
389 assert(chain <= 0xffffff);
390 auto res = cast(uint)code.length;
391 code ~= cast(uint)op|(chain<<8);
392 return res;
395 void fixJumpChain (uint chain, uint addr) {
396 assert(chain <= 0xffffff);
397 assert(addr <= 0xffffff);
398 while (chain) {
399 auto nc = op3Byte(code[chain]);
400 code[chain] = (code[chain]&0xff)|(addr<<8);
401 chain = nc;
405 assert(fn !is null);
406 assert(fn.ebody !is null);
407 assert(fn.name.length);
409 bool[256] slots;
410 foreach (immutable idx; 0..Slot.max+1) slots[idx] = true; // used
411 uint firstFreeSlot = Slot.max+1;
412 uint maxUsedSlot = firstFreeSlot-1;
414 ubyte allocSlot (Loc loc, int ddest=-1) {
415 if (ddest >= 0) {
416 assert(ddest < slots.length);
417 return cast(ubyte)ddest;
419 foreach (immutable idx; firstFreeSlot..slots.length) {
420 if (!slots[idx]) {
421 if (idx > maxUsedSlot) maxUsedSlot = cast(uint)idx;
422 slots[idx] = true;
423 return cast(ubyte)idx;
426 compileError(loc, "out of free slots");
427 assert(0);
430 ubyte reserveCallSlots (Loc loc, uint resnum) {
431 foreach_reverse (immutable idx, bool v; slots) {
432 if (v) {
433 if (idx+resnum+1 > slots.length) compileError(loc, "out of free slots");
434 return cast(ubyte)(idx+1);
437 compileError(loc, "out of free slots");
438 assert(0);
441 void freeSlot (ubyte num) {
442 if (num >= firstFreeSlot) {
443 assert(slots[num]);
444 slots[num] = false;
448 ubyte[string] locals;
449 uint[string] globals;
450 Loc[string] vdecls; // for error messages
452 // collect var declarations (gml is not properly scoped)
453 visitNodes(fn.ebody, (Node n) {
454 if (auto vd = cast(NodeVarDecl)n) {
455 foreach (immutable idx, string name; vd.names) {
456 if (name in locals) {
457 if (vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
458 } else if (name in globals) {
459 if (!vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
461 vdecls[name] = vd.locs[idx];
462 if (vd.asGlobal) {
463 globals[name] = 0;
464 } else {
465 // don't allocate slots for locals here, we can remove some locals due to arguments aliasing later
466 //firstFreeSlot = allocSlot(vd.locs[idx]);
467 //locals[name] = cast(ubyte)firstFreeSlot;
468 //++firstFreeSlot;
469 locals[name] = 42; // temporary value
473 return VisitRes.Continue;
476 /* here we will do very simple analysis for code like
477 * var m, n;
478 * m = argument0;
479 * n = argument1;
480 * ...no `arument0` and `argument1` usage after this point
481 * we can just alias `m` to `arument0`, and `n` to `argument1` then
484 string[16] aaliases; // argument aliases
486 uint firstBadStatement = 0;
487 foreach (immutable idx, Node st; fn.ebody.stats) {
488 if (cast(NodeStatementEmpty)st || cast(NodeStatementExpr)st || cast(NodeVarDecl)st) {
489 firstBadStatement = cast(uint)idx+1;
490 } else {
491 break;
494 if (firstBadStatement > 0) {
495 bool[string] varsused;
496 // scan statements, find assignments
497 foreach (immutable idx, Node st; fn.ebody.stats[0..firstBadStatement]) {
498 if (auto se = cast(NodeStatementExpr)st) {
499 if (auto ass = cast(NodeBinaryAss)se.e) {
500 // wow, assignment
501 auto lv = cast(NodeId)ass.el;
502 auto rv = cast(NodeId)ass.er;
503 if (lv !is null && rv !is null) {
504 // "a = b"
505 { import std.stdio : stderr; stderr.writeln("found assignment: '", lv.name, "' = '", rv.name, "'"); }
506 if (argvar(rv.name) >= 0 && argvar(lv.name) < 0) {
507 // "a = argumentx"
508 if (lv.name in varsused || rv.name in varsused) continue; // no wai
509 if (lv.name !in locals) continue; // not a local
510 auto ai = argvar(rv.name);
511 if (aaliases[ai].length && aaliases[ai] != lv.name) continue; // already have an alias (TODO)
512 aaliases[ai] = lv.name; // possible alias
513 } else {
514 // check for reassignment
515 if (lv.name !in varsused) {
516 // not used before, but used now; remove it from aliases
517 foreach (ref an; aaliases) if (an == lv.name) an = null;
518 varsused[lv.name] = true;
525 // now check if we have any assignment to aliased argument
526 foreach (immutable idx, string an; aaliases) {
527 if (an.length == 0) continue;
528 visitNodes(fn.ebody, (Node n) {
529 if (auto ass = cast(NodeBinaryAss)n) {
530 if (auto id = cast(NodeId)ass.el) {
531 auto ai = argvar(id.name);
532 if (ai >= 0) aaliases[idx] = null;
533 return VisitRes.Stop;
536 return VisitRes.Continue;
539 // remove aliases from locals (we don't need slots for 'em)
540 foreach (immutable idx, string an; aaliases) {
541 if (an.length == 0) continue;
542 locals.remove(an);
544 // dump aliases
546 import std.stdio : stderr;
547 foreach (immutable idx, string an; aaliases) {
548 if (an.length) stderr.writeln("'argument", idx, "' is aliased to '", an, "'");
554 // now assign slots to locals
555 foreach (string name; locals.keys) {
556 firstFreeSlot = allocSlot(vdecls[name]);
557 locals[name] = cast(ubyte)firstFreeSlot;
558 ++firstFreeSlot;
561 void emitPLit (Loc loc, ubyte dest, Real v) {
562 uint vpidx = uint.max;
563 if (v.isReal) {
564 // number
565 import core.stdc.math : lrint;
566 if (lrint(v) == v && lrint(v) >= short.min && lrint(v) <= short.max) {
567 emit2Bytes(Op.ilit, dest, cast(short)lrint(v));
568 return;
570 //FIXME: speed it up!
571 foreach (immutable idx, Real vp; vpool) if (vp == v) { vpidx = cast(uint)idx; break; }
572 } else if (v.isString) {
573 // string
574 //FIXME: speed it up!
575 auto sid = v.getStrId;
576 foreach (immutable idx, Real vp; vpool) if (vp.isString && vp.getStrId == sid) { vpidx = cast(uint)idx; break; }
577 } else {
578 assert(0, "wtf?!");
580 if (vpidx == uint.max) {
581 vpidx = cast(uint)vpool.length;
582 if (vpidx >= 0xffffff) compileError(loc, "too many constants");
583 vpool ~= v;
585 if (vpidx < ushort.max) {
586 emit2Bytes(Op.plit, dest, cast(ushort)vpidx);
587 } else {
588 // special form
589 emit2Bytes(Op.plit, dest, cast(short)ushort.max);
590 emit3Bytes(Op.skip, vpidx);
594 uint allocStrConst (string s, Loc loc) {
595 if (s.length == 0) return 0;
596 //FIXME: speed it up!
597 foreach (immutable idx, ref ds; spool) {
598 if (ds.val == s) return cast(ushort)idx;
600 auto sidx = cast(uint)spool.length;
601 if (sidx >= 0xffffff) compileError(loc, "too many strings");
602 spool ~= Str(s, 0);
603 return sidx;
606 int varSlot (string name) {
607 auto avn = argvar(name);
608 if (avn >= 0) return Slot.Argument0+avn;
609 switch (name) {
610 case "self": return Slot.Self;
611 case "other": return Slot.Other;
612 default:
614 // argument aliases
615 foreach (immutable idx, string an; aaliases) if (an == name) return cast(int)Slot.Argument0+idx;
616 // locals
617 if (auto v = name in locals) return *v;
618 return -1;
621 // options for expression
622 static struct EOpts {
623 int ddest = -1; // >=0: put result in this slot
624 bool dna; // use `ddest` only if we don't need to allocate more slots
627 // returns dest slot
628 // can put value in desired dest
629 ubyte compileExpr (Node nn, int ddest=-1, bool wantref=false) {
630 ubyte doBinOp (Op op, NodeBinary n) {
631 auto dest = allocSlot(n.loc, ddest);
632 auto o0 = compileExpr(n.el);
633 auto o1 = compileExpr(n.er);
634 emit(op, dest, o0, o1);
635 freeSlot(o0);
636 freeSlot(o1);
637 return dest;
640 ubyte doUnOp (Op op, NodeUnary n) {
641 auto dest = allocSlot(n.loc, ddest);
642 auto o0 = compileExpr(n.e);
643 emit(op, dest, o0);
644 freeSlot(o0);
645 return dest;
648 nn.pcs = pc;
649 scope(exit) nn.pce = pc;
650 return selectNode!ubyte(nn,
651 (NodeLiteralNum n) {
652 auto dest = allocSlot(n.loc, ddest);
653 emitPLit(n.loc, dest, n.val);
654 return dest;
656 (NodeLiteralStr n) {
657 auto dest = allocSlot(n.loc, ddest);
658 auto sid = allocStrConst(n.val, n.loc);
659 emitPLit(n.loc, dest, buildStrId(sid));
660 return dest;
662 (NodeUnaryParens n) => compileExpr(n.e, ddest, wantref),
663 (NodeUnaryNot n) => doUnOp(Op.lnot, n),
664 (NodeUnaryNeg n) => doUnOp(Op.neg, n),
665 (NodeUnaryBitNeg n) => doUnOp(Op.bneg, n),
666 (NodeBinaryAss n) {
667 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");
668 if (auto did = cast(NodeId)n.el) {
669 auto vdst = varSlot(did.name);
670 assert(vdst >= 0);
671 auto dest = compileExpr(n.er, ddest:vdst);
672 freeSlot(dest);
673 } else {
674 auto src = compileExpr(n.er);
675 auto dest = compileExpr(n.el, wantref:true);
676 emit(Op.rstore, dest, src);
677 freeSlot(src);
678 freeSlot(dest);
680 return 0;
682 (NodeBinaryAdd n) => doBinOp(Op.add, n),
683 (NodeBinarySub n) => doBinOp(Op.sub, n),
684 (NodeBinaryMul n) => doBinOp(Op.mul, n),
685 (NodeBinaryRDiv n) => doBinOp(Op.rdiv, n),
686 (NodeBinaryDiv n) => doBinOp(Op.div, n),
687 (NodeBinaryMod n) => doBinOp(Op.mod, n),
688 (NodeBinaryBitOr n) => doBinOp(Op.bor, n),
689 (NodeBinaryBitAnd n) => doBinOp(Op.band, n),
690 (NodeBinaryBitXor n) => doBinOp(Op.bxor, n),
691 (NodeBinaryLShift n) => doBinOp(Op.shl, n),
692 (NodeBinaryRShift n) => doBinOp(Op.shr, n),
693 (NodeBinaryLess n) => doBinOp(Op.lt, n),
694 (NodeBinaryLessEqu n) => doBinOp(Op.le, n),
695 (NodeBinaryGreat n) => doBinOp(Op.gt, n),
696 (NodeBinaryGreatEqu n) => doBinOp(Op.ge, n),
697 (NodeBinaryEqu n) => doBinOp(Op.eq, n),
698 (NodeBinaryNotEqu n) => doBinOp(Op.ne, n),
699 (NodeBinaryLogOr n) => doBinOp(Op.lor, n),
700 (NodeBinaryLogAnd n) => doBinOp(Op.land, n),
701 (NodeBinaryLogXor n) => doBinOp(Op.lxor, n),
702 (NodeFCall n) {
703 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
704 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
705 auto dest = allocSlot(n.loc, ddest);
706 // preallocate frame
707 // we can do this, as current slot allocation scheme guarantees
708 // that we won't have used slots with higher numbert after compiling
709 // argument expressions
710 // `reserveCallSlots()` won't mark slots as used
711 auto frameSize = cast(uint)n.args.length+Slot.Argument0;
712 auto fcs = reserveCallSlots(n.loc, frameSize+1); // +1 for script id
713 // put arguments where we want 'em to be
714 foreach (immutable idx, Node a; n.args) {
715 // reserve result slot, so it won't be overwritten
716 assert(!slots[fcs+Slot.Argument0+idx]);
717 slots[fcs+Slot.Argument0+idx] = true;
718 auto dp = compileExpr(a, fcs+Slot.Argument0+idx);
719 if (dp != fcs+Slot.Argument0+idx) assert(0, "internal compiler error");
721 // now free result slots
722 foreach (immutable idx; 0..n.args.length) freeSlot(cast(ubyte)(fcs+Slot.Argument0+idx));
723 // make sure that our invariant holds
724 if (reserveCallSlots(n.loc, 1) != fcs) assert(0, "internal compiler error");
725 // put script id
726 // emit call
727 uint sid = sid4name((cast(NodeId)n.fe).name);
728 emit2Bytes(Op.xlit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)sid);
729 emit(Op.call, dest, fcs, cast(ubyte)n.args.length);
730 return dest;
732 (NodeId n) {
733 if (wantref) {
734 auto vsl = varSlot(n.name);
735 assert(vsl >= 0);
736 auto dest = allocSlot(n.loc, ddest);
737 emit(Op.lref, dest, cast(ubyte)vsl);
738 return dest;
739 } else {
740 auto vsl = varSlot(n.name);
741 assert(vsl >= 0);
742 if (ddest < 0) return vsl; // just use this slot directly
743 auto dest = allocSlot(n.loc, ddest);
744 if (dest == vsl) return dest;
745 emit(Op.copy, dest, cast(ubyte)vsl, 1);
746 return dest;
748 assert(0);
749 //return 0;
751 (NodeDot n) {
752 assert(0);
754 (NodeIndex n) {
755 //if (auto r = visitNodes(n.ei0, dg)) return r;
756 //if (auto r = visitNodes(n.ei1, dg)) return r;
757 //return visitNodes(n.e, dg);
758 assert(0);
760 () { assert(0, "unimplemented node: "~typeid(nn).name); },
764 uint breakChain; // current jump chain for `break`
765 uint contChain; // current jump chain for `continue`
766 bool contChainIsAddr; // is `contChain` an address, not a chain?
767 bool inSwitch; // are we in `switch` now?
769 void compile (Node nn) {
770 assert(nn !is null);
771 nn.pcs = pc;
772 scope(exit) nn.pce = pc;
773 return selectNode!void(nn,
774 (NodeVarDecl n) {},
775 (NodeBlock n) {
776 foreach (Node st; n.stats) compile(st);
778 (NodeStatementEmpty n) {},
779 (NodeStatementExpr n) {
780 freeSlot(compileExpr(n.e));
782 (NodeReturn n) {
783 if (n.e is null) {
784 emit2Bytes(Op.ilit, 0, 0);
785 emit(Op.ret, 0);
786 } else {
787 auto dest = compileExpr(n.e);
788 emit(Op.ret, dest);
789 freeSlot(dest);
792 (NodeWith n) {
793 assert(0);
795 (NodeIf n) {
796 auto cs = compileExpr(n.ec);
797 freeSlot(cs); // yep, free it here
798 emit(Op.xtrue, cs);
799 uint jfc = 0;
800 // simple optimization
801 jfc = emitJumpChain(0, Op.jump);
802 compile(n.et);
803 if (n.ef !is null) {
804 auto exc = emitJumpChain(0, Op.jump);
805 fixJumpChain(jfc, pc);
806 jfc = exc;
807 compile(n.ef);
809 fixJumpChain(jfc, pc);
811 (NodeStatementBreak n) {
812 breakChain = emitJumpChain(breakChain);
814 (NodeStatementContinue n) {
815 if (contChainIsAddr) {
816 emitJumpTo(Op.jump, contChain);
817 } else {
818 contChain = emitJumpChain(contChain);
821 (NodeFor n) {
822 freeSlot(compileExpr(n.einit));
823 // generate code like this:
824 // jump to "continue"
825 // body
826 // continue:
827 // cond
828 // jumptostart
829 auto obc = breakChain;
830 auto occ = contChain;
831 auto cca = contChainIsAddr;
832 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
833 // jump to "continue"
834 contChain = emitJumpChain(0); // start new chain
835 contChainIsAddr = false;
836 breakChain = 0; // start new chain
837 auto stpc = pc;
838 // body
839 compile(n.ebody);
840 // fix "continue"
841 fixJumpChain(contChain, pc);
842 // condition
843 auto dest = compileExpr(n.econd);
844 freeSlot(dest); // yep, right here
845 emit(Op.xfalse); // skip jump on false
846 emitJumpTo(Op.jump, stpc);
847 // "break" is here
848 fixJumpChain(breakChain, pc);
850 (NodeWhile n) {
851 // nothing fancy
852 auto obc = breakChain;
853 auto occ = contChain;
854 auto cca = contChainIsAddr;
855 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
856 // new break chain
857 breakChain = 0;
858 // "continue" is here
859 contChain = pc;
860 contChainIsAddr = true;
861 // condition
862 auto dest = compileExpr(n.econd);
863 freeSlot(dest); // yep, right here
864 emit(Op.xfalse); // skip jump on false
865 breakChain = emitJumpChain(breakChain); // get out of here
866 // body
867 compile(n.ebody);
868 // and again
869 emitJumpTo(Op.jump, contChain);
870 // "break" is here
871 fixJumpChain(breakChain, pc);
873 (NodeDoUntil n) {
874 // nothing fancy
875 auto obc = breakChain;
876 auto occ = contChain;
877 auto cca = contChainIsAddr;
878 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
879 auto stpc = pc;
880 // new break chain
881 breakChain = 0;
882 // new continue chain
883 contChain = 0;
884 contChainIsAddr = false;
885 // body
886 compile(n.ebody);
887 // "continue" is here
888 fixJumpChain(contChain, pc);
889 // condition
890 auto dest = compileExpr(n.econd);
891 freeSlot(dest); // yep, right here
892 emit(Op.xfalse); // skip jump on false
893 // and again
894 emitJumpTo(Op.jump, stpc);
895 // "break" is here
896 fixJumpChain(breakChain, pc);
898 (NodeRepeat n) {
899 // allocate node for counter
900 auto cnt = compileExpr(n.ecount);
901 // allocate "1" constant (we will need it)
902 auto one = allocSlot(n.loc);
903 emit2Bytes(Op.ilit, one, cast(short)1);
904 // alice in chains
905 auto obc = breakChain;
906 auto occ = contChain;
907 auto cca = contChainIsAddr;
908 scope(exit) { breakChain = obc; contChain = occ; contChainIsAddr = cca; }
909 // new break chain
910 breakChain = 0;
911 // "continue" is here
912 contChain = pc;
913 contChainIsAddr = true;
914 // check and decrement counter
915 auto ck = allocSlot(n.ecount.loc);
916 freeSlot(ck); // we don't need that slot anymore, allow body to reuse it
917 emit(Op.ge, ck, cnt, one);
918 emit(Op.xtrue, ck);
919 breakChain = emitJumpChain(breakChain); // get out of here
920 // decrement counter in-place
921 emit(Op.sub, cnt, cnt, one);
922 // body
923 compile(n.ebody);
924 // and again
925 emitJumpTo(Op.jump, contChain);
926 // "break" is here
927 fixJumpChain(breakChain, pc);
928 // free used slots
929 freeSlot(one);
930 freeSlot(cnt);
932 (NodeSwitch n) {
934 if (auto r = visitNodes(n.e, dg)) return r;
935 foreach (ref ci; n.cases) {
936 if (auto r = visitNodes(ci.e, dg)) return r;
937 if (auto r = visitNodes(ci.st, dg)) return r;
939 return null;
941 assert(0);
943 () { assert(0, "unimplemented node: "~typeid(nn).name); },
947 if (auto sid = fn.name in scripts) {
948 if (scriptPCs[*sid] < 0) return; // can't override built-in function
951 uint sid = sid4name(fn.name);
952 //{ import std.stdio; writeln("compiling '", fn.name, "' (", sid, ")..."); }
953 auto startpc = emit(Op.enter);
954 fn.pcs = pc;
955 compile(fn.ebody);
956 emit(Op.ret);
957 fn.pce = pc;
958 // patch enter
959 code[startpc] = (locals.length<<24)|((maxUsedSlot+1)<<16)|cast(ubyte)Op.enter;
960 scriptPCs[sid] = startpc;
961 scriptASTs[sid] = fn;
964 private:
965 static struct CallFrame {
966 uint script; // script id
967 uint bp; // base pointer (address of the current frame in stack)
968 uint pc; // current pc; will be set on "call"; it is used by callee
969 ubyte rval; // slot for return value; will be set on "call"; it is used by callee
970 @disable this (this);
972 CallFrame[32768] frames;
973 CallFrame* curframe;
974 Real[] stack;
976 void runtimeError(A...) (uint pc, A args) {
977 import std.stdio : stderr;
978 stderr.writef("ERROR at %08X: ", pc);
979 stderr.writeln(args);
980 // try to build stack trace
981 if (curframe !is null) {
982 curframe.pc = pc;
983 auto cf = curframe;
984 for (;;) {
985 stderr.writefln("%08X: %s", cf.pc, scriptNum2Name[cf.script]);
986 if (cf is frames.ptr) break; // it's not legal to compare pointers from different regions
987 --cf;
990 throw new Exception("fuuuuu");
993 public void opIndexAssign(DG) (DG dg, string name) if (isCallable!DG) {
994 assert(name.length > 0);
995 uint sid;
996 if (auto sptr = name in scripts) {
997 sid = *sptr;
998 } else {
999 sid = cast(uint)scriptPCs.length;
1000 if (sid > 32767) assert(0, "too many scripts");
1001 assert(scriptASTs.length == sid);
1002 // reserve slots
1003 scriptPCs ~= 0;
1004 scriptASTs ~= null;
1005 scriptNum2Name[sid] = name;
1006 scripts[name] = sid;
1008 auto pnum = cast(uint)prims.length;
1009 assert(pnum);
1010 scriptPCs[sid] = -cast(int)pnum;
1011 prims ~= register(dg);
1014 public Real exec(A...) (string name, A args) {
1015 static assert(A.length < 16, "too many arguments");
1016 auto sid = scripts[name];
1017 assert(curframe is null);
1018 // create frame
1019 if (stack.length < 65536) stack.length = 65536;
1020 curframe = &frames[0];
1021 curframe.bp = 0;
1022 curframe.script = sid;
1023 stack[0..Slot.max+1] = 0;
1024 foreach (immutable idx, immutable a; args) {
1025 static if (is(typeof(a) : const(char)[])) {
1026 //FIXME
1027 assert(0);
1028 } else static if (is(typeof(a) : Real)) {
1029 stack[Slot.Argument0+idx] = cast(Real)a;
1030 } else {
1031 static assert(0, "invalid argument type");
1034 //{ import std.stdio; writeln(scriptPCs[sid]); }
1035 return doExec(scriptPCs[sid]);
1038 // current frame must be properly initialized
1039 Real doExec (uint pc) {
1040 enum BinOpMixin(string op, string ack="") =
1041 "auto dest = opx.opDest;\n"~
1042 "auto o0 = bp[opx.opOp0];\n"~
1043 "auto o1 = bp[opx.opOp1];\n"~
1044 ack~
1045 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1046 "bp[dest] = o0"~op~"o1;\n"~
1047 "break;";
1048 enum BinIOpMixin(string op, string ack="") =
1049 "auto dest = opx.opDest;\n"~
1050 "auto o0 = bp[opx.opOp0];\n"~
1051 "auto o1 = bp[opx.opOp1];\n"~
1052 ack~
1053 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1054 "bp[dest] = lrint(o0)"~op~"lrint(o1);\n"~
1055 "break;";
1057 enum BinCmpMixin(string op) =
1058 "auto dest = opx.opDest;\n"~
1059 "auto o0 = bp[opx.opOp0];\n"~
1060 "auto o1 = bp[opx.opOp1];\n"~
1061 "assert(!o0.isUndef && !o1.isUndef);\n"~
1062 "if (o0.isString) {\n"~
1063 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1064 " string s0 = spool[o0.getStrId].val;\n"~
1065 " string s1 = spool[o1.getStrId].val;\n"~
1066 " bp[dest] = (s0 "~op~" s1 ? 1 : 0);\n"~
1067 "} else {\n"~
1068 " assert(o0.isReal);\n"~
1069 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1070 " bp[dest] = (o0 "~op~" o1 ? 1 : 0);\n"~
1071 "}\n"~
1072 "break;";
1074 enum BinLogMixin(string op) =
1075 "auto dest = opx.opDest;\n"~
1076 "auto o0 = bp[opx.opOp0];\n"~
1077 "auto o1 = bp[opx.opOp1];\n"~
1078 "assert(!o0.isUndef && !o1.isUndef);\n"~
1079 "if (o0.isString) {\n"~
1080 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1081 " string s0 = spool[o0.getStrId].val;\n"~
1082 " string s1 = spool[o1.getStrId].val;\n"~
1083 " bp[dest] = (s0.length "~op~" s1.length ? 1 : 0);\n"~
1084 "} else {\n"~
1085 " assert(o0.isReal);\n"~
1086 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
1087 " bp[dest] = (lrint(o0) "~op~" lrint(o1) ? 1 : 0);\n"~
1088 "}\n"~
1089 "break;";
1091 static if (is(Real == float)) {
1092 import core.stdc.math : lrint = lrintf;
1093 } else static if (is(Real == double)) {
1094 import core.stdc.math : lrint;
1095 } else {
1096 static assert(0, "wtf?!");
1098 assert(curframe !is null);
1099 assert(pc > 0 && pc < code.length);
1100 assert(code[pc].opCode == Op.enter);
1101 assert(stack.length > 0);
1102 auto bp = &stack[curframe.bp];
1103 auto origcf = curframe;
1104 auto cptr = code.ptr+pc;
1105 //if (stack.length < 65536) stack.length = 65536;
1106 debug(vm_exec) uint maxslots = Slot.max+1;
1107 for (;;) {
1108 debug(vm_exec) {
1109 import std.stdio : stderr;
1110 foreach (immutable idx; 0..maxslots) stderr.writeln(" ", idx, ": ", bp[idx]);
1111 dumpInstr(stderr, cast(uint)(cptr-code.ptr));
1113 auto opx = *cptr++;
1114 switch (opx.opCode) {
1115 case Op.nop:
1116 break;
1118 case Op.copy: // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
1119 import core.stdc.string : memmove;
1120 auto dest = opx.opDest;
1121 auto first = opx.opOp0;
1122 auto count = opx.opOp1;
1123 if (count) memmove(bp+dest, bp+first, count*Real.sizeof);
1124 break;
1126 case Op.lnot: // lognot
1127 auto dest = opx.opDest;
1128 auto o0 = bp[opx.opOp0];
1129 assert(!o0.isUndef);
1130 if (o0.isString) {
1131 auto s0 = spool[o0.getStrId].val;
1132 bp[dest] = (s0.length ? 0 : 1);
1133 } else {
1134 bp[dest] = (lrint(o0) ? 0 : 1);
1136 break;
1137 case Op.neg:
1138 auto dest = opx.opDest;
1139 auto o0 = bp[opx.opOp0];
1140 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1141 bp[dest] = -o0;
1142 break;
1143 case Op.bneg:
1144 auto dest = opx.opDest;
1145 auto o0 = bp[opx.opOp0];
1146 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1147 bp[dest] = cast(int)(~(cast(int)lrint(o0)));
1148 break;
1150 case Op.add:
1151 auto dest = opx.opDest;
1152 auto o0 = bp[opx.opOp0];
1153 auto o1 = bp[opx.opOp1];
1154 assert(!o0.isUndef && !o1.isUndef);
1155 if (o0.isString) {
1156 if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1157 string s0 = spool[o0.getStrId].val;
1158 string s1 = spool[o1.getStrId].val;
1159 //FIXME
1160 if (s0.length == 0) {
1161 bp[dest] = o1;
1162 } else if (s1.length == 0) {
1163 bp[dest] = o0;
1164 } else {
1165 bp[dest] = buildStrId(newDynStr(s0~s1));
1167 } else {
1168 assert(o0.isReal);
1169 if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
1170 bp[dest] = o0+o1;
1172 break;
1173 case Op.sub: mixin(BinOpMixin!"-");
1174 case Op.mul: mixin(BinOpMixin!"*");
1175 case Op.mod: mixin(BinOpMixin!("%", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1176 case Op.div: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1177 case Op.rdiv: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
1178 case Op.bor: mixin(BinIOpMixin!"|");
1179 case Op.bxor: mixin(BinIOpMixin!"^");
1180 case Op.band: mixin(BinIOpMixin!"&");
1181 case Op.shl: mixin(BinIOpMixin!"<<");
1182 case Op.shr: mixin(BinIOpMixin!">>");
1184 case Op.lt: mixin(BinCmpMixin!"<");
1185 case Op.le: mixin(BinCmpMixin!"<=");
1186 case Op.gt: mixin(BinCmpMixin!">");
1187 case Op.ge: mixin(BinCmpMixin!">=");
1188 case Op.eq: mixin(BinCmpMixin!"==");
1189 case Op.ne: mixin(BinCmpMixin!"!=");
1191 case Op.lor: mixin(BinLogMixin!"||");
1192 case Op.land: mixin(BinLogMixin!"&&");
1193 case Op.lxor: assert(0);
1195 case Op.plit: // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
1196 auto dest = opx.opDest;
1197 uint idx = cast(ushort)opx.op2Byte;
1198 if (idx == ushort.max) {
1199 assert((*cptr).opCode == Op.skip);
1200 idx = (*cptr++).op3Byte;
1202 bp[dest] = vpool.ptr[idx];
1203 break;
1204 case Op.ilit: // dest becomes ilit val (val: short) -- load small integer literal
1205 auto dest = opx.opDest;
1206 bp[dest] = opx.opILit;
1207 break;
1208 case Op.xlit: // dest becomes integer(!) val (val: short) -- load small integer literal
1209 auto dest = opx.opDest;
1210 *cast(uint*)(bp+dest) = opx.opILit;
1211 break;
1213 case Op.jump: // addr: 3 bytes
1214 cptr = code.ptr+opx.op3Byte;
1215 break;
1216 case Op.xtrue: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
1217 if (lrint(bp[opx.opDest]) != 0) ++cptr;
1218 break;
1219 case Op.xfalse: // dest is reg to check; skip next instruction if dest is "gml false" (i.e. fabs(v) >= 0.5`)
1220 if (lrint(bp[opx.opDest]) == 0) ++cptr;
1221 break;
1223 case Op.call: // dest is result; op0: call frame (see below); op1: number of args
1224 // call frame is:
1225 // new function frame
1226 // int scriptid (after op1+3 slots)
1227 // note that there should be no used registers after those (as that will be used as new function frame regs)
1228 auto sid = *cast(uint*)(bp+opx.opOp0+Slot.Argument0+opx.opOp1);
1229 if (sid >= scriptPCs.length) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid script id");
1230 pc = scriptPCs.ptr[sid];
1231 if (pc < 1 || pc >= code.length) {
1232 if (pc&0x8000_0000) {
1233 // this is primitive
1234 uint pid = -cast(int)pc;
1235 if (pid >= prims.length) assert(0, "wtf?!");
1236 bp[opx.opDest] = prims.ptr[pid](cast(uint)(cptr-code.ptr-1), bp+opx.opOp0, opx.opOp1);
1237 break;
1238 } else {
1239 string scname;
1240 foreach (auto kv; scripts.byKeyValue) if (kv.value == sid) { scname = kv.key; break; }
1241 runtimeError(cast(uint)(cptr-code.ptr-1), "trying to execute undefined script '", scname, "'");
1244 debug(vm_exec) {
1245 import std.stdio : stderr;
1246 stderr.writeln("calling '", scriptNum2Name[sid], "'");
1247 foreach (immutable aidx; 0..opx.opOp1) stderr.writeln(" ", bp[opx.opOp0+Slot.Argument0+aidx]);
1249 // if this is tail call, just do it as tail call then
1250 // but don't optimize out top-level call, heh
1251 if (curframe !is origcf && (*cptr).opCode == Op.ret) {
1252 import core.stdc.string : memcpy;
1253 // yay, it is a tail call!
1254 // copy arguments (it's safe to use `memcpy()` here); `self` and `other` are automatically ok
1255 if (opx.opOp1) memcpy(bp+Slot.Argument0, bp+opx.opOp0+Slot.Argument0, Real.sizeof*opx.opOp1);
1256 // simply replace current frame with new one
1257 } else {
1258 bp[opx.opOp0..opx.opOp0+Slot.Argument0] = bp[0..Slot.Argument0]; // copy `self` and `other`
1259 curframe.pc = cast(uint)(cptr-code.ptr);
1260 curframe.rval = opx.opDest;
1261 ++curframe;
1262 curframe.bp = curframe[-1].bp+opx.opOp0;
1263 bp = &stack[curframe.bp];
1265 curframe.script = sid;
1266 cptr = code.ptr+scriptPCs.ptr[sid];
1267 //assert((*cptr).opCode == Op.enter);
1268 // clear unused arguments
1269 if (opx.opOp1 < 16) bp[Slot.Argument0+opx.opOp1..Slot.Argument15+1] = 0;
1270 break;
1272 case Op.enter: // op0: number of stack slots used (including result and args); op1: number of locals
1273 if (curframe.bp+opx.opOp0 > stack.length) {
1274 stack.length = curframe.bp+opx.opOp0;
1275 bp = &stack[curframe.bp];
1277 //foreach (immutable idx; Slot.max+1..Slot.max+1+opx.opOp1) bp[idx] = 0; // clear locals
1278 if (opx.opOp1) bp[Slot.max+1..Slot.max+1+opx.opOp1] = 0; // clear locals
1279 debug(vm_exec) maxslots = opx.opOp0;
1280 debug(vm_exec) { import std.stdio : stderr; foreach (immutable idx; Slot.Argument0..Slot.Argument15+1) stderr.writeln(" :", bp[idx]); }
1281 break;
1283 case Op.ret: // dest is retvalue; it is copied to reg0; other stack items are discarded
1284 if (curframe is origcf) return bp[opx.opDest]; // done
1285 assert(cast(uint)curframe > cast(uint)origcf);
1286 --curframe;
1287 auto rv = bp[opx.opDest];
1288 // remove stack frame
1289 bp = &stack[curframe.bp];
1290 cptr = code.ptr+curframe.pc;
1291 bp[curframe.rval] = rv;
1292 debug(vm_exec) { import std.stdio : stderr; stderr.writeln("RET(", curframe.rval, "): ", rv); }
1293 break;
1295 //as we are using refloads only in the last stage of assignment, they can create values
1296 case Op.lref: // load slot reference to dest
1297 *cast(int*)bp[opx.opDest] = opx.opOp0;
1298 break;
1299 //case Op.oref: // load object reference to dest; op0: int reg (obj id; -666: global object)
1300 //case Op.fref: // load field reference; op0: varref; op1: int reg (field id); can't create fields
1301 //case Op.fcrf: // load field reference; op0: varref; op1: int reg (field id); can create field
1302 //case Op.iref: // load indexed reference; op0: varref; op1: int reg (index)
1303 //case Op.mref: // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
1305 //case Op.rload: // load from op0-varref to dest
1306 case Op.rstore: // store to op0-varref from op1
1307 auto x = *cast(int*)bp[opx.opOp0];
1308 assert(x >= 0 && x <= 255);
1309 bp[x] = bp[opx.opOp1];
1310 break;
1312 //case Op.oload: // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
1313 //case Op.iload: // load indexed (as iref)
1314 //case Op.mload: // load indexed (as mref)
1315 default: assert(0);
1320 private:
1321 // create primitive delegate for D delegate/function
1322 // D function can include special args like:
1323 // Real* -- bp
1324 // VM -- vm instance (should be at the end)
1325 // Real -- unmodified argument value
1326 // one or two args after VM: `self` and `other`
1327 // string, integer, float
1328 // no ref args are supported, sorry
1329 private PrimDg register(DG) (DG dg) @trusted if (isCallable!DG) {
1330 import core.stdc.math : lrint;
1331 assert(dg !is null);
1332 // build call thunk
1333 return delegate (uint pc, Real* bp, ubyte argc) {
1334 // prepare arguments
1335 Parameters!DG arguments;
1336 alias rt = ReturnType!dg;
1337 // (VM self, Real* bp, ubyte argc)
1338 static if (arguments.length == 3 &&
1339 is(typeof(arguments[0]) : VM) &&
1340 is(typeof(arguments[1]) == Real*) &&
1341 is(typeof(arguments[2]) : int))
1343 static if (is(rt == void)) {
1344 cast(void)dg(this, bp, cast(typeof(arguments[2]))argc);
1345 return cast(Real)0;
1346 } else {
1347 return Value(this, dg(this, bp, cast(typeof(arguments[2]))argc));
1349 } else {
1350 foreach (immutable idx, ref arg; arguments) {
1351 // is last argument suitable for `withobj`?
1352 static if (is(typeof(arg) : VM)) {
1353 arg = this;
1354 static if (idx+1 < arguments.length) {
1355 static assert(is(typeof(arguments[idx+1]) == Real), "invalid 'self' argument type");
1356 arguments[idx+1] = bp[Slot.Self];
1357 static if (idx+2 < arguments.length) {
1358 static assert(is(typeof(arguments[idx+2]) == Real), "invalid 'other' argument type");
1359 arguments[idx+2] = bp[Slot.Other];
1360 static assert(idx+3 == arguments.length, "too many extra arguments");
1363 } else {
1364 static assert(idx < 16, "too many arguments required");
1365 static if (is(typeof(arg) == const(char)[]) || is(typeof(arg) == string)) {
1366 auto v = bp[Slot.Argument0+idx];
1367 if (!v.isString) runtimeError(pc, "invalid argument type");
1368 arg = getDynStr(v.getStrId);
1369 } else static if (is(typeof(arg) == bool)) {
1370 auto v = bp[Slot.Argument0+idx];
1371 if (v.isString) arg = (v.getStrId != 0);
1372 else if (v.isReal) arg = (lrint(v) != 0);
1373 else runtimeError(pc, "invalid argument type");
1374 } else static if (is(typeof(arg) : long) || is(typeof(arg) : double)) {
1375 auto v = bp[Slot.Argument0+idx];
1376 if (!v.isReal) runtimeError(pc, "invalid D argument type");
1377 arg = cast(typeof(arg))v;
1381 static if (is(rt == void)) {
1382 cast(void)dg(arguments);
1383 return cast(Real)0;
1384 } else {
1385 return Value(this, dg(arguments));
1391 static:
1392 enum OpArgs {
1393 None,
1394 Dest,
1395 DestOp0,
1396 DestOp0Op1,
1397 Dest2Bytes,
1398 Dest3Bytes,
1399 DestInt,
1400 DestJump,
1401 DestCall,
1402 Op0Op1,
1404 immutable OpArgs[ubyte] opargs;
1405 shared static this () {
1406 with(OpArgs) opargs = [
1407 Op.nop: None,
1408 Op.skip: None,
1409 Op.copy: DestOp0Op1,
1410 Op.lnot: DestOp0, //: lognot
1411 Op.neg: DestOp0,
1412 Op.bneg: DestOp0,
1414 Op.add: DestOp0Op1,
1415 Op.sub: DestOp0Op1,
1416 Op.mul: DestOp0Op1,
1417 Op.mod: DestOp0Op1,
1418 Op.div: DestOp0Op1,
1419 Op.rdiv: DestOp0Op1,
1420 Op.bor: DestOp0Op1,
1421 Op.bxor: DestOp0Op1,
1422 Op.band: DestOp0Op1,
1423 Op.shl: DestOp0Op1,
1424 Op.shr: DestOp0Op1,
1425 Op.lt: DestOp0Op1,
1426 Op.le: DestOp0Op1,
1427 Op.gt: DestOp0Op1,
1428 Op.ge: DestOp0Op1,
1429 Op.eq: DestOp0Op1,
1430 Op.ne: DestOp0Op1,
1431 Op.lor: DestOp0Op1,
1432 Op.land: DestOp0Op1,
1433 Op.lxor: DestOp0Op1,
1435 Op.plit: Dest2Bytes,
1436 Op.ilit: DestInt,
1437 Op.xlit: DestInt,
1439 Op.jump: DestJump,
1440 Op.xtrue: Dest,
1441 Op.xfalse: Dest,
1443 Op.call: DestCall,
1445 Op.enter: DestOp0Op1,
1447 Op.ret: Dest,
1449 Op.lref: DestOp0,
1450 Op.oref: DestOp0,
1451 Op.fref: DestOp0Op1,
1452 Op.fcrf: DestOp0Op1,
1453 Op.iref: DestOp0Op1,
1454 Op.mref: DestOp0Op1,
1456 Op.rload: DestOp0,
1457 Op.rstore: DestOp0,
1459 Op.oload: DestOp0Op1,
1460 Op.iload: DestOp0Op1,
1461 Op.mload: DestOp0Op1,
1464 Op.siter: DestOp0,
1465 Op.niter: DestJump,
1466 Op.kiter: Dest,
1468 Op.lirint: DestOp0, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
1474 // ////////////////////////////////////////////////////////////////////////// //
1475 private:
1476 ubyte opCode (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op&0xff); }
1477 ubyte opDest (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>8)&0xff); }
1478 ubyte opOp0 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>16)&0xff); }
1479 ubyte opOp1 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>24)&0xff); }
1480 short opILit (uint op) pure nothrow @safe @nogc { pragma(inline, true); return cast(short)((op>>16)&0xffff); }
1481 uint op3Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>8); }
1482 uint op2Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>16); }
1484 uint opMakeILit (ubyte op, byte dest, short val) pure nothrow @safe @nogc { pragma(inline, true); return ((val<<16)|((dest&0xff)<<8)|op); }
1485 uint opMake3Byte (ubyte op, uint val) pure nothrow @safe @nogc { pragma(inline, true); assert(val <= 0xffffff); return (val<<8)|op; }