one small optimization worth alot!
[gaemu.git] / gmlvm.d
blob68281a6d305d843ce3f37a64cc5b53e3c73ff2e4
1 module gmlvm is aliced;
3 import gmlparser;
4 import std.stdio : File;
7 // ////////////////////////////////////////////////////////////////////////// //
8 alias Real = float;
11 // value manipulation
12 static bool isReal (Real v) {
13 import std.math;
14 return !isNaN(v);
17 static bool isString (Real v) {
18 import std.math;
19 return isNaN(v);
22 static bool isUndef (Real v) {
23 import std.math;
24 return (isNaN(v) && getNaNPayload(v) < 0);
27 // creates "undefined" value
28 static Real undefValue () {
29 import std.math;
30 return NaN(-666);
33 // for invalid strings it returns 0
34 static int getStrId (Real v) {
35 import std.math;
36 if (isNaN(v)) {
37 auto res = getNaNPayload(v);
38 static if (is(Real == float)) {
39 return (res < 0 ? 0 : cast(int)res);
40 } else {
41 return (res < 0 || res > int.max ? 0 : cast(int)res);
43 } else {
44 return 0;
48 Real buildStrId (int id) {
49 import std.math;
50 static if (is(Real == float)) {
51 assert(id >= 0 && id <= 0x3F_FFFF);
52 } else {
53 assert(id >= 0);
55 return NaN(id);
59 // ////////////////////////////////////////////////////////////////////////// //
60 enum Op {
61 nop,
63 copy, // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
65 lnot, //: lognot
66 neg,
67 bneg,
69 add,
70 sub,
71 mul,
72 mod,
73 div,
74 rdiv,
75 bor,
76 bxor,
77 band,
78 shl,
79 shr,
80 lt,
81 le,
82 gt,
83 ge,
84 eq,
85 ne,
86 lor,
87 land,
88 lxor,
90 plit, // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
91 ilit, // dest becomes ilit val (val: short) -- load small integer literal
92 xlit, // dest becomes integer(!) val (val: short) -- load small integer literal
94 jump, // addr: 3 bytes
95 xtrue, // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
96 xfalse, // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
98 call, // dest is result; op0: call frame (see below); op1: number of args
99 // call frame is:
100 // new function frame
101 // int scriptid (after op1+3 slots)
102 // note that there should be no used registers after those (as that will be used as new function frame regs)
104 //tcall, // same as call, but does tail call
106 prim, // call "primitive" (built-in function); dest is result; op0: call frame (see below); op1: number of args
107 // call frame is:
108 // new function frame (starting with return value)
109 // int primid (after op1+3 slots)
110 // note that there should be no used registers after those (as that will be used as new function frame regs)
112 //tprim, // same as prim, but does tail call
114 enter, // op0: number of stack slots used (including result and args); op1: number of locals
115 // any function will ALWAYS starts with this
117 ret, // dest is retvalue; it is copied to reg0; other stack items are discarded
119 //as we are using refloads only in the last stage of assignment, they can create values
120 lref, // load slot reference to dest
121 oref, // load object reference to dest; op0: int reg (obj id; -666: global object)
122 fref, // load field reference; op0: varref; op1: int reg (field id); can't create fields
123 fcrf, // load field reference; op0: varref; op1: int reg (field id); can create field
124 iref, // load indexed reference; op0: varref; op1: int reg (index)
125 mref, // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
127 rload, // load from op0-varref to dest
128 rstore, // store to op0-varref from op1
130 oload, // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
131 iload, // load indexed (as iref)
132 mload, // load indexed (as mref)
135 //`with` is done by copying `self` to another reg, execute the code and restore `self`
137 siter, // start instance iterator; dest: iterid; op0: objid or instid
138 // this is special: it will skip next instruction if iteration has at least one item
139 // next instruction is always jump, which skips the loop
140 niter, // dest is iterreg; do jump (pc is the same as in jump) if iteration is NOT complete
141 kiter, // kill iterator, should be called to prevent memory leaks
143 // so return from `with` should call kiter for all created iterators first
145 // possible iterator management: preallocate slots for each non-overlapped "with";
146 // let VM to free all iterators from those slots on function exit
148 lirint, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
152 // ////////////////////////////////////////////////////////////////////////// //
153 final class VM {
154 public:
156 private:
157 uint[] code; // [0] is reserved
158 uint[string] scripts; // name -> number
159 uint[] scriptPCs; // by number; 0 is reserved
160 // fixuper will not remove fixup chains, so we can replace script with new one
161 Real[] vpool; // pool of values
162 string[] spool; // pool of strings
163 Real[] globals;
164 uint[string] fields; // known fields and their offsets in object (and in globals too)
166 public:
167 public:
168 this () {
169 code.length = 1;
170 scriptPCs.length = 1;
173 void compile (NodeFunc fn) {
174 import std.stdio : stdout;
175 auto spc = code.length;
176 doCompileFunc(fn);
177 while (spc < code.length) spc += dumpInstr(stdout, spc);
180 bool isJump (uint pc) {
181 if (pc < 1 || pc >= code.length) return false;
182 switch (code[pc].opCode) {
183 case Op.jump:
184 return true;
185 default: break;
187 return false;
190 // returns instruction size
191 uint dumpInstr (File fo, uint pc) {
192 fo.writef("%08X: ", pc);
193 if (pc == 0 || pc >= code.length) {
194 fo.writeln("<INVALID>");
195 return 1;
197 auto atp = opargs[code[pc].opCode];
198 if (atp == OpArgs.None) {
199 fo.writefln("%s", cast(Op)code[pc].opCode);
200 return 1;
202 fo.writef("%-8s", cast(Op)code[pc].opCode);
203 switch (atp) with (OpArgs) {
204 case Dest: fo.writefln("dest:%s", code[pc].opDest); break;
205 case DestOp0: fo.writefln("dest:%s, op0:%s", code[pc].opDest, code[pc].opOp0); break;
206 case DestOp0Op1: fo.writefln("dest:%s, op0:%s, op1:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
207 case Dest2Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op2Byte); break;
208 case Dest3Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op3Byte); break;
209 case DestInt: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].opILit); break;
210 case DestJump: fo.writefln("0x%08x", code[pc].op3Byte); break;
211 case DestCall: fo.writefln("dest:%s; frame:%s; args:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
212 case Op0Op1: fo.writefln("op0:%s, op1:%s", code[pc].opOp0, code[pc].opOp1); break;
213 default: assert(0);
215 return 1;
218 private:
219 enum Slot {
220 Self,
221 Other,
222 Argument0,
223 Argument1,
224 Argument2,
225 Argument3,
226 Argument4,
227 Argument5,
228 Argument6,
229 Argument7,
230 Argument8,
231 Argument9,
232 Argument10,
233 Argument11,
234 Argument12,
235 Argument13,
236 Argument14,
237 Argument15,
241 void doCompileFunc (NodeFunc fn) {
243 uint pc () { return cast(uint)code.length; }
245 uint emit (Op op, ubyte dest=0, ubyte op0=0, ubyte op1=0) {
246 auto res = cast(uint)code.length;
247 code ~= (op1<<24)|(op0<<16)|(dest<<8)|cast(ubyte)op;
248 return res;
251 uint emit3Bytes (Op op, uint val) {
252 assert(val <= 0xffffff);
253 auto res = cast(uint)code.length;
254 code ~= (val<<8)|cast(ubyte)op;
255 return res;
258 uint emit2Bytes (Op op, ubyte dest, short val) {
259 auto res = cast(uint)code.length;
260 code ~= (val<<16)|(dest<<8)|cast(ubyte)op;
261 return res;
264 uint emitJumpTo (Op op, uint addr) {
265 assert(addr <= 0xffffff);
266 auto res = cast(uint)code.length;
267 code ~= cast(uint)op|(addr<<8);
268 return res;
271 // this starts "jump chain", return new chain id
272 uint emitJumpChain (uint chain, Op op) {
273 assert(chain <= 0xffffff);
274 auto res = cast(uint)code.length;
275 code ~= cast(uint)op|(chain<<8);
276 return res;
279 void fixJumpChain (uint chain, uint addr) {
280 assert(chain <= 0xffffff);
281 assert(addr <= 0xffffff);
282 while (chain) {
283 auto nc = op3Byte(code[chain]);
284 code[chain] = (code[chain]&0xff)|(addr<<8);
285 chain = nc;
289 assert(fn !is null);
290 assert(fn.ebody !is null);
291 assert(fn.name.length);
293 void compileError(A...) (Loc loc, A args) {
294 if (fn.pp !is null) {
295 fn.pp.error(loc, args);
296 } else {
297 import std.stdio : stderr;
298 stderr.writeln("ERROR at ", loc, ": ", args);
299 string msg;
300 foreach (immutable a; args) {
301 import std.string : format;
302 msg ~= "%s".format(a);
304 throw new ErrorAt(loc, msg);
308 bool[256] slots;
309 foreach (immutable idx; 0..Slot.max+1) slots[idx] = true; // used
310 uint firstFreeSlot = Slot.max+1;
311 uint maxUsedSlot = firstFreeSlot-1;
313 ubyte allocSlot (Loc loc, int ddest=-1) {
314 if (ddest >= 0) {
315 assert(ddest < slots.length);
316 return cast(ubyte)ddest;
318 foreach (immutable idx; firstFreeSlot..slots.length) {
319 if (!slots[idx]) {
320 if (idx > maxUsedSlot) maxUsedSlot = cast(uint)idx;
321 slots[idx] = true;
322 return cast(ubyte)idx;
325 compileError(loc, "out of free slots");
326 assert(0);
329 ubyte reserveCallSlots (Loc loc, uint resnum) {
330 foreach_reverse (immutable idx, bool v; slots) {
331 if (v) {
332 if (idx+resnum+1 > slots.length) compileError(loc, "out of free slots");
333 return cast(ubyte)(idx+1);
336 compileError(loc, "out of free slots");
337 assert(0);
340 void freeSlot (ubyte num) {
341 if (num >= firstFreeSlot) {
342 assert(slots[num]);
343 slots[num] = false;
347 ubyte[string] locals;
348 uint[string] globals;
349 Loc[string] vdecls; // for error messages
351 // collect var declarations (gml is not properly scoped)
352 visitNodes(fn.ebody, (Node n) {
353 if (auto vd = cast(NodeVarDecl)n) {
354 foreach (immutable idx, string name; vd.names) {
355 if (name in locals) {
356 if (vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
357 } else if (name in globals) {
358 if (!vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
360 vdecls[name] = vd.locs[idx];
361 if (vd.asGlobal) {
362 globals[name] = 0;
363 } else {
364 firstFreeSlot = allocSlot(vd.locs[idx]);
365 locals[name] = cast(ubyte)firstFreeSlot;
366 ++firstFreeSlot;
370 return VisitRes.Continue;
373 ushort allocNumConst (Real v, Loc loc) {
374 //FIXME: speed it up!
375 foreach (immutable idx, Real vp; vpool) {
376 if (vp == v) return cast(ushort)idx;
378 auto vpi = cast(uint)vpool.length;
379 if (vpi > ushort.max) compileError(loc, "too many constants");
380 vpool ~= v;
381 return cast(ushort)vpi;
384 ushort allocStrConst (string s, Loc loc) {
385 //FIXME: speed it up!
386 foreach (immutable idx, string vp; spool) {
387 if (vp == s) return allocNumConst(buildStrId(cast(uint)idx), loc);
389 auto sidx = cast(uint)spool.length;
390 spool ~= s;
391 return allocNumConst(buildStrId(sidx), loc);
394 int varSlot (string name) {
395 switch (name) {
396 case "argument0": return Slot.Argument0+0;
397 case "argument1": return Slot.Argument0+1;
398 case "argument2": return Slot.Argument0+2;
399 case "argument3": return Slot.Argument0+3;
400 case "argument4": return Slot.Argument0+4;
401 case "argument5": return Slot.Argument0+5;
402 case "argument6": return Slot.Argument0+6;
403 case "argument7": return Slot.Argument0+7;
404 case "argument8": return Slot.Argument0+8;
405 case "argument9": return Slot.Argument0+9;
406 case "argument10": return Slot.Argument0+10;
407 case "argument11": return Slot.Argument0+11;
408 case "argument12": return Slot.Argument0+12;
409 case "argument13": return Slot.Argument0+13;
410 case "argument14": return Slot.Argument0+14;
411 case "argument15": return Slot.Argument0+15;
412 case "self": return Slot.Self;
413 case "other": return Slot.Other;
414 default:
416 if (auto v = name in locals) return *v;
417 return -1;
420 // returns dest slot
421 // can put value in desired dest
422 ubyte compileExpr (Node nn, int ddest=-1, bool wantref=false) {
423 ubyte doBinOp (Op op, NodeBinary n) {
424 auto dest = allocSlot(n.loc, ddest);
425 auto o0 = compileExpr(n.el);
426 auto o1 = compileExpr(n.er);
427 emit(op, dest, o0, o1);
428 freeSlot(o0);
429 freeSlot(o1);
430 return dest;
433 ubyte doUnOp (Op op, NodeUnary n) {
434 auto dest = allocSlot(n.loc, ddest);
435 auto o0 = compileExpr(n.e);
436 emit(op, dest, o0);
437 freeSlot(o0);
438 return dest;
441 return selectNode!ubyte(nn,
442 (NodeLiteralNum n) {
443 import core.stdc.math : lrint;
444 auto dest = allocSlot(n.loc, ddest);
445 if (lrint(n.val) == n.val && lrint(n.val) >= short.min && lrint(n.val) <= short.max) {
446 emit2Bytes(Op.ilit, dest, cast(short)lrint(n.val));
447 } else {
448 emit2Bytes(Op.plit, dest, allocNumConst(n.val, n.loc));
450 return dest;
452 (NodeLiteralStr n) {
453 auto dest = allocSlot(n.loc, ddest);
454 emit2Bytes(Op.plit, dest, allocStrConst(n.val, n.loc));
455 return dest;
457 (NodeUnaryParens n) => compileExpr(n.e, ddest, wantref),
458 (NodeUnaryNot n) => doUnOp(Op.lnot, n),
459 (NodeUnaryNeg n) => doUnOp(Op.neg, n),
460 (NodeUnaryBitNeg n) => doUnOp(Op.bneg, n),
461 (NodeBinaryAss n) {
462 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");
463 if (auto did = cast(NodeId)n.el) {
464 auto vdst = varSlot(did.name);
465 assert(vdst >= 0);
466 auto dest = compileExpr(n.er, ddest:vdst);
467 freeSlot(dest);
468 } else {
469 auto src = compileExpr(n.er);
470 auto dest = compileExpr(n.el, wantref:true);
471 emit(Op.rstore, dest, src);
472 freeSlot(src);
473 freeSlot(dest);
475 return 0;
477 (NodeBinaryAdd n) => doBinOp(Op.add, n),
478 (NodeBinarySub n) => doBinOp(Op.sub, n),
479 (NodeBinaryMul n) => doBinOp(Op.mul, n),
480 (NodeBinaryRDiv n) => doBinOp(Op.rdiv, n),
481 (NodeBinaryDiv n) => doBinOp(Op.div, n),
482 (NodeBinaryMod n) => doBinOp(Op.mod, n),
483 (NodeBinaryBitOr n) => doBinOp(Op.bor, n),
484 (NodeBinaryBitAnd n) => doBinOp(Op.band, n),
485 (NodeBinaryBitXor n) => doBinOp(Op.bxor, n),
486 (NodeBinaryLShift n) => doBinOp(Op.shl, n),
487 (NodeBinaryRShift n) => doBinOp(Op.shr, n),
488 (NodeBinaryLess n) => doBinOp(Op.lt, n),
489 (NodeBinaryLessEqu n) => doBinOp(Op.le, n),
490 (NodeBinaryGreat n) => doBinOp(Op.gt, n),
491 (NodeBinaryGreatEqu n) => doBinOp(Op.ge, n),
492 (NodeBinaryEqu n) => doBinOp(Op.eq, n),
493 (NodeBinaryNotEqu n) => doBinOp(Op.ne, n),
494 (NodeBinaryLogOr n) => doBinOp(Op.lor, n),
495 (NodeBinaryLogAnd n) => doBinOp(Op.land, n),
496 (NodeBinaryLogXor n) => doBinOp(Op.lxor, n),
497 (NodeFCall n) {
498 auto dest = allocSlot(n.loc, ddest);
499 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
500 ubyte[16] slt;
501 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
502 foreach (immutable idx, Node a; n.args) slt[idx] = compileExpr(a);
503 auto fcs = reserveCallSlots(n.loc, cast(uint)n.args.length+Slot.Argument0+1);
505 foreach (immutable idx; 0..n.args.length) {
506 emit(Op.copy, cast(ubyte)(fcs+Slot.Argument0+idx), slt[idx], 1); //TODO: optimize
510 uint sidx = 0;
511 while (sidx < n.args.length) {
512 uint eidx = sidx+1;
513 while (eidx < n.args.length && slt[eidx] == slt[eidx-1]+1) ++eidx;
514 emit(Op.copy, cast(ubyte)(fcs+Slot.Argument0+sidx), slt[sidx], cast(ubyte)(eidx-sidx));
515 sidx = eidx;
518 foreach (immutable idx, Node a; n.args) freeSlot(slt[idx]);
519 // put script id
520 if (auto aptr = (cast(NodeId)n.fe).name in scripts) {
521 // known script
522 emit2Bytes(Op.xlit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)(*aptr));
523 } else {
524 auto snum = cast(uint)scriptPCs.length;
525 if (snum > 32767) compileError(n.loc, "too many scripts");
526 scriptPCs ~= 0;
527 scripts[(cast(NodeId)n.fe).name] = snum;
528 // unknown script
529 emit2Bytes(Op.xlit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)snum);
531 // emit call
532 emit(Op.call, dest, fcs, cast(ubyte)n.args.length);
533 return dest;
535 (NodeId n) {
536 if (wantref) {
537 auto vsl = varSlot(n.name);
538 assert(vsl >= 0);
539 auto dest = allocSlot(n.loc, ddest);
540 emit(Op.lref, dest, cast(ubyte)vsl);
541 return dest;
542 } else {
543 auto vsl = varSlot(n.name);
544 assert(vsl >= 0);
545 if (ddest < 0) return vsl; // just use this slot directly
546 auto dest = allocSlot(n.loc, ddest);
547 if (dest == vsl) return dest;
548 emit(Op.copy, dest, cast(ubyte)vsl, 1);
549 return dest;
551 assert(0);
552 //return 0;
554 (NodeDot n) {
555 assert(0);
557 (NodeIndex n) {
558 //if (auto r = visitNodes(n.ei0, dg)) return r;
559 //if (auto r = visitNodes(n.ei1, dg)) return r;
560 //return visitNodes(n.e, dg);
561 assert(0);
563 () { assert(0, "unimplemented node: "~typeid(nn).name); },
567 void compile (Node nn) {
568 assert(nn !is null);
569 return selectNode!void(nn,
570 (NodeVarDecl n) {},
571 (NodeBlock n) {
572 foreach (Node st; n.stats) compile(st);
574 (NodeStatementEmpty n) {},
575 (NodeStatementExpr n) {
576 freeSlot(compileExpr(n.e));
578 (NodeReturn n) {
579 if (n.e is null) {
580 emit2Bytes(Op.ilit, 0, 0);
581 emit(Op.ret, 0);
582 } else {
583 auto dest = compileExpr(n.e);
584 emit(Op.ret, dest);
585 freeSlot(dest);
588 (NodeWith n) {
589 assert(0);
591 (NodeIf n) {
592 auto cs = compileExpr(n.ec);
593 freeSlot(cs); // yep, free it here
594 emit(Op.xtrue, cs);
595 uint jfc = 0;
596 // simple optimization
597 jfc = emitJumpChain(0, Op.jump);
598 compile(n.et);
599 if (n.ef !is null) {
600 auto exc = emitJumpChain(0, Op.jump);
601 fixJumpChain(jfc, pc);
602 jfc = exc;
603 compile(n.ef);
605 fixJumpChain(jfc, pc);
607 (NodeStatementBreak n) {
608 assert(0);
610 (NodeStatementContinue n) {
611 assert(0);
613 (NodeFor n) {
615 if (auto r = visitNodes(n.einit, dg)) return r;
616 if (auto r = visitNodes(n.econd, dg)) return r;
617 if (auto r = visitNodes(n.enext, dg)) return r;
618 return visitNodes(n.ebody, dg);
620 assert(0);
622 (NodeWhile n) {
623 assert(0);
625 (NodeDoUntil n) {
626 assert(0);
628 (NodeRepeat n) {
629 assert(0);
631 (NodeSwitch n) {
633 if (auto r = visitNodes(n.e, dg)) return r;
634 foreach (ref ci; n.cases) {
635 if (auto r = visitNodes(ci.e, dg)) return r;
636 if (auto r = visitNodes(ci.st, dg)) return r;
638 return null;
640 assert(0);
642 () { assert(0, "unimplemented node: "~typeid(nn).name); },
646 auto startpc = emit(Op.enter);
647 compile(fn.ebody);
648 emit(Op.ret);
649 // patch enter
650 code[startpc] = (locals.length<<24)|((maxUsedSlot+1)<<16)|cast(ubyte)Op.enter;
651 if (auto sid = fn.name in scripts) {
652 scriptPCs[*sid] = startpc;
653 } else {
654 auto snum = cast(uint)scriptPCs.length;
655 if (snum > 32767) compileError(fn.loc, "too many scripts");
656 scriptPCs ~= startpc;
657 scripts[fn.name] = snum;
661 private:
662 static struct CallFrame {
663 uint script;
664 uint bp; // base pointer (address of the current frame in stack)
665 uint pc; // current pc; will be set on "call"
666 ubyte rval; // slot for return value; will be set on "call"
667 @disable this (this);
669 CallFrame[32768] frames;
670 CallFrame* curframe;
671 Real[] stack;
673 void runtimeError(A...) (uint pc, A args) {
674 import std.stdio : stderr;
675 stderr.writef("ERROR at %08X: ", pc);
676 stderr.writeln(args);
677 throw new Exception("fuuuuu");
680 public Real exec(A...) (string name, A args) {
681 static assert(A.length < 16, "too many arguments");
682 auto sid = scripts[name];
683 assert(curframe is null);
684 // create frame
685 if (stack.length < 65536) stack.length = 65536;
686 curframe = &frames[0];
687 curframe.bp = 0;
688 stack[0..Slot.max+1] = 0;
689 foreach (immutable idx, immutable a; args) {
690 static if (is(typeof(a) : const(char)[])) {
691 //FIXME
692 assert(0);
693 } else static if (is(typeof(a) : Real)) {
694 stack[Slot.Argument0+idx] = cast(Real)a;
695 } else {
696 static assert(0, "invalid argument type");
699 //{ import std.stdio; writeln(scriptPCs[sid]); }
700 return doExec(scriptPCs[sid]);
703 // current frame must be properly initialized
704 Real doExec (uint pc) {
705 enum BinOpMixin(string op, string ack="") =
706 "auto dest = opx.opDest;\n"~
707 "auto o0 = bp[opx.opOp0];\n"~
708 "auto o1 = bp[opx.opOp1];\n"~
709 ack~
710 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
711 "bp[dest] = o0"~op~"o1;\n"~
712 "break;";
713 enum BinIOpMixin(string op, string ack="") =
714 "auto dest = opx.opDest;\n"~
715 "auto o0 = bp[opx.opOp0];\n"~
716 "auto o1 = bp[opx.opOp1];\n"~
717 ack~
718 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
719 "bp[dest] = lrint(o0)"~op~"lrint(o1);\n"~
720 "break;";
722 enum BinCmpMixin(string op) =
723 "auto dest = opx.opDest;\n"~
724 "auto o0 = bp[opx.opOp0];\n"~
725 "auto o1 = bp[opx.opOp1];\n"~
726 "assert(!o0.isUndef && !o1.isUndef);\n"~
727 "if (o0.isString) {\n"~
728 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
729 " string s0 = spool[o0.getStrId];\n"~
730 " string s1 = spool[o1.getStrId];\n"~
731 " bp[dest] = (s0 "~op~" s1 ? 1 : 0);\n"~
732 "} else {\n"~
733 " assert(o0.isReal);\n"~
734 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
735 " bp[dest] = (o0 "~op~" o1 ? 1 : 0);\n"~
736 "}\n"~
737 "break;";
739 enum BinLogMixin(string op) =
740 "auto dest = opx.opDest;\n"~
741 "auto o0 = bp[opx.opOp0];\n"~
742 "auto o1 = bp[opx.opOp1];\n"~
743 "assert(!o0.isUndef && !o1.isUndef);\n"~
744 "if (o0.isString) {\n"~
745 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
746 " string s0 = spool[o0.getStrId];\n"~
747 " string s1 = spool[o1.getStrId];\n"~
748 " bp[dest] = (s0.length "~op~" s1.length ? 1 : 0);\n"~
749 "} else {\n"~
750 " assert(o0.isReal);\n"~
751 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
752 " bp[dest] = (lrint(o0) "~op~" lrint(o1) ? 1 : 0);\n"~
753 "}\n"~
754 "break;";
756 static if (is(Real == float)) {
757 import core.stdc.math : lrint = lrintf;
758 } else {
759 import core.stdc.math : lrint;
761 assert(curframe !is null);
762 assert(pc > 0 && pc < code.length);
763 assert(code[pc].opCode == Op.enter);
764 assert(stack.length > 0);
765 auto bp = &stack[curframe.bp];
766 auto origcf = curframe;
767 auto cptr = code.ptr+pc;
768 //if (stack.length < 65536) stack.length = 65536;
769 debug(vm_exec) uint maxslots = Slot.max+1;
770 for (;;) {
771 debug(vm_exec) {
772 import std.stdio : stderr;
773 foreach (immutable idx; 0..maxslots) stderr.writeln(" ", idx, ": ", bp[idx]);
774 dumpInstr(stderr, cast(uint)(cptr-code.ptr));
776 auto opx = *cptr++;
777 switch (opx.opCode) {
778 case Op.nop:
779 break;
781 case Op.copy: // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
782 import core.stdc.string : memmove;
783 auto dest = opx.opDest;
784 auto first = opx.opOp0;
785 auto count = opx.opOp1;
786 if (count) memmove(bp+dest, bp+first, count*Real.sizeof);
787 break;
789 case Op.lnot: // lognot
790 auto dest = opx.opDest;
791 auto o0 = bp[opx.opOp0];
792 assert(!o0.isUndef);
793 if (o0.isString) {
794 auto s0 = spool[o0.getStrId];
795 bp[dest] = (s0.length ? 0 : 1);
796 } else {
797 bp[dest] = (lrint(o0) ? 0 : 1);
799 break;
800 case Op.neg:
801 auto dest = opx.opDest;
802 auto o0 = bp[opx.opOp0];
803 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
804 bp[dest] = -o0;
805 break;
806 case Op.bneg:
807 auto dest = opx.opDest;
808 auto o0 = bp[opx.opOp0];
809 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
810 bp[dest] = cast(int)(~(cast(int)lrint(o0)));
811 break;
813 case Op.add:
814 auto dest = opx.opDest;
815 auto o0 = bp[opx.opOp0];
816 auto o1 = bp[opx.opOp1];
817 assert(!o0.isUndef && !o1.isUndef);
818 if (o0.isString) {
819 if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
820 string s0 = spool[o0.getStrId];
821 string s1 = spool[o1.getStrId];
822 //FIXME
823 if (s0.length == 0) {
824 bp[dest] = o1;
825 } else if (s1.length == 0) {
826 bp[dest] = o0;
827 } else {
828 auto sidx = cast(uint)spool.length;
829 spool ~= s0~s1;
830 bp[dest] = buildStrId(sidx);
832 } else {
833 assert(o0.isReal);
834 if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
835 bp[dest] = o0+o1;
837 break;
838 case Op.sub: mixin(BinOpMixin!"-");
839 case Op.mul: mixin(BinOpMixin!"*");
840 case Op.mod: mixin(BinOpMixin!("%", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
841 case Op.div: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
842 case Op.rdiv: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
843 case Op.bor: mixin(BinIOpMixin!"|");
844 case Op.bxor: mixin(BinIOpMixin!"^");
845 case Op.band: mixin(BinIOpMixin!"&");
846 case Op.shl: mixin(BinIOpMixin!"<<");
847 case Op.shr: mixin(BinIOpMixin!">>");
849 case Op.lt: mixin(BinCmpMixin!"<");
850 case Op.le: mixin(BinCmpMixin!"<=");
851 case Op.gt: mixin(BinCmpMixin!">");
852 case Op.ge: mixin(BinCmpMixin!">=");
853 case Op.eq: mixin(BinCmpMixin!"==");
854 case Op.ne: mixin(BinCmpMixin!"!=");
856 case Op.lor: mixin(BinLogMixin!"||");
857 case Op.land: mixin(BinLogMixin!"&&");
858 case Op.lxor: assert(0);
860 case Op.plit: // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
861 auto dest = opx.opDest;
862 bp[dest] = vpool[opx.op2Byte];
863 break;
864 case Op.ilit: // dest becomes ilit val (val: short) -- load small integer literal
865 auto dest = opx.opDest;
866 bp[dest] = opx.opILit;
867 break;
868 case Op.xlit: // dest becomes integer(!) val (val: short) -- load small integer literal
869 auto dest = opx.opDest;
870 *cast(uint*)(bp+dest) = opx.opILit;
871 break;
873 case Op.jump: // addr: 3 bytes
874 cptr = code.ptr+opx.op3Byte;
875 break;
876 case Op.xtrue: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
877 if (lrint(bp[opx.opDest]) != 0) ++cptr;
878 break;
879 case Op.xfalse: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
880 if (lrint(bp[opx.opDest]) == 0) ++cptr;
881 break;
883 case Op.call: // dest is result; op0: call frame (see below); op1: number of args
884 // call frame is:
885 // new function frame
886 // int scriptid (after op1+3 slots)
887 // note that there should be no used registers after those (as that will be used as new function frame regs)
888 auto sid = *cast(uint*)(bp+opx.opOp0+Slot.Argument0+opx.opOp1);
889 debug(vm_exec) {
890 import std.stdio : stderr;
891 foreach (auto kv; scripts.byKeyValue) {
892 if (kv.value == sid) {
893 stderr.writeln("calling '", kv.key, "'");
894 foreach (immutable aidx; 0..opx.opOp1) {
895 stderr.writeln(" ", bp[opx.opOp0+Slot.Argument0+aidx]);
900 bp[opx.opOp0+Slot.Argument0+opx.opOp1] = 0; // just in case
901 bp[opx.opOp0..opx.opOp0+Slot.Argument0] = bp[0..Slot.Argument0]; // copy `self` and `other`
902 curframe.pc = cast(uint)(cptr-code.ptr);
903 curframe.rval = opx.opDest;
904 ++curframe;
905 curframe.bp = curframe[-1].bp+opx.opOp0;
906 curframe.script = sid;
907 bp = &stack[curframe.bp];
908 cptr = code.ptr+scriptPCs[sid];
909 //assert((*cptr).opCode == Op.enter);
910 if (opx.opOp1 < 16) bp[Slot.Argument0+opx.opOp1..Slot.Argument15+1] = 0;
911 break;
913 //tcall, // same as call, but does tail call
915 //case Op.prim: // call "primitive" (built-in function); dest is result; op0: call frame (see below); op1: number of args
916 // call frame is:
917 // new function frame (starting with return value)
918 // int primid (after op1+3 slots)
919 // note that there should be no used registers after those (as that will be used as new function frame regs)
921 //tprim, // same as prim, but does tail call
923 case Op.enter: // op0: number of stack slots used (including result and args); op1: number of locals
924 if (curframe.bp+opx.opOp0 > stack.length) {
925 stack.length = curframe.bp+opx.opOp0;
926 bp = &stack[curframe.bp];
928 //foreach (immutable idx; Slot.max+1..Slot.max+1+opx.opOp1) bp[idx] = 0; // clear locals
929 if (opx.opOp1) bp[Slot.max+1..Slot.max+1+opx.opOp1] = 0; // clear locals
930 debug(vm_exec) maxslots = opx.opOp0;
931 debug(vm_exec) { import std.stdio : stderr; foreach (immutable idx; Slot.Argument0..Slot.Argument15+1) stderr.writeln(" :", bp[idx]); }
932 break;
934 case Op.ret: // dest is retvalue; it is copied to reg0; other stack items are discarded
935 if (curframe is origcf) return bp[opx.opDest]; // done
936 assert(cast(uint)curframe > cast(uint)origcf);
937 --curframe;
938 auto rv = bp[opx.opDest];
939 // remove stack frame
940 bp = &stack[curframe.bp];
941 cptr = code.ptr+curframe.pc;
942 bp[curframe.rval] = rv;
943 debug(vm_exec) { import std.stdio : stderr; stderr.writeln("RET(", curframe.rval, "): ", rv); }
944 break;
946 //as we are using refloads only in the last stage of assignment, they can create values
947 case Op.lref: // load slot reference to dest
948 *cast(int*)bp[opx.opDest] = opx.opOp0;
949 break;
950 //case Op.oref: // load object reference to dest; op0: int reg (obj id; -666: global object)
951 //case Op.fref: // load field reference; op0: varref; op1: int reg (field id); can't create fields
952 //case Op.fcrf: // load field reference; op0: varref; op1: int reg (field id); can create field
953 //case Op.iref: // load indexed reference; op0: varref; op1: int reg (index)
954 //case Op.mref: // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
956 //case Op.rload: // load from op0-varref to dest
957 case Op.rstore: // store to op0-varref from op1
958 auto x = *cast(int*)bp[opx.opOp0];
959 assert(x >= 0 && x <= 255);
960 bp[x] = bp[opx.opOp1];
961 break;
963 //case Op.oload: // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
964 //case Op.iload: // load indexed (as iref)
965 //case Op.mload: // load indexed (as mref)
966 default: assert(0);
973 static:
974 enum OpArgs {
975 None,
976 Dest,
977 DestOp0,
978 DestOp0Op1,
979 Dest2Bytes,
980 Dest3Bytes,
981 DestInt,
982 DestJump,
983 DestCall,
984 Op0Op1,
986 immutable OpArgs[ubyte] opargs;
987 shared static this () {
988 with(OpArgs) opargs = [
989 Op.nop: None,
990 Op.copy: DestOp0Op1,
991 Op.lnot: DestOp0, //: lognot
992 Op.neg: DestOp0,
993 Op.bneg: DestOp0,
995 Op.add: DestOp0Op1,
996 Op.sub: DestOp0Op1,
997 Op.mul: DestOp0Op1,
998 Op.mod: DestOp0Op1,
999 Op.div: DestOp0Op1,
1000 Op.rdiv: DestOp0Op1,
1001 Op.bor: DestOp0Op1,
1002 Op.bxor: DestOp0Op1,
1003 Op.band: DestOp0Op1,
1004 Op.shl: DestOp0Op1,
1005 Op.shr: DestOp0Op1,
1006 Op.lt: DestOp0Op1,
1007 Op.le: DestOp0Op1,
1008 Op.gt: DestOp0Op1,
1009 Op.ge: DestOp0Op1,
1010 Op.eq: DestOp0Op1,
1011 Op.ne: DestOp0Op1,
1012 Op.lor: DestOp0Op1,
1013 Op.land: DestOp0Op1,
1014 Op.lxor: DestOp0Op1,
1016 Op.plit: Dest2Bytes,
1017 Op.ilit: DestInt,
1018 Op.xlit: DestInt,
1020 Op.jump: DestJump,
1021 Op.xtrue: Dest,
1022 Op.xfalse: Dest,
1024 Op.call: DestCall,
1025 //Op.tcall: DestCall,
1027 Op.prim: DestCall,
1028 //Op.tprim: DestCall,
1030 Op.enter: Op0Op1,
1032 Op.ret: Dest,
1034 Op.lref: DestOp0,
1035 Op.oref: DestOp0,
1036 Op.fref: DestOp0Op1,
1037 Op.fcrf: DestOp0Op1,
1038 Op.iref: DestOp0Op1,
1039 Op.mref: DestOp0Op1,
1041 Op.rload: DestOp0,
1042 Op.rstore: DestOp0,
1044 Op.oload: DestOp0Op1,
1045 Op.iload: DestOp0Op1,
1046 Op.mload: DestOp0Op1,
1049 Op.siter: DestOp0,
1050 Op.niter: DestJump,
1051 Op.kiter: Dest,
1053 Op.lirint: DestOp0, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
1059 // ////////////////////////////////////////////////////////////////////////// //
1060 private:
1061 ubyte opCode (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op&0xff); }
1062 ubyte opDest (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>8)&0xff); }
1063 ubyte opOp0 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>16)&0xff); }
1064 ubyte opOp1 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>24)&0xff); }
1065 short opILit (uint op) pure nothrow @safe @nogc { pragma(inline, true); return cast(short)((op>>16)&0xffff); }
1066 uint op3Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>8); }
1067 uint op2Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>16); }
1069 uint opMakeILit (ubyte op, byte dest, short val) pure nothrow @safe @nogc { pragma(inline, true); return ((val<<16)|((dest&0xff)<<8)|op); }
1070 uint opMake3Byte (ubyte op, uint val) pure nothrow @safe @nogc { pragma(inline, true); assert(val <= 0xffffff); return (val<<8)|op; }