added TCO detection to vm; cut another 10 msecs from ackermann
[gaemu.git] / gmlvm.d
blobcaca9553c28c5d0faa3860af938977ba9988f805
1 module gmlvm is aliced;
3 import gmlparser;
4 import std.stdio : File;
7 // ////////////////////////////////////////////////////////////////////////// //
8 //alias Real = float;
9 alias Real = double;
12 // value manipulation
13 static bool isReal (Real v) {
14 import std.math;
15 return !isNaN(v);
18 static bool isString (Real v) {
19 import std.math;
20 return isNaN(v);
23 static bool isUndef (Real v) {
24 import std.math;
25 return (isNaN(v) && getNaNPayload(v) < 0);
28 // creates "undefined" value
29 static Real undefValue () {
30 import std.math;
31 return NaN(-666);
34 // for invalid strings it returns 0
35 static int getStrId (Real v) {
36 import std.math;
37 if (isNaN(v)) {
38 auto res = getNaNPayload(v);
39 static if (Real.sizeof == 4) {
40 return (res < 0 ? 0 : cast(int)res);
41 } else {
42 return (res < 0 || res > int.max ? 0 : cast(int)res);
44 } else {
45 return 0;
49 Real buildStrId (int id) {
50 import std.math;
51 static if (Real.sizeof == 4) {
52 assert(id >= 0 && id <= 0x3F_FFFF);
53 } else {
54 assert(id >= 0);
56 return NaN(id);
60 // ////////////////////////////////////////////////////////////////////////// //
61 enum Op {
62 nop,
63 skip, // skip current instruction; it usually has 3-byte payload
65 copy, // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
67 lnot, //: lognot
68 neg,
69 bneg,
71 add,
72 sub,
73 mul,
74 mod,
75 div,
76 rdiv,
77 bor,
78 bxor,
79 band,
80 shl,
81 shr,
82 lt,
83 le,
84 gt,
85 ge,
86 eq,
87 ne,
88 lor,
89 land,
90 lxor,
92 plit, // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot; if val is 0xffff, next instruction is skip
93 ilit, // dest becomes ilit val (val: short) -- load small integer literal
94 xlit, // dest becomes integer(!) val (val: short) -- load small integer literal
96 jump, // addr: 3 bytes
97 xtrue, // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
98 xfalse, // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
100 call, // dest is result; op0: call frame (see below); op1: number of args
101 // call frame is:
102 // new function frame
103 // int scriptid (after op1+3 slots)
104 // note that there should be no used registers after those (as that will be used as new function frame regs)
106 enter, // op0: number of stack slots used (including result and args); op1: number of locals
107 // any function will ALWAYS starts with this
109 ret, // dest is retvalue; it is copied to reg0; other stack items are discarded
111 //as we are using refloads only in the last stage of assignment, they can create values
112 lref, // load slot reference to dest
113 oref, // load object reference to dest; op0: int reg (obj id; -666: global object)
114 fref, // load field reference; op0: varref; op1: int reg (field id); can't create fields
115 fcrf, // load field reference; op0: varref; op1: int reg (field id); can create field
116 iref, // load indexed reference; op0: varref; op1: int reg (index)
117 mref, // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
119 rload, // load from op0-varref to dest
120 rstore, // store to op0-varref from op1
122 oload, // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
123 iload, // load indexed (as iref)
124 mload, // load indexed (as mref)
127 //`with` is done by copying `self` to another reg, execute the code and restore `self`
129 siter, // start instance iterator; dest: iterid; op0: objid or instid
130 // this is special: it will skip next instruction if iteration has at least one item
131 // next instruction is always jump, which skips the loop
132 niter, // dest is iterreg; do jump (pc is the same as in jump) if iteration is NOT complete
133 kiter, // kill iterator, should be called to prevent memory leaks
135 // so return from `with` should call kiter for all created iterators first
137 // possible iterator management: preallocate slots for each non-overlapped "with";
138 // let VM to free all iterators from those slots on function exit
140 lirint, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
144 // ////////////////////////////////////////////////////////////////////////// //
145 final class VM {
146 public:
148 private:
149 uint[] code; // [0] is reserved
150 uint[string] scripts; // name -> number
151 string[uint] scriptNum2Name;
152 uint[] scriptPCs; // by number; 0 is reserved
153 NodeFunc[] scriptASTs; // by number
154 // fixuper will not remove fixup chains, so we can replace script with new one
155 Real[] vpool; // pool of values
156 string[] spool; // pool of strings
157 Real[] globals;
158 uint[string] fields; // known fields and their offsets in object (and in globals too)
160 public:
161 public:
162 this () {
163 code.length = 1;
164 scriptPCs.length = 1;
165 scriptASTs.length = 1;
166 // preallocate small strings
167 spool ~= null;
168 foreach (ubyte c; 0..256) spool ~= ""~cast(char)c;
171 void compile (NodeFunc fn) {
172 import std.stdio : stdout;
173 auto spc = code.length;
174 doCompileFunc(fn);
175 while (spc < code.length) spc += dumpInstr(stdout, spc);
178 bool isJump (uint pc) {
179 if (pc < 1 || pc >= code.length) return false;
180 switch (code[pc].opCode) {
181 case Op.jump:
182 return true;
183 default: break;
185 return false;
188 // returns instruction size
189 uint dumpInstr (File fo, uint pc) {
190 fo.writef("%08X: ", pc);
191 if (pc == 0 || pc >= code.length) {
192 fo.writeln("<INVALID>");
193 return 1;
195 auto atp = opargs[code[pc].opCode];
196 if (atp == OpArgs.None) {
197 fo.writefln("%s", cast(Op)code[pc].opCode);
198 return 1;
200 fo.writef("%-8s", cast(Op)code[pc].opCode);
201 switch (atp) with (OpArgs) {
202 case Dest: fo.writefln("dest:%s", code[pc].opDest); break;
203 case DestOp0: fo.writefln("dest:%s, op0:%s", code[pc].opDest, code[pc].opOp0); break;
204 case DestOp0Op1: fo.writefln("dest:%s, op0:%s, op1:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
205 case Dest2Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op2Byte); break;
206 case Dest3Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op3Byte); break;
207 case DestInt: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].opILit); break;
208 case DestJump: fo.writefln("0x%08x", code[pc].op3Byte); break;
209 case DestCall: fo.writefln("dest:%s; frame:%s; args:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
210 case Op0Op1: fo.writefln("op0:%s, op1:%s", code[pc].opOp0, code[pc].opOp1); break;
211 default: assert(0);
213 return 1;
216 private:
217 enum Slot {
218 Self,
219 Other,
220 Argument0,
221 Argument1,
222 Argument2,
223 Argument3,
224 Argument4,
225 Argument5,
226 Argument6,
227 Argument7,
228 Argument8,
229 Argument9,
230 Argument10,
231 Argument11,
232 Argument12,
233 Argument13,
234 Argument14,
235 Argument15,
239 void doCompileFunc (NodeFunc fn) {
241 void compileError(A...) (Loc loc, A args) {
242 if (fn.pp !is null) {
243 fn.pp.error(loc, args);
244 } else {
245 import std.stdio : stderr;
246 stderr.writeln("ERROR at ", loc, ": ", args);
247 string msg;
248 foreach (immutable a; args) {
249 import std.string : format;
250 msg ~= "%s".format(a);
252 throw new ErrorAt(loc, msg);
256 uint sid4name (string name) {
257 if (auto sptr = name in scripts) {
258 return *sptr;
259 } else {
260 auto sid = cast(uint)scriptPCs.length;
261 if (sid > 32767) compileError(fn.loc, "too many scripts");
262 assert(scriptASTs.length == sid);
263 // reserve slots
264 scriptPCs ~= 0;
265 scriptASTs ~= null;
266 scriptNum2Name[sid] = name;
267 scripts[name] = sid;
268 return sid;
272 uint pc () { return cast(uint)code.length; }
274 uint emit (Op op, ubyte dest=0, ubyte op0=0, ubyte op1=0) {
275 auto res = cast(uint)code.length;
276 code ~= (op1<<24)|(op0<<16)|(dest<<8)|cast(ubyte)op;
277 return res;
280 uint emit3Bytes (Op op, uint val) {
281 assert(val <= 0xffffff);
282 auto res = cast(uint)code.length;
283 code ~= (val<<8)|cast(ubyte)op;
284 return res;
287 uint emit2Bytes (Op op, ubyte dest, short val) {
288 auto res = cast(uint)code.length;
289 code ~= (val<<16)|(dest<<8)|cast(ubyte)op;
290 return res;
293 uint emitJumpTo (Op op, uint addr) {
294 assert(addr <= 0xffffff);
295 auto res = cast(uint)code.length;
296 code ~= cast(uint)op|(addr<<8);
297 return res;
300 // this starts "jump chain", return new chain id
301 uint emitJumpChain (uint chain, Op op) {
302 assert(chain <= 0xffffff);
303 auto res = cast(uint)code.length;
304 code ~= cast(uint)op|(chain<<8);
305 return res;
308 void fixJumpChain (uint chain, uint addr) {
309 assert(chain <= 0xffffff);
310 assert(addr <= 0xffffff);
311 while (chain) {
312 auto nc = op3Byte(code[chain]);
313 code[chain] = (code[chain]&0xff)|(addr<<8);
314 chain = nc;
318 assert(fn !is null);
319 assert(fn.ebody !is null);
320 assert(fn.name.length);
322 bool[256] slots;
323 foreach (immutable idx; 0..Slot.max+1) slots[idx] = true; // used
324 uint firstFreeSlot = Slot.max+1;
325 uint maxUsedSlot = firstFreeSlot-1;
327 ubyte allocSlot (Loc loc, int ddest=-1) {
328 if (ddest >= 0) {
329 assert(ddest < slots.length);
330 return cast(ubyte)ddest;
332 foreach (immutable idx; firstFreeSlot..slots.length) {
333 if (!slots[idx]) {
334 if (idx > maxUsedSlot) maxUsedSlot = cast(uint)idx;
335 slots[idx] = true;
336 return cast(ubyte)idx;
339 compileError(loc, "out of free slots");
340 assert(0);
343 ubyte reserveCallSlots (Loc loc, uint resnum) {
344 foreach_reverse (immutable idx, bool v; slots) {
345 if (v) {
346 if (idx+resnum+1 > slots.length) compileError(loc, "out of free slots");
347 return cast(ubyte)(idx+1);
350 compileError(loc, "out of free slots");
351 assert(0);
354 void freeSlot (ubyte num) {
355 if (num >= firstFreeSlot) {
356 assert(slots[num]);
357 slots[num] = false;
361 ubyte[string] locals;
362 uint[string] globals;
363 Loc[string] vdecls; // for error messages
365 // collect var declarations (gml is not properly scoped)
366 visitNodes(fn.ebody, (Node n) {
367 if (auto vd = cast(NodeVarDecl)n) {
368 foreach (immutable idx, string name; vd.names) {
369 if (name in locals) {
370 if (vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
371 } else if (name in globals) {
372 if (!vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
374 vdecls[name] = vd.locs[idx];
375 if (vd.asGlobal) {
376 globals[name] = 0;
377 } else {
378 firstFreeSlot = allocSlot(vd.locs[idx]);
379 locals[name] = cast(ubyte)firstFreeSlot;
380 ++firstFreeSlot;
384 return VisitRes.Continue;
387 void emitPLit (Loc loc, ubyte dest, Real v) {
388 uint vpidx = uint.max;
389 if (isReal(v)) {
390 // number
391 import core.stdc.math : lrint;
392 if (lrint(v) == v && lrint(v) >= short.min && lrint(v) <= short.max) {
393 emit2Bytes(Op.ilit, dest, cast(short)lrint(v));
394 return;
396 //FIXME: speed it up!
397 foreach (immutable idx, Real vp; vpool) if (vp == v) { vpidx = cast(uint)idx; break; }
398 } else if (isString(v)) {
399 // string
400 //FIXME: speed it up!
401 auto sid = v.getStrId;
402 foreach (immutable idx, Real vp; vpool) if (vp.isString && vp.getStrId == sid) { vpidx = cast(uint)idx; break; }
403 } else {
404 assert(0, "wtf?!");
406 if (vpidx == uint.max) {
407 vpidx = cast(uint)vpool.length;
408 if (vpidx >= 0xffffff) compileError(loc, "too many constants");
409 vpool ~= v;
411 if (vpidx < ushort.max) {
412 emit2Bytes(Op.plit, dest, cast(ushort)vpidx);
413 } else {
414 // special form
415 emit2Bytes(Op.plit, dest, cast(short)ushort.max);
416 emit3Bytes(Op.skip, vpidx);
420 uint allocStrConst (string s, Loc loc) {
421 if (s.length == 0) return 0;
422 //FIXME: speed it up!
423 foreach (immutable idx, string vp; spool) {
424 if (vp == s) return cast(ushort)idx;
426 auto sidx = cast(uint)spool.length;
427 if (sidx >= 0xffffff) compileError(loc, "too many strings");
428 spool ~= s;
429 return sidx;
432 int varSlot (string name) {
433 switch (name) {
434 case "argument0": return Slot.Argument0+0;
435 case "argument1": return Slot.Argument0+1;
436 case "argument2": return Slot.Argument0+2;
437 case "argument3": return Slot.Argument0+3;
438 case "argument4": return Slot.Argument0+4;
439 case "argument5": return Slot.Argument0+5;
440 case "argument6": return Slot.Argument0+6;
441 case "argument7": return Slot.Argument0+7;
442 case "argument8": return Slot.Argument0+8;
443 case "argument9": return Slot.Argument0+9;
444 case "argument10": return Slot.Argument0+10;
445 case "argument11": return Slot.Argument0+11;
446 case "argument12": return Slot.Argument0+12;
447 case "argument13": return Slot.Argument0+13;
448 case "argument14": return Slot.Argument0+14;
449 case "argument15": return Slot.Argument0+15;
450 case "self": return Slot.Self;
451 case "other": return Slot.Other;
452 default:
454 if (auto v = name in locals) return *v;
455 return -1;
458 // options for expression
459 static struct EOpts {
460 int ddest = -1; // >=0: put result in this slot
461 bool dna; // use `ddest` only if we don't need to allocate more slots
464 // returns dest slot
465 // can put value in desired dest
466 ubyte compileExpr (Node nn, int ddest=-1, bool wantref=false) {
467 ubyte doBinOp (Op op, NodeBinary n) {
468 auto dest = allocSlot(n.loc, ddest);
469 auto o0 = compileExpr(n.el);
470 auto o1 = compileExpr(n.er);
471 emit(op, dest, o0, o1);
472 freeSlot(o0);
473 freeSlot(o1);
474 return dest;
477 ubyte doUnOp (Op op, NodeUnary n) {
478 auto dest = allocSlot(n.loc, ddest);
479 auto o0 = compileExpr(n.e);
480 emit(op, dest, o0);
481 freeSlot(o0);
482 return dest;
485 nn.pcs = pc;
486 scope(exit) nn.pce = pc;
487 return selectNode!ubyte(nn,
488 (NodeLiteralNum n) {
489 auto dest = allocSlot(n.loc, ddest);
490 emitPLit(n.loc, dest, n.val);
491 return dest;
493 (NodeLiteralStr n) {
494 auto dest = allocSlot(n.loc, ddest);
495 auto sid = allocStrConst(n.val, n.loc);
496 emitPLit(n.loc, dest, buildStrId(sid));
497 return dest;
499 (NodeUnaryParens n) => compileExpr(n.e, ddest, wantref),
500 (NodeUnaryNot n) => doUnOp(Op.lnot, n),
501 (NodeUnaryNeg n) => doUnOp(Op.neg, n),
502 (NodeUnaryBitNeg n) => doUnOp(Op.bneg, n),
503 (NodeBinaryAss n) {
504 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");
505 if (auto did = cast(NodeId)n.el) {
506 auto vdst = varSlot(did.name);
507 assert(vdst >= 0);
508 auto dest = compileExpr(n.er, ddest:vdst);
509 freeSlot(dest);
510 } else {
511 auto src = compileExpr(n.er);
512 auto dest = compileExpr(n.el, wantref:true);
513 emit(Op.rstore, dest, src);
514 freeSlot(src);
515 freeSlot(dest);
517 return 0;
519 (NodeBinaryAdd n) => doBinOp(Op.add, n),
520 (NodeBinarySub n) => doBinOp(Op.sub, n),
521 (NodeBinaryMul n) => doBinOp(Op.mul, n),
522 (NodeBinaryRDiv n) => doBinOp(Op.rdiv, n),
523 (NodeBinaryDiv n) => doBinOp(Op.div, n),
524 (NodeBinaryMod n) => doBinOp(Op.mod, n),
525 (NodeBinaryBitOr n) => doBinOp(Op.bor, n),
526 (NodeBinaryBitAnd n) => doBinOp(Op.band, n),
527 (NodeBinaryBitXor n) => doBinOp(Op.bxor, n),
528 (NodeBinaryLShift n) => doBinOp(Op.shl, n),
529 (NodeBinaryRShift n) => doBinOp(Op.shr, n),
530 (NodeBinaryLess n) => doBinOp(Op.lt, n),
531 (NodeBinaryLessEqu n) => doBinOp(Op.le, n),
532 (NodeBinaryGreat n) => doBinOp(Op.gt, n),
533 (NodeBinaryGreatEqu n) => doBinOp(Op.ge, n),
534 (NodeBinaryEqu n) => doBinOp(Op.eq, n),
535 (NodeBinaryNotEqu n) => doBinOp(Op.ne, n),
536 (NodeBinaryLogOr n) => doBinOp(Op.lor, n),
537 (NodeBinaryLogAnd n) => doBinOp(Op.land, n),
538 (NodeBinaryLogXor n) => doBinOp(Op.lxor, n),
539 (NodeFCall n) {
540 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
541 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
542 auto dest = allocSlot(n.loc, ddest);
543 // preallocate frame
544 // we can do this, as current slot allocation scheme guarantees
545 // that we won't have used slots with higher numbert after compiling
546 // argument expressions
547 // `reserveCallSlots()` won't mark slots as used
548 auto frameSize = cast(uint)n.args.length+Slot.Argument0;
549 auto fcs = reserveCallSlots(n.loc, frameSize+1); // +1 for script id
550 // put arguments where we want 'em to be
551 foreach (immutable idx, Node a; n.args) {
552 // reserve result slot, so it won't be overwritten
553 assert(!slots[fcs+Slot.Argument0+idx]);
554 slots[fcs+Slot.Argument0+idx] = true;
555 auto dp = compileExpr(a, fcs+Slot.Argument0+idx);
556 if (dp != fcs+Slot.Argument0+idx) assert(0, "internal compiler error");
558 // now free result slots
559 foreach (immutable idx; 0..n.args.length) freeSlot(cast(ubyte)(fcs+Slot.Argument0+idx));
560 // make sure that our invariant holds
561 if (reserveCallSlots(n.loc, 1) != fcs) assert(0, "internal compiler error");
562 // put script id
563 // emit call
564 uint sid = sid4name((cast(NodeId)n.fe).name);
565 emit2Bytes(Op.xlit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)sid);
566 emit(Op.call, dest, fcs, cast(ubyte)n.args.length);
567 return dest;
569 (NodeId n) {
570 if (wantref) {
571 auto vsl = varSlot(n.name);
572 assert(vsl >= 0);
573 auto dest = allocSlot(n.loc, ddest);
574 emit(Op.lref, dest, cast(ubyte)vsl);
575 return dest;
576 } else {
577 auto vsl = varSlot(n.name);
578 assert(vsl >= 0);
579 if (ddest < 0) return vsl; // just use this slot directly
580 auto dest = allocSlot(n.loc, ddest);
581 if (dest == vsl) return dest;
582 emit(Op.copy, dest, cast(ubyte)vsl, 1);
583 return dest;
585 assert(0);
586 //return 0;
588 (NodeDot n) {
589 assert(0);
591 (NodeIndex n) {
592 //if (auto r = visitNodes(n.ei0, dg)) return r;
593 //if (auto r = visitNodes(n.ei1, dg)) return r;
594 //return visitNodes(n.e, dg);
595 assert(0);
597 () { assert(0, "unimplemented node: "~typeid(nn).name); },
601 void compile (Node nn) {
602 assert(nn !is null);
603 nn.pcs = pc;
604 scope(exit) nn.pce = pc;
605 return selectNode!void(nn,
606 (NodeVarDecl n) {},
607 (NodeBlock n) {
608 foreach (Node st; n.stats) compile(st);
610 (NodeStatementEmpty n) {},
611 (NodeStatementExpr n) {
612 freeSlot(compileExpr(n.e));
614 (NodeReturn n) {
615 if (n.e is null) {
616 emit2Bytes(Op.ilit, 0, 0);
617 emit(Op.ret, 0);
618 } else {
619 auto dest = compileExpr(n.e);
620 emit(Op.ret, dest);
621 freeSlot(dest);
624 (NodeWith n) {
625 assert(0);
627 (NodeIf n) {
628 auto cs = compileExpr(n.ec);
629 freeSlot(cs); // yep, free it here
630 emit(Op.xtrue, cs);
631 uint jfc = 0;
632 // simple optimization
633 jfc = emitJumpChain(0, Op.jump);
634 compile(n.et);
635 if (n.ef !is null) {
636 auto exc = emitJumpChain(0, Op.jump);
637 fixJumpChain(jfc, pc);
638 jfc = exc;
639 compile(n.ef);
641 fixJumpChain(jfc, pc);
643 (NodeStatementBreak n) {
644 assert(0);
646 (NodeStatementContinue n) {
647 assert(0);
649 (NodeFor n) {
651 if (auto r = visitNodes(n.einit, dg)) return r;
652 if (auto r = visitNodes(n.econd, dg)) return r;
653 if (auto r = visitNodes(n.enext, dg)) return r;
654 return visitNodes(n.ebody, dg);
656 assert(0);
658 (NodeWhile n) {
659 assert(0);
661 (NodeDoUntil n) {
662 assert(0);
664 (NodeRepeat n) {
665 assert(0);
667 (NodeSwitch n) {
669 if (auto r = visitNodes(n.e, dg)) return r;
670 foreach (ref ci; n.cases) {
671 if (auto r = visitNodes(ci.e, dg)) return r;
672 if (auto r = visitNodes(ci.st, dg)) return r;
674 return null;
676 assert(0);
678 () { assert(0, "unimplemented node: "~typeid(nn).name); },
682 uint sid = sid4name(fn.name);
683 //{ import std.stdio; writeln("compiling '", fn.name, "' (", sid, ")..."); }
684 auto startpc = emit(Op.enter);
685 fn.pcs = pc;
686 compile(fn.ebody);
687 emit(Op.ret);
688 fn.pce = pc;
689 // patch enter
690 code[startpc] = (locals.length<<24)|((maxUsedSlot+1)<<16)|cast(ubyte)Op.enter;
691 scriptPCs[sid] = startpc;
692 scriptASTs[sid] = fn;
695 private:
696 static struct CallFrame {
697 uint script;
698 uint bp; // base pointer (address of the current frame in stack)
699 uint pc; // current pc; will be set on "call"
700 ubyte rval; // slot for return value; will be set on "call"
701 @disable this (this);
703 CallFrame[32768] frames;
704 CallFrame* curframe;
705 Real[] stack;
707 void runtimeError(A...) (uint pc, A args) {
708 import std.stdio : stderr;
709 stderr.writef("ERROR at %08X: ", pc);
710 stderr.writeln(args);
711 // try to build stack trace
712 if (curframe !is null) {
713 curframe.pc = pc;
714 auto cf = curframe;
715 for (;;) {
716 stderr.writefln("%08X: %s", cf.pc, scriptNum2Name[cf.script]);
717 if (cf is frames.ptr) break; // it's not legal to compare pointers from different regions
718 --cf;
721 throw new Exception("fuuuuu");
724 public Real exec(A...) (string name, A args) {
725 static assert(A.length < 16, "too many arguments");
726 auto sid = scripts[name];
727 assert(curframe is null);
728 // create frame
729 if (stack.length < 65536) stack.length = 65536;
730 curframe = &frames[0];
731 curframe.bp = 0;
732 curframe.script = sid;
733 stack[0..Slot.max+1] = 0;
734 foreach (immutable idx, immutable a; args) {
735 static if (is(typeof(a) : const(char)[])) {
736 //FIXME
737 assert(0);
738 } else static if (is(typeof(a) : Real)) {
739 stack[Slot.Argument0+idx] = cast(Real)a;
740 } else {
741 static assert(0, "invalid argument type");
744 //{ import std.stdio; writeln(scriptPCs[sid]); }
745 return doExec(scriptPCs[sid]);
748 // current frame must be properly initialized
749 Real doExec (uint pc) {
750 enum BinOpMixin(string op, string ack="") =
751 "auto dest = opx.opDest;\n"~
752 "auto o0 = bp[opx.opOp0];\n"~
753 "auto o1 = bp[opx.opOp1];\n"~
754 ack~
755 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
756 "bp[dest] = o0"~op~"o1;\n"~
757 "break;";
758 enum BinIOpMixin(string op, string ack="") =
759 "auto dest = opx.opDest;\n"~
760 "auto o0 = bp[opx.opOp0];\n"~
761 "auto o1 = bp[opx.opOp1];\n"~
762 ack~
763 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
764 "bp[dest] = lrint(o0)"~op~"lrint(o1);\n"~
765 "break;";
767 enum BinCmpMixin(string op) =
768 "auto dest = opx.opDest;\n"~
769 "auto o0 = bp[opx.opOp0];\n"~
770 "auto o1 = bp[opx.opOp1];\n"~
771 "assert(!o0.isUndef && !o1.isUndef);\n"~
772 "if (o0.isString) {\n"~
773 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
774 " string s0 = spool[o0.getStrId];\n"~
775 " string s1 = spool[o1.getStrId];\n"~
776 " bp[dest] = (s0 "~op~" s1 ? 1 : 0);\n"~
777 "} else {\n"~
778 " assert(o0.isReal);\n"~
779 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
780 " bp[dest] = (o0 "~op~" o1 ? 1 : 0);\n"~
781 "}\n"~
782 "break;";
784 enum BinLogMixin(string op) =
785 "auto dest = opx.opDest;\n"~
786 "auto o0 = bp[opx.opOp0];\n"~
787 "auto o1 = bp[opx.opOp1];\n"~
788 "assert(!o0.isUndef && !o1.isUndef);\n"~
789 "if (o0.isString) {\n"~
790 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
791 " string s0 = spool[o0.getStrId];\n"~
792 " string s1 = spool[o1.getStrId];\n"~
793 " bp[dest] = (s0.length "~op~" s1.length ? 1 : 0);\n"~
794 "} else {\n"~
795 " assert(o0.isReal);\n"~
796 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
797 " bp[dest] = (lrint(o0) "~op~" lrint(o1) ? 1 : 0);\n"~
798 "}\n"~
799 "break;";
801 static if (is(Real == float)) {
802 import core.stdc.math : lrint = lrintf;
803 } else static if (is(Real == double)) {
804 import core.stdc.math : lrint;
805 } else {
806 static assert(0, "wtf?!");
808 assert(curframe !is null);
809 assert(pc > 0 && pc < code.length);
810 assert(code[pc].opCode == Op.enter);
811 assert(stack.length > 0);
812 auto bp = &stack[curframe.bp];
813 auto origcf = curframe;
814 auto cptr = code.ptr+pc;
815 //if (stack.length < 65536) stack.length = 65536;
816 debug(vm_exec) uint maxslots = Slot.max+1;
817 for (;;) {
818 debug(vm_exec) {
819 import std.stdio : stderr;
820 foreach (immutable idx; 0..maxslots) stderr.writeln(" ", idx, ": ", bp[idx]);
821 dumpInstr(stderr, cast(uint)(cptr-code.ptr));
823 auto opx = *cptr++;
824 switch (opx.opCode) {
825 case Op.nop:
826 break;
828 case Op.copy: // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
829 import core.stdc.string : memmove;
830 auto dest = opx.opDest;
831 auto first = opx.opOp0;
832 auto count = opx.opOp1;
833 if (count) memmove(bp+dest, bp+first, count*Real.sizeof);
834 break;
836 case Op.lnot: // lognot
837 auto dest = opx.opDest;
838 auto o0 = bp[opx.opOp0];
839 assert(!o0.isUndef);
840 if (o0.isString) {
841 auto s0 = spool[o0.getStrId];
842 bp[dest] = (s0.length ? 0 : 1);
843 } else {
844 bp[dest] = (lrint(o0) ? 0 : 1);
846 break;
847 case Op.neg:
848 auto dest = opx.opDest;
849 auto o0 = bp[opx.opOp0];
850 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
851 bp[dest] = -o0;
852 break;
853 case Op.bneg:
854 auto dest = opx.opDest;
855 auto o0 = bp[opx.opOp0];
856 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
857 bp[dest] = cast(int)(~(cast(int)lrint(o0)));
858 break;
860 case Op.add:
861 auto dest = opx.opDest;
862 auto o0 = bp[opx.opOp0];
863 auto o1 = bp[opx.opOp1];
864 assert(!o0.isUndef && !o1.isUndef);
865 if (o0.isString) {
866 if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
867 string s0 = spool[o0.getStrId];
868 string s1 = spool[o1.getStrId];
869 //FIXME
870 if (s0.length == 0) {
871 bp[dest] = o1;
872 } else if (s1.length == 0) {
873 bp[dest] = o0;
874 } else {
875 auto sidx = cast(uint)spool.length;
876 spool ~= s0~s1;
877 bp[dest] = buildStrId(sidx);
879 } else {
880 assert(o0.isReal);
881 if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
882 bp[dest] = o0+o1;
884 break;
885 case Op.sub: mixin(BinOpMixin!"-");
886 case Op.mul: mixin(BinOpMixin!"*");
887 case Op.mod: mixin(BinOpMixin!("%", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
888 case Op.div: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
889 case Op.rdiv: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
890 case Op.bor: mixin(BinIOpMixin!"|");
891 case Op.bxor: mixin(BinIOpMixin!"^");
892 case Op.band: mixin(BinIOpMixin!"&");
893 case Op.shl: mixin(BinIOpMixin!"<<");
894 case Op.shr: mixin(BinIOpMixin!">>");
896 case Op.lt: mixin(BinCmpMixin!"<");
897 case Op.le: mixin(BinCmpMixin!"<=");
898 case Op.gt: mixin(BinCmpMixin!">");
899 case Op.ge: mixin(BinCmpMixin!">=");
900 case Op.eq: mixin(BinCmpMixin!"==");
901 case Op.ne: mixin(BinCmpMixin!"!=");
903 case Op.lor: mixin(BinLogMixin!"||");
904 case Op.land: mixin(BinLogMixin!"&&");
905 case Op.lxor: assert(0);
907 case Op.plit: // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
908 auto dest = opx.opDest;
909 uint idx = cast(ushort)opx.op2Byte;
910 if (idx == ushort.max) {
911 assert((*cptr).opCode == Op.skip);
912 idx = (*cptr++).op3Byte;
914 bp[dest] = vpool.ptr[idx];
915 break;
916 case Op.ilit: // dest becomes ilit val (val: short) -- load small integer literal
917 auto dest = opx.opDest;
918 bp[dest] = opx.opILit;
919 break;
920 case Op.xlit: // dest becomes integer(!) val (val: short) -- load small integer literal
921 auto dest = opx.opDest;
922 *cast(uint*)(bp+dest) = opx.opILit;
923 break;
925 case Op.jump: // addr: 3 bytes
926 cptr = code.ptr+opx.op3Byte;
927 break;
928 case Op.xtrue: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
929 if (lrint(bp[opx.opDest]) != 0) ++cptr;
930 break;
931 case Op.xfalse: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
932 if (lrint(bp[opx.opDest]) == 0) ++cptr;
933 break;
935 case Op.call: // dest is result; op0: call frame (see below); op1: number of args
936 // call frame is:
937 // new function frame
938 // int scriptid (after op1+3 slots)
939 // note that there should be no used registers after those (as that will be used as new function frame regs)
940 auto sid = *cast(uint*)(bp+opx.opOp0+Slot.Argument0+opx.opOp1);
941 if (sid >= scriptPCs.length) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid script id");
942 pc = scriptPCs.ptr[sid];
943 if (pc < 1 || pc >= code.length) {
944 string scname;
945 foreach (auto kv; scripts.byKeyValue) if (kv.value == sid) { scname = kv.key; break; }
946 runtimeError(cast(uint)(cptr-code.ptr-1), "trying to execute undefined script '", scname, "'");
948 debug(vm_exec) {
949 import std.stdio : stderr;
950 stderr.writeln("calling '", scriptNum2Name[sid], "'");
951 foreach (immutable aidx; 0..opx.opOp1) stderr.writeln(" ", bp[opx.opOp0+Slot.Argument0+aidx]);
953 // if this is tail call, just do it as tail call then
954 // but don't optimize out top-level call, heh
955 if (curframe !is origcf && (*cptr).opCode == Op.ret) {
956 import core.stdc.string : memcpy;
957 // yay, it is a tail call!
958 // copy arguments (it's safe to use `memcpy()` here); `self` and `other` are automatically ok
959 if (opx.opOp1) memcpy(bp+Slot.Argument0, bp+opx.opOp0+Slot.Argument0, Real.sizeof*opx.opOp1);
960 // simply replace current frame with new one
961 } else {
962 bp[opx.opOp0..opx.opOp0+Slot.Argument0] = bp[0..Slot.Argument0]; // copy `self` and `other`
963 curframe.pc = cast(uint)(cptr-code.ptr);
964 curframe.rval = opx.opDest;
965 ++curframe;
966 curframe.bp = curframe[-1].bp+opx.opOp0;
967 bp = &stack[curframe.bp];
969 curframe.script = sid;
970 cptr = code.ptr+scriptPCs.ptr[sid];
971 //assert((*cptr).opCode == Op.enter);
972 // clear unused arguments
973 if (opx.opOp1 < 16) bp[Slot.Argument0+opx.opOp1..Slot.Argument15+1] = 0;
974 break;
976 case Op.enter: // op0: number of stack slots used (including result and args); op1: number of locals
977 if (curframe.bp+opx.opOp0 > stack.length) {
978 stack.length = curframe.bp+opx.opOp0;
979 bp = &stack[curframe.bp];
981 //foreach (immutable idx; Slot.max+1..Slot.max+1+opx.opOp1) bp[idx] = 0; // clear locals
982 if (opx.opOp1) bp[Slot.max+1..Slot.max+1+opx.opOp1] = 0; // clear locals
983 debug(vm_exec) maxslots = opx.opOp0;
984 debug(vm_exec) { import std.stdio : stderr; foreach (immutable idx; Slot.Argument0..Slot.Argument15+1) stderr.writeln(" :", bp[idx]); }
985 break;
987 case Op.ret: // dest is retvalue; it is copied to reg0; other stack items are discarded
988 if (curframe is origcf) return bp[opx.opDest]; // done
989 assert(cast(uint)curframe > cast(uint)origcf);
990 --curframe;
991 auto rv = bp[opx.opDest];
992 // remove stack frame
993 bp = &stack[curframe.bp];
994 cptr = code.ptr+curframe.pc;
995 bp[curframe.rval] = rv;
996 debug(vm_exec) { import std.stdio : stderr; stderr.writeln("RET(", curframe.rval, "): ", rv); }
997 break;
999 //as we are using refloads only in the last stage of assignment, they can create values
1000 case Op.lref: // load slot reference to dest
1001 *cast(int*)bp[opx.opDest] = opx.opOp0;
1002 break;
1003 //case Op.oref: // load object reference to dest; op0: int reg (obj id; -666: global object)
1004 //case Op.fref: // load field reference; op0: varref; op1: int reg (field id); can't create fields
1005 //case Op.fcrf: // load field reference; op0: varref; op1: int reg (field id); can create field
1006 //case Op.iref: // load indexed reference; op0: varref; op1: int reg (index)
1007 //case Op.mref: // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
1009 //case Op.rload: // load from op0-varref to dest
1010 case Op.rstore: // store to op0-varref from op1
1011 auto x = *cast(int*)bp[opx.opOp0];
1012 assert(x >= 0 && x <= 255);
1013 bp[x] = bp[opx.opOp1];
1014 break;
1016 //case Op.oload: // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
1017 //case Op.iload: // load indexed (as iref)
1018 //case Op.mload: // load indexed (as mref)
1019 default: assert(0);
1026 static:
1027 enum OpArgs {
1028 None,
1029 Dest,
1030 DestOp0,
1031 DestOp0Op1,
1032 Dest2Bytes,
1033 Dest3Bytes,
1034 DestInt,
1035 DestJump,
1036 DestCall,
1037 Op0Op1,
1039 immutable OpArgs[ubyte] opargs;
1040 shared static this () {
1041 with(OpArgs) opargs = [
1042 Op.nop: None,
1043 Op.skip: None,
1044 Op.copy: DestOp0Op1,
1045 Op.lnot: DestOp0, //: lognot
1046 Op.neg: DestOp0,
1047 Op.bneg: DestOp0,
1049 Op.add: DestOp0Op1,
1050 Op.sub: DestOp0Op1,
1051 Op.mul: DestOp0Op1,
1052 Op.mod: DestOp0Op1,
1053 Op.div: DestOp0Op1,
1054 Op.rdiv: DestOp0Op1,
1055 Op.bor: DestOp0Op1,
1056 Op.bxor: DestOp0Op1,
1057 Op.band: DestOp0Op1,
1058 Op.shl: DestOp0Op1,
1059 Op.shr: DestOp0Op1,
1060 Op.lt: DestOp0Op1,
1061 Op.le: DestOp0Op1,
1062 Op.gt: DestOp0Op1,
1063 Op.ge: DestOp0Op1,
1064 Op.eq: DestOp0Op1,
1065 Op.ne: DestOp0Op1,
1066 Op.lor: DestOp0Op1,
1067 Op.land: DestOp0Op1,
1068 Op.lxor: DestOp0Op1,
1070 Op.plit: Dest2Bytes,
1071 Op.ilit: DestInt,
1072 Op.xlit: DestInt,
1074 Op.jump: DestJump,
1075 Op.xtrue: Dest,
1076 Op.xfalse: Dest,
1078 Op.call: DestCall,
1080 Op.enter: Op0Op1,
1082 Op.ret: Dest,
1084 Op.lref: DestOp0,
1085 Op.oref: DestOp0,
1086 Op.fref: DestOp0Op1,
1087 Op.fcrf: DestOp0Op1,
1088 Op.iref: DestOp0Op1,
1089 Op.mref: DestOp0Op1,
1091 Op.rload: DestOp0,
1092 Op.rstore: DestOp0,
1094 Op.oload: DestOp0Op1,
1095 Op.iload: DestOp0Op1,
1096 Op.mload: DestOp0Op1,
1099 Op.siter: DestOp0,
1100 Op.niter: DestJump,
1101 Op.kiter: Dest,
1103 Op.lirint: DestOp0, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
1109 // ////////////////////////////////////////////////////////////////////////// //
1110 private:
1111 ubyte opCode (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op&0xff); }
1112 ubyte opDest (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>8)&0xff); }
1113 ubyte opOp0 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>16)&0xff); }
1114 ubyte opOp1 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>24)&0xff); }
1115 short opILit (uint op) pure nothrow @safe @nogc { pragma(inline, true); return cast(short)((op>>16)&0xffff); }
1116 uint op3Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>8); }
1117 uint op2Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>16); }
1119 uint opMakeILit (ubyte op, byte dest, short val) pure nothrow @safe @nogc { pragma(inline, true); return ((val<<16)|((dest&0xff)<<8)|op); }
1120 uint opMake3Byte (ubyte op, uint val) pure nothrow @safe @nogc { pragma(inline, true); assert(val <= 0xffffff); return (val<<8)|op; }