don't allocate slots for argument aliases
[gaemu.git] / gmlvm.d
blobe88c5831a2404c01cde95a03ae4fdfb753f3273f
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) {
240 int argvar (string s) {
241 switch (s) {
242 case "argument0": return 0;
243 case "argument1": return 1;
244 case "argument2": return 2;
245 case "argument3": return 3;
246 case "argument4": return 4;
247 case "argument5": return 5;
248 case "argument6": return 6;
249 case "argument7": return 7;
250 case "argument8": return 8;
251 case "argument9": return 9;
252 case "argument10": return 10;
253 case "argument11": return 11;
254 case "argument12": return 12;
255 case "argument13": return 13;
256 case "argument14": return 14;
257 case "argument15": return 15;
258 default:
260 return -1;
263 void compileError(A...) (Loc loc, A args) {
264 if (fn.pp !is null) {
265 fn.pp.error(loc, args);
266 } else {
267 import std.stdio : stderr;
268 stderr.writeln("ERROR at ", loc, ": ", args);
269 string msg;
270 foreach (immutable a; args) {
271 import std.string : format;
272 msg ~= "%s".format(a);
274 throw new ErrorAt(loc, msg);
278 uint sid4name (string name) {
279 if (auto sptr = name in scripts) {
280 return *sptr;
281 } else {
282 auto sid = cast(uint)scriptPCs.length;
283 if (sid > 32767) compileError(fn.loc, "too many scripts");
284 assert(scriptASTs.length == sid);
285 // reserve slots
286 scriptPCs ~= 0;
287 scriptASTs ~= null;
288 scriptNum2Name[sid] = name;
289 scripts[name] = sid;
290 return sid;
294 uint pc () { return cast(uint)code.length; }
296 uint emit (Op op, ubyte dest=0, ubyte op0=0, ubyte op1=0) {
297 auto res = cast(uint)code.length;
298 code ~= (op1<<24)|(op0<<16)|(dest<<8)|cast(ubyte)op;
299 return res;
302 uint emit3Bytes (Op op, uint val) {
303 assert(val <= 0xffffff);
304 auto res = cast(uint)code.length;
305 code ~= (val<<8)|cast(ubyte)op;
306 return res;
309 uint emit2Bytes (Op op, ubyte dest, short val) {
310 auto res = cast(uint)code.length;
311 code ~= (val<<16)|(dest<<8)|cast(ubyte)op;
312 return res;
315 uint emitJumpTo (Op op, uint addr) {
316 assert(addr <= 0xffffff);
317 auto res = cast(uint)code.length;
318 code ~= cast(uint)op|(addr<<8);
319 return res;
322 // this starts "jump chain", return new chain id
323 uint emitJumpChain (uint chain, Op op) {
324 assert(chain <= 0xffffff);
325 auto res = cast(uint)code.length;
326 code ~= cast(uint)op|(chain<<8);
327 return res;
330 void fixJumpChain (uint chain, uint addr) {
331 assert(chain <= 0xffffff);
332 assert(addr <= 0xffffff);
333 while (chain) {
334 auto nc = op3Byte(code[chain]);
335 code[chain] = (code[chain]&0xff)|(addr<<8);
336 chain = nc;
340 assert(fn !is null);
341 assert(fn.ebody !is null);
342 assert(fn.name.length);
344 bool[256] slots;
345 foreach (immutable idx; 0..Slot.max+1) slots[idx] = true; // used
346 uint firstFreeSlot = Slot.max+1;
347 uint maxUsedSlot = firstFreeSlot-1;
349 ubyte allocSlot (Loc loc, int ddest=-1) {
350 if (ddest >= 0) {
351 assert(ddest < slots.length);
352 return cast(ubyte)ddest;
354 foreach (immutable idx; firstFreeSlot..slots.length) {
355 if (!slots[idx]) {
356 if (idx > maxUsedSlot) maxUsedSlot = cast(uint)idx;
357 slots[idx] = true;
358 return cast(ubyte)idx;
361 compileError(loc, "out of free slots");
362 assert(0);
365 ubyte reserveCallSlots (Loc loc, uint resnum) {
366 foreach_reverse (immutable idx, bool v; slots) {
367 if (v) {
368 if (idx+resnum+1 > slots.length) compileError(loc, "out of free slots");
369 return cast(ubyte)(idx+1);
372 compileError(loc, "out of free slots");
373 assert(0);
376 void freeSlot (ubyte num) {
377 if (num >= firstFreeSlot) {
378 assert(slots[num]);
379 slots[num] = false;
383 ubyte[string] locals;
384 uint[string] globals;
385 Loc[string] vdecls; // for error messages
387 // collect var declarations (gml is not properly scoped)
388 visitNodes(fn.ebody, (Node n) {
389 if (auto vd = cast(NodeVarDecl)n) {
390 foreach (immutable idx, string name; vd.names) {
391 if (name in locals) {
392 if (vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
393 } else if (name in globals) {
394 if (!vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
396 vdecls[name] = vd.locs[idx];
397 if (vd.asGlobal) {
398 globals[name] = 0;
399 } else {
400 // don't allocate slots for locals here, we can remove some locals due to arguments aliasing later
401 //firstFreeSlot = allocSlot(vd.locs[idx]);
402 //locals[name] = cast(ubyte)firstFreeSlot;
403 //++firstFreeSlot;
404 locals[name] = 42; // temporary value
408 return VisitRes.Continue;
411 /* here we will do very simple analysis for code like
412 * var m, n;
413 * m = argument0;
414 * n = argument1;
415 * ...no `arument0` and `argument1` usage after this point
416 * we can just alias `m` to `arument0`, and `n` to `argument1` then
419 string[16] aaliases; // argument aliases
421 uint firstBadStatement = 0;
422 foreach (immutable idx, Node st; fn.ebody.stats) {
423 if (cast(NodeStatementEmpty)st || cast(NodeStatementExpr)st || cast(NodeVarDecl)st) {
424 firstBadStatement = cast(uint)idx+1;
425 } else {
426 break;
429 if (firstBadStatement > 0) {
430 bool[string] varsused;
431 // scan statements, find assignments
432 foreach (immutable idx, Node st; fn.ebody.stats[0..firstBadStatement]) {
433 if (auto se = cast(NodeStatementExpr)st) {
434 if (auto ass = cast(NodeBinaryAss)se.e) {
435 // wow, assignment
436 auto lv = cast(NodeId)ass.el;
437 auto rv = cast(NodeId)ass.er;
438 if (lv !is null && rv !is null) {
439 // "a = b"
440 { import std.stdio : stderr; stderr.writeln("found assignment: '", lv.name, "' = '", rv.name, "'"); }
441 if (argvar(rv.name) >= 0 && argvar(lv.name) < 0) {
442 // "a = argumentx"
443 if (lv.name in varsused || rv.name in varsused) continue; // no wai
444 if (lv.name !in locals) continue; // not a local
445 auto ai = argvar(rv.name);
446 if (aaliases[ai].length && aaliases[ai] != lv.name) continue; // already have an alias (TODO)
447 aaliases[ai] = lv.name; // possible alias
448 } else {
449 // check for reassignment
450 if (lv.name !in varsused) {
451 // not used before, but used now; remove it from aliases
452 foreach (ref an; aaliases) if (an == lv.name) an = null;
453 varsused[lv.name] = true;
460 // now check if we have any assignment to aliased argument
461 foreach (immutable idx, string an; aaliases) {
462 if (an.length == 0) continue;
463 visitNodes(fn.ebody, (Node n) {
464 if (auto ass = cast(NodeBinaryAss)n) {
465 if (auto id = cast(NodeId)ass.el) {
466 auto ai = argvar(id.name);
467 if (ai >= 0) aaliases[idx] = null;
468 return VisitRes.Stop;
471 return VisitRes.Continue;
474 // remove aliases from locals (we don't need slots for 'em)
475 foreach (immutable idx, string an; aaliases) {
476 if (an.length == 0) continue;
477 locals.remove(an);
479 // dump aliases
481 import std.stdio : stderr;
482 foreach (immutable idx, string an; aaliases) {
483 if (an.length) stderr.writeln("'argument", idx, "' is aliased to '", an, "'");
489 // now assign slots to locals
490 foreach (string name; locals.keys) {
491 firstFreeSlot = allocSlot(vdecls[name]);
492 locals[name] = cast(ubyte)firstFreeSlot;
493 ++firstFreeSlot;
496 void emitPLit (Loc loc, ubyte dest, Real v) {
497 uint vpidx = uint.max;
498 if (isReal(v)) {
499 // number
500 import core.stdc.math : lrint;
501 if (lrint(v) == v && lrint(v) >= short.min && lrint(v) <= short.max) {
502 emit2Bytes(Op.ilit, dest, cast(short)lrint(v));
503 return;
505 //FIXME: speed it up!
506 foreach (immutable idx, Real vp; vpool) if (vp == v) { vpidx = cast(uint)idx; break; }
507 } else if (isString(v)) {
508 // string
509 //FIXME: speed it up!
510 auto sid = v.getStrId;
511 foreach (immutable idx, Real vp; vpool) if (vp.isString && vp.getStrId == sid) { vpidx = cast(uint)idx; break; }
512 } else {
513 assert(0, "wtf?!");
515 if (vpidx == uint.max) {
516 vpidx = cast(uint)vpool.length;
517 if (vpidx >= 0xffffff) compileError(loc, "too many constants");
518 vpool ~= v;
520 if (vpidx < ushort.max) {
521 emit2Bytes(Op.plit, dest, cast(ushort)vpidx);
522 } else {
523 // special form
524 emit2Bytes(Op.plit, dest, cast(short)ushort.max);
525 emit3Bytes(Op.skip, vpidx);
529 uint allocStrConst (string s, Loc loc) {
530 if (s.length == 0) return 0;
531 //FIXME: speed it up!
532 foreach (immutable idx, string vp; spool) {
533 if (vp == s) return cast(ushort)idx;
535 auto sidx = cast(uint)spool.length;
536 if (sidx >= 0xffffff) compileError(loc, "too many strings");
537 spool ~= s;
538 return sidx;
541 int varSlot (string name) {
542 auto avn = argvar(name);
543 if (avn >= 0) return Slot.Argument0+avn;
544 switch (name) {
545 case "self": return Slot.Self;
546 case "other": return Slot.Other;
547 default:
549 // argument aliases
550 foreach (immutable idx, string an; aaliases) if (an == name) return cast(int)Slot.Argument0+idx;
551 // locals
552 if (auto v = name in locals) return *v;
553 return -1;
556 // options for expression
557 static struct EOpts {
558 int ddest = -1; // >=0: put result in this slot
559 bool dna; // use `ddest` only if we don't need to allocate more slots
562 // returns dest slot
563 // can put value in desired dest
564 ubyte compileExpr (Node nn, int ddest=-1, bool wantref=false) {
565 ubyte doBinOp (Op op, NodeBinary n) {
566 auto dest = allocSlot(n.loc, ddest);
567 auto o0 = compileExpr(n.el);
568 auto o1 = compileExpr(n.er);
569 emit(op, dest, o0, o1);
570 freeSlot(o0);
571 freeSlot(o1);
572 return dest;
575 ubyte doUnOp (Op op, NodeUnary n) {
576 auto dest = allocSlot(n.loc, ddest);
577 auto o0 = compileExpr(n.e);
578 emit(op, dest, o0);
579 freeSlot(o0);
580 return dest;
583 nn.pcs = pc;
584 scope(exit) nn.pce = pc;
585 return selectNode!ubyte(nn,
586 (NodeLiteralNum n) {
587 auto dest = allocSlot(n.loc, ddest);
588 emitPLit(n.loc, dest, n.val);
589 return dest;
591 (NodeLiteralStr n) {
592 auto dest = allocSlot(n.loc, ddest);
593 auto sid = allocStrConst(n.val, n.loc);
594 emitPLit(n.loc, dest, buildStrId(sid));
595 return dest;
597 (NodeUnaryParens n) => compileExpr(n.e, ddest, wantref),
598 (NodeUnaryNot n) => doUnOp(Op.lnot, n),
599 (NodeUnaryNeg n) => doUnOp(Op.neg, n),
600 (NodeUnaryBitNeg n) => doUnOp(Op.bneg, n),
601 (NodeBinaryAss n) {
602 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");
603 if (auto did = cast(NodeId)n.el) {
604 auto vdst = varSlot(did.name);
605 assert(vdst >= 0);
606 auto dest = compileExpr(n.er, ddest:vdst);
607 freeSlot(dest);
608 } else {
609 auto src = compileExpr(n.er);
610 auto dest = compileExpr(n.el, wantref:true);
611 emit(Op.rstore, dest, src);
612 freeSlot(src);
613 freeSlot(dest);
615 return 0;
617 (NodeBinaryAdd n) => doBinOp(Op.add, n),
618 (NodeBinarySub n) => doBinOp(Op.sub, n),
619 (NodeBinaryMul n) => doBinOp(Op.mul, n),
620 (NodeBinaryRDiv n) => doBinOp(Op.rdiv, n),
621 (NodeBinaryDiv n) => doBinOp(Op.div, n),
622 (NodeBinaryMod n) => doBinOp(Op.mod, n),
623 (NodeBinaryBitOr n) => doBinOp(Op.bor, n),
624 (NodeBinaryBitAnd n) => doBinOp(Op.band, n),
625 (NodeBinaryBitXor n) => doBinOp(Op.bxor, n),
626 (NodeBinaryLShift n) => doBinOp(Op.shl, n),
627 (NodeBinaryRShift n) => doBinOp(Op.shr, n),
628 (NodeBinaryLess n) => doBinOp(Op.lt, n),
629 (NodeBinaryLessEqu n) => doBinOp(Op.le, n),
630 (NodeBinaryGreat n) => doBinOp(Op.gt, n),
631 (NodeBinaryGreatEqu n) => doBinOp(Op.ge, n),
632 (NodeBinaryEqu n) => doBinOp(Op.eq, n),
633 (NodeBinaryNotEqu n) => doBinOp(Op.ne, n),
634 (NodeBinaryLogOr n) => doBinOp(Op.lor, n),
635 (NodeBinaryLogAnd n) => doBinOp(Op.land, n),
636 (NodeBinaryLogXor n) => doBinOp(Op.lxor, n),
637 (NodeFCall n) {
638 if (cast(NodeId)n.fe is null) compileError(n.loc, "invalid function call");
639 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
640 auto dest = allocSlot(n.loc, ddest);
641 // preallocate frame
642 // we can do this, as current slot allocation scheme guarantees
643 // that we won't have used slots with higher numbert after compiling
644 // argument expressions
645 // `reserveCallSlots()` won't mark slots as used
646 auto frameSize = cast(uint)n.args.length+Slot.Argument0;
647 auto fcs = reserveCallSlots(n.loc, frameSize+1); // +1 for script id
648 // put arguments where we want 'em to be
649 foreach (immutable idx, Node a; n.args) {
650 // reserve result slot, so it won't be overwritten
651 assert(!slots[fcs+Slot.Argument0+idx]);
652 slots[fcs+Slot.Argument0+idx] = true;
653 auto dp = compileExpr(a, fcs+Slot.Argument0+idx);
654 if (dp != fcs+Slot.Argument0+idx) assert(0, "internal compiler error");
656 // now free result slots
657 foreach (immutable idx; 0..n.args.length) freeSlot(cast(ubyte)(fcs+Slot.Argument0+idx));
658 // make sure that our invariant holds
659 if (reserveCallSlots(n.loc, 1) != fcs) assert(0, "internal compiler error");
660 // put script id
661 // emit call
662 uint sid = sid4name((cast(NodeId)n.fe).name);
663 emit2Bytes(Op.xlit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)sid);
664 emit(Op.call, dest, fcs, cast(ubyte)n.args.length);
665 return dest;
667 (NodeId n) {
668 if (wantref) {
669 auto vsl = varSlot(n.name);
670 assert(vsl >= 0);
671 auto dest = allocSlot(n.loc, ddest);
672 emit(Op.lref, dest, cast(ubyte)vsl);
673 return dest;
674 } else {
675 auto vsl = varSlot(n.name);
676 assert(vsl >= 0);
677 if (ddest < 0) return vsl; // just use this slot directly
678 auto dest = allocSlot(n.loc, ddest);
679 if (dest == vsl) return dest;
680 emit(Op.copy, dest, cast(ubyte)vsl, 1);
681 return dest;
683 assert(0);
684 //return 0;
686 (NodeDot n) {
687 assert(0);
689 (NodeIndex n) {
690 //if (auto r = visitNodes(n.ei0, dg)) return r;
691 //if (auto r = visitNodes(n.ei1, dg)) return r;
692 //return visitNodes(n.e, dg);
693 assert(0);
695 () { assert(0, "unimplemented node: "~typeid(nn).name); },
699 void compile (Node nn) {
700 assert(nn !is null);
701 nn.pcs = pc;
702 scope(exit) nn.pce = pc;
703 return selectNode!void(nn,
704 (NodeVarDecl n) {},
705 (NodeBlock n) {
706 foreach (Node st; n.stats) compile(st);
708 (NodeStatementEmpty n) {},
709 (NodeStatementExpr n) {
710 freeSlot(compileExpr(n.e));
712 (NodeReturn n) {
713 if (n.e is null) {
714 emit2Bytes(Op.ilit, 0, 0);
715 emit(Op.ret, 0);
716 } else {
717 auto dest = compileExpr(n.e);
718 emit(Op.ret, dest);
719 freeSlot(dest);
722 (NodeWith n) {
723 assert(0);
725 (NodeIf n) {
726 auto cs = compileExpr(n.ec);
727 freeSlot(cs); // yep, free it here
728 emit(Op.xtrue, cs);
729 uint jfc = 0;
730 // simple optimization
731 jfc = emitJumpChain(0, Op.jump);
732 compile(n.et);
733 if (n.ef !is null) {
734 auto exc = emitJumpChain(0, Op.jump);
735 fixJumpChain(jfc, pc);
736 jfc = exc;
737 compile(n.ef);
739 fixJumpChain(jfc, pc);
741 (NodeStatementBreak n) {
742 assert(0);
744 (NodeStatementContinue n) {
745 assert(0);
747 (NodeFor n) {
749 if (auto r = visitNodes(n.einit, dg)) return r;
750 if (auto r = visitNodes(n.econd, dg)) return r;
751 if (auto r = visitNodes(n.enext, dg)) return r;
752 return visitNodes(n.ebody, dg);
754 assert(0);
756 (NodeWhile n) {
757 assert(0);
759 (NodeDoUntil n) {
760 assert(0);
762 (NodeRepeat n) {
763 assert(0);
765 (NodeSwitch n) {
767 if (auto r = visitNodes(n.e, dg)) return r;
768 foreach (ref ci; n.cases) {
769 if (auto r = visitNodes(ci.e, dg)) return r;
770 if (auto r = visitNodes(ci.st, dg)) return r;
772 return null;
774 assert(0);
776 () { assert(0, "unimplemented node: "~typeid(nn).name); },
780 uint sid = sid4name(fn.name);
781 //{ import std.stdio; writeln("compiling '", fn.name, "' (", sid, ")..."); }
782 auto startpc = emit(Op.enter);
783 fn.pcs = pc;
784 compile(fn.ebody);
785 emit(Op.ret);
786 fn.pce = pc;
787 // patch enter
788 code[startpc] = (locals.length<<24)|((maxUsedSlot+1)<<16)|cast(ubyte)Op.enter;
789 scriptPCs[sid] = startpc;
790 scriptASTs[sid] = fn;
793 private:
794 static struct CallFrame {
795 uint script; // script id
796 uint bp; // base pointer (address of the current frame in stack)
797 uint pc; // current pc; will be set on "call"; it is used by callee
798 ubyte rval; // slot for return value; will be set on "call"; it is used by callee
799 @disable this (this);
801 CallFrame[32768] frames;
802 CallFrame* curframe;
803 Real[] stack;
805 void runtimeError(A...) (uint pc, A args) {
806 import std.stdio : stderr;
807 stderr.writef("ERROR at %08X: ", pc);
808 stderr.writeln(args);
809 // try to build stack trace
810 if (curframe !is null) {
811 curframe.pc = pc;
812 auto cf = curframe;
813 for (;;) {
814 stderr.writefln("%08X: %s", cf.pc, scriptNum2Name[cf.script]);
815 if (cf is frames.ptr) break; // it's not legal to compare pointers from different regions
816 --cf;
819 throw new Exception("fuuuuu");
822 public Real exec(A...) (string name, A args) {
823 static assert(A.length < 16, "too many arguments");
824 auto sid = scripts[name];
825 assert(curframe is null);
826 // create frame
827 if (stack.length < 65536) stack.length = 65536;
828 curframe = &frames[0];
829 curframe.bp = 0;
830 curframe.script = sid;
831 stack[0..Slot.max+1] = 0;
832 foreach (immutable idx, immutable a; args) {
833 static if (is(typeof(a) : const(char)[])) {
834 //FIXME
835 assert(0);
836 } else static if (is(typeof(a) : Real)) {
837 stack[Slot.Argument0+idx] = cast(Real)a;
838 } else {
839 static assert(0, "invalid argument type");
842 //{ import std.stdio; writeln(scriptPCs[sid]); }
843 return doExec(scriptPCs[sid]);
846 // current frame must be properly initialized
847 Real doExec (uint pc) {
848 enum BinOpMixin(string op, string ack="") =
849 "auto dest = opx.opDest;\n"~
850 "auto o0 = bp[opx.opOp0];\n"~
851 "auto o1 = bp[opx.opOp1];\n"~
852 ack~
853 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
854 "bp[dest] = o0"~op~"o1;\n"~
855 "break;";
856 enum BinIOpMixin(string op, string ack="") =
857 "auto dest = opx.opDest;\n"~
858 "auto o0 = bp[opx.opOp0];\n"~
859 "auto o1 = bp[opx.opOp1];\n"~
860 ack~
861 "if (!o0.isReal || !o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
862 "bp[dest] = lrint(o0)"~op~"lrint(o1);\n"~
863 "break;";
865 enum BinCmpMixin(string op) =
866 "auto dest = opx.opDest;\n"~
867 "auto o0 = bp[opx.opOp0];\n"~
868 "auto o1 = bp[opx.opOp1];\n"~
869 "assert(!o0.isUndef && !o1.isUndef);\n"~
870 "if (o0.isString) {\n"~
871 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
872 " string s0 = spool[o0.getStrId];\n"~
873 " string s1 = spool[o1.getStrId];\n"~
874 " bp[dest] = (s0 "~op~" s1 ? 1 : 0);\n"~
875 "} else {\n"~
876 " assert(o0.isReal);\n"~
877 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
878 " bp[dest] = (o0 "~op~" o1 ? 1 : 0);\n"~
879 "}\n"~
880 "break;";
882 enum BinLogMixin(string op) =
883 "auto dest = opx.opDest;\n"~
884 "auto o0 = bp[opx.opOp0];\n"~
885 "auto o1 = bp[opx.opOp1];\n"~
886 "assert(!o0.isUndef && !o1.isUndef);\n"~
887 "if (o0.isString) {\n"~
888 " if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
889 " string s0 = spool[o0.getStrId];\n"~
890 " string s1 = spool[o1.getStrId];\n"~
891 " bp[dest] = (s0.length "~op~" s1.length ? 1 : 0);\n"~
892 "} else {\n"~
893 " assert(o0.isReal);\n"~
894 " if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), `invalid type`);\n"~
895 " bp[dest] = (lrint(o0) "~op~" lrint(o1) ? 1 : 0);\n"~
896 "}\n"~
897 "break;";
899 static if (is(Real == float)) {
900 import core.stdc.math : lrint = lrintf;
901 } else static if (is(Real == double)) {
902 import core.stdc.math : lrint;
903 } else {
904 static assert(0, "wtf?!");
906 assert(curframe !is null);
907 assert(pc > 0 && pc < code.length);
908 assert(code[pc].opCode == Op.enter);
909 assert(stack.length > 0);
910 auto bp = &stack[curframe.bp];
911 auto origcf = curframe;
912 auto cptr = code.ptr+pc;
913 //if (stack.length < 65536) stack.length = 65536;
914 debug(vm_exec) uint maxslots = Slot.max+1;
915 for (;;) {
916 debug(vm_exec) {
917 import std.stdio : stderr;
918 foreach (immutable idx; 0..maxslots) stderr.writeln(" ", idx, ": ", bp[idx]);
919 dumpInstr(stderr, cast(uint)(cptr-code.ptr));
921 auto opx = *cptr++;
922 switch (opx.opCode) {
923 case Op.nop:
924 break;
926 case Op.copy: // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
927 import core.stdc.string : memmove;
928 auto dest = opx.opDest;
929 auto first = opx.opOp0;
930 auto count = opx.opOp1;
931 if (count) memmove(bp+dest, bp+first, count*Real.sizeof);
932 break;
934 case Op.lnot: // lognot
935 auto dest = opx.opDest;
936 auto o0 = bp[opx.opOp0];
937 assert(!o0.isUndef);
938 if (o0.isString) {
939 auto s0 = spool[o0.getStrId];
940 bp[dest] = (s0.length ? 0 : 1);
941 } else {
942 bp[dest] = (lrint(o0) ? 0 : 1);
944 break;
945 case Op.neg:
946 auto dest = opx.opDest;
947 auto o0 = bp[opx.opOp0];
948 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
949 bp[dest] = -o0;
950 break;
951 case Op.bneg:
952 auto dest = opx.opDest;
953 auto o0 = bp[opx.opOp0];
954 if (!o0.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
955 bp[dest] = cast(int)(~(cast(int)lrint(o0)));
956 break;
958 case Op.add:
959 auto dest = opx.opDest;
960 auto o0 = bp[opx.opOp0];
961 auto o1 = bp[opx.opOp1];
962 assert(!o0.isUndef && !o1.isUndef);
963 if (o0.isString) {
964 if (!o1.isString) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
965 string s0 = spool[o0.getStrId];
966 string s1 = spool[o1.getStrId];
967 //FIXME
968 if (s0.length == 0) {
969 bp[dest] = o1;
970 } else if (s1.length == 0) {
971 bp[dest] = o0;
972 } else {
973 auto sidx = cast(uint)spool.length;
974 spool ~= s0~s1;
975 bp[dest] = buildStrId(sidx);
977 } else {
978 assert(o0.isReal);
979 if (!o1.isReal) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid type");
980 bp[dest] = o0+o1;
982 break;
983 case Op.sub: mixin(BinOpMixin!"-");
984 case Op.mul: mixin(BinOpMixin!"*");
985 case Op.mod: mixin(BinOpMixin!("%", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
986 case Op.div: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
987 case Op.rdiv: mixin(BinOpMixin!("/", q{ if (o1 == 0) runtimeError(cast(uint)(cptr-code.ptr-1), "division by zero"); }));
988 case Op.bor: mixin(BinIOpMixin!"|");
989 case Op.bxor: mixin(BinIOpMixin!"^");
990 case Op.band: mixin(BinIOpMixin!"&");
991 case Op.shl: mixin(BinIOpMixin!"<<");
992 case Op.shr: mixin(BinIOpMixin!">>");
994 case Op.lt: mixin(BinCmpMixin!"<");
995 case Op.le: mixin(BinCmpMixin!"<=");
996 case Op.gt: mixin(BinCmpMixin!">");
997 case Op.ge: mixin(BinCmpMixin!">=");
998 case Op.eq: mixin(BinCmpMixin!"==");
999 case Op.ne: mixin(BinCmpMixin!"!=");
1001 case Op.lor: mixin(BinLogMixin!"||");
1002 case Op.land: mixin(BinLogMixin!"&&");
1003 case Op.lxor: assert(0);
1005 case Op.plit: // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
1006 auto dest = opx.opDest;
1007 uint idx = cast(ushort)opx.op2Byte;
1008 if (idx == ushort.max) {
1009 assert((*cptr).opCode == Op.skip);
1010 idx = (*cptr++).op3Byte;
1012 bp[dest] = vpool.ptr[idx];
1013 break;
1014 case Op.ilit: // dest becomes ilit val (val: short) -- load small integer literal
1015 auto dest = opx.opDest;
1016 bp[dest] = opx.opILit;
1017 break;
1018 case Op.xlit: // dest becomes integer(!) val (val: short) -- load small integer literal
1019 auto dest = opx.opDest;
1020 *cast(uint*)(bp+dest) = opx.opILit;
1021 break;
1023 case Op.jump: // addr: 3 bytes
1024 cptr = code.ptr+opx.op3Byte;
1025 break;
1026 case Op.xtrue: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
1027 if (lrint(bp[opx.opDest]) != 0) ++cptr;
1028 break;
1029 case Op.xfalse: // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
1030 if (lrint(bp[opx.opDest]) == 0) ++cptr;
1031 break;
1033 case Op.call: // dest is result; op0: call frame (see below); op1: number of args
1034 // call frame is:
1035 // new function frame
1036 // int scriptid (after op1+3 slots)
1037 // note that there should be no used registers after those (as that will be used as new function frame regs)
1038 auto sid = *cast(uint*)(bp+opx.opOp0+Slot.Argument0+opx.opOp1);
1039 if (sid >= scriptPCs.length) runtimeError(cast(uint)(cptr-code.ptr-1), "invalid script id");
1040 pc = scriptPCs.ptr[sid];
1041 if (pc < 1 || pc >= code.length) {
1042 string scname;
1043 foreach (auto kv; scripts.byKeyValue) if (kv.value == sid) { scname = kv.key; break; }
1044 runtimeError(cast(uint)(cptr-code.ptr-1), "trying to execute undefined script '", scname, "'");
1046 debug(vm_exec) {
1047 import std.stdio : stderr;
1048 stderr.writeln("calling '", scriptNum2Name[sid], "'");
1049 foreach (immutable aidx; 0..opx.opOp1) stderr.writeln(" ", bp[opx.opOp0+Slot.Argument0+aidx]);
1051 // if this is tail call, just do it as tail call then
1052 // but don't optimize out top-level call, heh
1053 if (curframe !is origcf && (*cptr).opCode == Op.ret) {
1054 import core.stdc.string : memcpy;
1055 // yay, it is a tail call!
1056 // copy arguments (it's safe to use `memcpy()` here); `self` and `other` are automatically ok
1057 if (opx.opOp1) memcpy(bp+Slot.Argument0, bp+opx.opOp0+Slot.Argument0, Real.sizeof*opx.opOp1);
1058 // simply replace current frame with new one
1059 } else {
1060 bp[opx.opOp0..opx.opOp0+Slot.Argument0] = bp[0..Slot.Argument0]; // copy `self` and `other`
1061 curframe.pc = cast(uint)(cptr-code.ptr);
1062 curframe.rval = opx.opDest;
1063 ++curframe;
1064 curframe.bp = curframe[-1].bp+opx.opOp0;
1065 bp = &stack[curframe.bp];
1067 curframe.script = sid;
1068 cptr = code.ptr+scriptPCs.ptr[sid];
1069 //assert((*cptr).opCode == Op.enter);
1070 // clear unused arguments
1071 if (opx.opOp1 < 16) bp[Slot.Argument0+opx.opOp1..Slot.Argument15+1] = 0;
1072 break;
1074 case Op.enter: // op0: number of stack slots used (including result and args); op1: number of locals
1075 if (curframe.bp+opx.opOp0 > stack.length) {
1076 stack.length = curframe.bp+opx.opOp0;
1077 bp = &stack[curframe.bp];
1079 //foreach (immutable idx; Slot.max+1..Slot.max+1+opx.opOp1) bp[idx] = 0; // clear locals
1080 if (opx.opOp1) bp[Slot.max+1..Slot.max+1+opx.opOp1] = 0; // clear locals
1081 debug(vm_exec) maxslots = opx.opOp0;
1082 debug(vm_exec) { import std.stdio : stderr; foreach (immutable idx; Slot.Argument0..Slot.Argument15+1) stderr.writeln(" :", bp[idx]); }
1083 break;
1085 case Op.ret: // dest is retvalue; it is copied to reg0; other stack items are discarded
1086 if (curframe is origcf) return bp[opx.opDest]; // done
1087 assert(cast(uint)curframe > cast(uint)origcf);
1088 --curframe;
1089 auto rv = bp[opx.opDest];
1090 // remove stack frame
1091 bp = &stack[curframe.bp];
1092 cptr = code.ptr+curframe.pc;
1093 bp[curframe.rval] = rv;
1094 debug(vm_exec) { import std.stdio : stderr; stderr.writeln("RET(", curframe.rval, "): ", rv); }
1095 break;
1097 //as we are using refloads only in the last stage of assignment, they can create values
1098 case Op.lref: // load slot reference to dest
1099 *cast(int*)bp[opx.opDest] = opx.opOp0;
1100 break;
1101 //case Op.oref: // load object reference to dest; op0: int reg (obj id; -666: global object)
1102 //case Op.fref: // load field reference; op0: varref; op1: int reg (field id); can't create fields
1103 //case Op.fcrf: // load field reference; op0: varref; op1: int reg (field id); can create field
1104 //case Op.iref: // load indexed reference; op0: varref; op1: int reg (index)
1105 //case Op.mref: // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
1107 //case Op.rload: // load from op0-varref to dest
1108 case Op.rstore: // store to op0-varref from op1
1109 auto x = *cast(int*)bp[opx.opOp0];
1110 assert(x >= 0 && x <= 255);
1111 bp[x] = bp[opx.opOp1];
1112 break;
1114 //case Op.oload: // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
1115 //case Op.iload: // load indexed (as iref)
1116 //case Op.mload: // load indexed (as mref)
1117 default: assert(0);
1124 static:
1125 enum OpArgs {
1126 None,
1127 Dest,
1128 DestOp0,
1129 DestOp0Op1,
1130 Dest2Bytes,
1131 Dest3Bytes,
1132 DestInt,
1133 DestJump,
1134 DestCall,
1135 Op0Op1,
1137 immutable OpArgs[ubyte] opargs;
1138 shared static this () {
1139 with(OpArgs) opargs = [
1140 Op.nop: None,
1141 Op.skip: None,
1142 Op.copy: DestOp0Op1,
1143 Op.lnot: DestOp0, //: lognot
1144 Op.neg: DestOp0,
1145 Op.bneg: DestOp0,
1147 Op.add: DestOp0Op1,
1148 Op.sub: DestOp0Op1,
1149 Op.mul: DestOp0Op1,
1150 Op.mod: DestOp0Op1,
1151 Op.div: DestOp0Op1,
1152 Op.rdiv: DestOp0Op1,
1153 Op.bor: DestOp0Op1,
1154 Op.bxor: DestOp0Op1,
1155 Op.band: DestOp0Op1,
1156 Op.shl: DestOp0Op1,
1157 Op.shr: DestOp0Op1,
1158 Op.lt: DestOp0Op1,
1159 Op.le: DestOp0Op1,
1160 Op.gt: DestOp0Op1,
1161 Op.ge: DestOp0Op1,
1162 Op.eq: DestOp0Op1,
1163 Op.ne: DestOp0Op1,
1164 Op.lor: DestOp0Op1,
1165 Op.land: DestOp0Op1,
1166 Op.lxor: DestOp0Op1,
1168 Op.plit: Dest2Bytes,
1169 Op.ilit: DestInt,
1170 Op.xlit: DestInt,
1172 Op.jump: DestJump,
1173 Op.xtrue: Dest,
1174 Op.xfalse: Dest,
1176 Op.call: DestCall,
1178 Op.enter: Op0Op1,
1180 Op.ret: Dest,
1182 Op.lref: DestOp0,
1183 Op.oref: DestOp0,
1184 Op.fref: DestOp0Op1,
1185 Op.fcrf: DestOp0Op1,
1186 Op.iref: DestOp0Op1,
1187 Op.mref: DestOp0Op1,
1189 Op.rload: DestOp0,
1190 Op.rstore: DestOp0,
1192 Op.oload: DestOp0Op1,
1193 Op.iload: DestOp0Op1,
1194 Op.mload: DestOp0Op1,
1197 Op.siter: DestOp0,
1198 Op.niter: DestJump,
1199 Op.kiter: Dest,
1201 Op.lirint: DestOp0, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
1207 // ////////////////////////////////////////////////////////////////////////// //
1208 private:
1209 ubyte opCode (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op&0xff); }
1210 ubyte opDest (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>8)&0xff); }
1211 ubyte opOp0 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>16)&0xff); }
1212 ubyte opOp1 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>24)&0xff); }
1213 short opILit (uint op) pure nothrow @safe @nogc { pragma(inline, true); return cast(short)((op>>16)&0xffff); }
1214 uint op3Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>8); }
1215 uint op2Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>16); }
1217 uint opMakeILit (ubyte op, byte dest, short val) pure nothrow @safe @nogc { pragma(inline, true); return ((val<<16)|((dest&0xff)<<8)|op); }
1218 uint opMake3Byte (ubyte op, uint val) pure nothrow @safe @nogc { pragma(inline, true); assert(val <= 0xffffff); return (val<<8)|op; }