more vm code
[gaemu.git] / gmlvm.d
blob9385060659a32fb7eeefefad97b005d6938e017d
1 module gmlvm is aliced;
3 import gmlparser;
4 import std.stdio : File;
7 enum Op {
8 nop,
10 copy, // copy regs; dest: dest reg; op0: first reg to copy; op1: number of regs to copy (0: no copy, lol)
12 lnot, //: lognot
13 neg,
14 bneg,
16 add,
17 sub,
18 mul,
19 mod,
20 div,
21 rdiv,
22 bor,
23 bxor,
24 band,
25 shl,
26 shr,
27 lt,
28 le,
29 gt,
30 ge,
31 eq,
32 ne,
33 lor,
34 land,
35 lxor,
37 plit, // dest becomes pool slot val (val: 2 bytes) -- load value from pool slot
38 ilit, // dest becomes ilit val (val: short) -- load small integer literal
39 xlit, // dest becomes integer(!) val (val: short) -- load small integer literal
41 jump, // addr: 3 bytes
42 xtrue, // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
43 xfalse, // dest is reg to check; skip next instruction if dest is "gml true" (i.e. fabs(v) >= 0.5`)
45 call, // dest is result; op0: call frame (see below); op1: number of args
46 // call frame is:
47 // new function frame (starting with return value)
48 // int scriptid (after op1+3 slots)
49 // note that there should be no used registers after those (as that will be used as new function frame regs)
51 //tcall, // same as call, but does tail call
53 prim, // call "primitive" (built-in function); dest is result; op0: call frame (see below); op1: number of args
54 // call frame is:
55 // new function frame (starting with return value)
56 // int primid (after op1+3 slots)
57 // note that there should be no used registers after those (as that will be used as new function frame regs)
59 //tprim, // same as prim, but does tail call
61 enter, // dest: number of stack slots used (including result and args)
62 // any function will ALWAYS starts with this
64 ret, // dest is retvalue; it is copied to reg0; other stack items are discarded
66 //as we are using refloads only in the last stage of assignment, they can create values
67 lref, // load var reference to dest
68 oref, // load object reference to dest; op0: int reg (obj id; -666: global object)
69 fref, // load field reference; op0: varref; op1: int reg (field id); can't create fields
70 fcrf, // load field reference; op0: varref; op1: int reg (field id); can create field
71 iref, // load indexed reference; op0: varref; op1: int reg (index)
72 mref, // load indexed reference; op0: varref; op1: int reg (first index); (op1+1): int reg (second index)
74 rload, // load from op0-varref to dest
75 rstore, // store to op0-varref from op1
77 oload, // load object field to dest; op0: int reg (obj id; -666: global object); op1: int reg (field id)
78 iload, // load indexed (as iref)
79 mload, // load indexed (as mref)
82 //`with` is done by copying `self` to another reg, execute the code and restore `self`
84 siter, // start instance iterator; dest: iterid; op0: objid or instid
85 // this is special: it will skip next instruction if iteration has at least one item
86 // next instruction is always jump, which skips the loop
87 niter, // dest is iterreg; do jump (pc is the same as in jump) if iteration is NOT complete
88 kiter, // kill iterator, should be called to prevent memory leaks
90 // so return from `with` should call kiter for all created iterators first
92 // possible iterator management: preallocate slots for each non-overlapped "with";
93 // let VM to free all iterators from those slots on function exit
95 lirint, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
99 final class VM {
100 public:
101 alias Real = float;
103 private:
104 uint[] code; // [0] is reserved
105 uint[string] scripts; // name -> number
106 uint[] scriptPCs; // by number; 0 is reserved
107 // fixuper will not remove fixup chains, so we can replace script with new one
108 Real[] vpool; // pool of values
109 string[] spool; // pool of strings
110 Real[] globals;
111 uint[string] fields; // known fields and their offsets in object (and in globals too)
113 public:
114 // value manipulation
115 static bool isReal (Real v) {
116 import std.math;
117 return !isNaN(v);
120 static bool isString (Real v) {
121 import std.math;
122 return isNaN(v);
125 static bool isUndef (Real v) {
126 import std.math;
127 return (isNaN(v) && getNaNPayload(v) < 0);
130 // creates "undefined" value
131 static Real undefValue () {
132 import std.math;
133 return NaN(-666);
136 // for invalid strings it returns 0
137 static int strId (Real v) {
138 import std.math;
139 if (isNaN(v)) {
140 auto res = getNaNPayload(v);
141 static if (is(Real == float)) {
142 return (res < 0 ? 0 : cast(int)res);
143 } else {
144 return (res < 0 || res > int.max ? 0 : cast(int)res);
146 } else {
147 return 0;
151 Real buildStrId (int id) {
152 import std.math;
153 static if (is(Real == float)) {
154 assert(id >= 0 && id <= 0x3F_FFFF);
155 } else {
156 assert(id >= 0);
158 return NaN(id);
161 public:
162 this () {
163 code.length = 1;
164 scriptPCs.length = 1;
167 void compile (NodeFunc fn) {
168 import std.stdio : stdout;
169 auto spc = code.length;
170 doCompileFunc(fn);
171 while (spc < code.length) spc += dumpInstr(stdout, spc);
174 bool isJump (uint pc) {
175 if (pc < 1 || pc >= code.length) return false;
176 switch (code[pc].opCode) {
177 case Op.jump:
178 return true;
179 default: break;
181 return false;
184 // returns instruction size
185 uint dumpInstr (File fo, uint pc) {
186 fo.writef("%08X: ", pc);
187 if (pc == 0 || pc >= code.length) {
188 fo.writeln("<INVALID>");
189 return 1;
191 auto atp = opargs[code[pc].opCode];
192 if (atp == OpArgs.None) {
193 fo.writefln("%s", cast(Op)code[pc].opCode);
194 return 1;
196 fo.writef("%-8s", cast(Op)code[pc].opCode);
197 switch (atp) with (OpArgs) {
198 case Dest: fo.writefln("dest:%s", code[pc].opDest); break;
199 case DestOp0: fo.writefln("dest:%s, op0:%s", code[pc].opDest, code[pc].opOp0); break;
200 case DestOp0Op1: fo.writefln("dest:%s, op0:%s, op1:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
201 case Dest2Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op2Byte); break;
202 case Dest3Bytes: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].op3Byte); break;
203 case DestInt: fo.writefln("dest:%s; val:%s", code[pc].opDest, code[pc].opILit); break;
204 case DestJump: fo.writefln("0x%08x", code[pc].op3Byte); break;
205 case DestCall: fo.writefln("dest:%s; frame:%s; args:%s", code[pc].opDest, code[pc].opOp0, code[pc].opOp1); break;
206 default: assert(0);
208 return 1;
211 private:
212 void doCompileFunc (NodeFunc fn) {
214 uint pc () { return cast(uint)code.length; }
216 uint emit (Op op, ubyte dest=0, ubyte op0=0, ubyte op1=0) {
217 auto res = cast(uint)code.length;
218 code ~= (op1<<24)|(op0<<16)|(dest<<8)|cast(ubyte)op;
219 return res;
222 uint emit3Bytes (Op op, uint val) {
223 assert(val <= 0xffffff);
224 auto res = cast(uint)code.length;
225 code ~= (val<<8)|cast(ubyte)op;
226 return res;
229 uint emit2Bytes (Op op, ubyte dest, short val) {
230 auto res = cast(uint)code.length;
231 code ~= (val<<16)|(dest<<8)|cast(ubyte)op;
232 return res;
235 uint emitJumpTo (Op op, uint addr) {
236 assert(addr <= 0xffffff);
237 auto res = cast(uint)code.length;
238 code ~= cast(uint)op|(addr<<8);
239 return res;
242 // this starts "jump chain", return new chain id
243 uint emitJumpChain (uint chain, Op op) {
244 assert(chain <= 0xffffff);
245 auto res = cast(uint)code.length;
246 code ~= cast(uint)op|(chain<<8);
247 return res;
250 void fixJumpChain (uint chain, uint addr) {
251 assert(chain <= 0xffffff);
252 assert(addr <= 0xffffff);
253 while (chain) {
254 auto nc = op3Byte(code[chain]);
255 code[chain] = (code[chain]&0xff)|(addr<<8);
256 chain = nc;
260 enum Slot {
261 RVal = 0,
262 Self,
263 Other,
264 Argument0,
265 Argument1,
266 Argument2,
267 Argument3,
268 Argument4,
269 Argument5,
270 Argument6,
271 Argument7,
272 Argument8,
273 Argument9,
274 Argument10,
275 Argument11,
276 Argument12,
277 Argument13,
278 Argument14,
279 Argument15,
282 assert(fn !is null);
283 assert(fn.ebody !is null);
284 assert(fn.name.length);
286 void compileError(A...) (Loc loc, A args) {
287 if (fn.pp !is null) {
288 fn.pp.error(loc, args);
289 } else {
290 import std.stdio : stderr;
291 stderr.writeln("ERROR at ", loc, ": ", args);
292 string msg;
293 foreach (immutable a; args) {
294 import std.string : format;
295 msg ~= "%s".format(a);
297 throw new ErrorAt(loc, msg);
301 bool[256] slots;
302 foreach (immutable idx; 0..Slot.max+1) slots[idx] = true; // used
303 uint firstFreeSlot = Slot.max+1;
304 uint maxUsedSlot = firstFreeSlot-1;
306 ubyte allocSlot (Loc loc, int ddest=-1) {
307 if (ddest >= 0) {
308 assert(ddest < slots.length);
309 return cast(ubyte)ddest;
311 foreach (immutable idx; firstFreeSlot..slots.length) {
312 if (!slots[idx]) {
313 if (idx > maxUsedSlot) maxUsedSlot = cast(uint)idx;
314 slots[idx] = true;
315 return cast(ubyte)idx;
318 compileError(loc, "out of free slots");
319 assert(0);
322 ubyte reserveCallSlots (Loc loc, uint resnum) {
323 foreach_reverse (immutable idx, bool v; slots) {
324 if (v) {
325 if (idx+resnum+1 > slots.length) compileError(loc, "out of free slots");
326 return cast(ubyte)(idx+1);
329 compileError(loc, "out of free slots");
330 assert(0);
333 void freeSlot (ubyte num) {
334 if (num >= firstFreeSlot) {
335 assert(slots[num]);
336 slots[num] = false;
340 ubyte[string] locals;
341 uint[string] globals;
342 Loc[string] vdecls; // for error messages
344 // collect var declarations (gml is not properly scoped)
345 visitNodes(fn.ebody, (Node n) {
346 if (auto vd = cast(NodeVarDecl)n) {
347 foreach (immutable idx, string name; vd.names) {
348 if (name in locals) {
349 if (vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
350 } else if (name in globals) {
351 if (!vd.asGlobal) compileError(vd.locs[idx], "conflicting variable '", name, "' declaration (previous at ", vdecls[name].toStringNoFile, ")");
353 vdecls[name] = vd.locs[idx];
354 if (vd.asGlobal) {
355 globals[name] = 0;
356 } else {
357 firstFreeSlot = allocSlot(vd.locs[idx]);
358 locals[name] = cast(ubyte)firstFreeSlot;
359 ++firstFreeSlot;
363 return VisitRes.Continue;
366 ushort allocNumConst (Real v) {
367 return 0;
370 ushort allocStrConst (string s) {
371 return 0;
374 // returns dest slot
375 // can put value in desired dest
376 ubyte compileExpr (Node nn, int ddest=-1, bool wantref=false) {
377 ubyte doBinOp (Op op, NodeBinary n) {
378 auto dest = allocSlot(n.loc, ddest);
379 auto o0 = compileExpr(n.el);
380 auto o1 = compileExpr(n.er);
381 emit(op, dest, o0, o1);
382 freeSlot(o0);
383 freeSlot(o1);
384 return dest;
387 ubyte doUnOp (Op op, NodeUnary n) {
388 auto dest = allocSlot(n.loc, ddest);
389 auto o0 = compileExpr(n.e);
390 emit(op, dest, o0);
391 freeSlot(o0);
392 return dest;
395 return selectNode!ubyte(nn,
396 (NodeLiteralNum n) {
397 auto dest = allocSlot(n.loc, ddest);
398 emit2Bytes(Op.plit, dest, allocNumConst(n.val));
399 return dest;
401 (NodeLiteralStr n) {
402 auto dest = allocSlot(n.loc, ddest);
403 emit2Bytes(Op.plit, dest, allocStrConst(n.val));
404 return dest;
406 (NodeUnaryParens n) => compileExpr(n.e, ddest, wantref),
407 (NodeUnaryNot n) => doUnOp(Op.lnot, n),
408 (NodeUnaryNeg n) => doUnOp(Op.neg, n),
409 (NodeUnaryBitNeg n) => doUnOp(Op.bneg, n),
410 (NodeBinaryAss n) {
411 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");
412 auto src = compileExpr(n.er);
413 auto dest = compileExpr(n.el, true);
414 emit(Op.rstore, dest, src);
415 freeSlot(src);
416 freeSlot(dest);
417 return 0;
419 (NodeBinaryAdd n) => doBinOp(Op.add, n),
420 (NodeBinarySub n) => doBinOp(Op.sub, n),
421 (NodeBinaryMul n) => doBinOp(Op.mul, n),
422 (NodeBinaryRDiv n) => doBinOp(Op.rdiv, n),
423 (NodeBinaryDiv n) => doBinOp(Op.div, n),
424 (NodeBinaryMod n) => doBinOp(Op.mod, n),
425 (NodeBinaryBitOr n) => doBinOp(Op.bor, n),
426 (NodeBinaryBitAnd n) => doBinOp(Op.band, n),
427 (NodeBinaryBitXor n) => doBinOp(Op.bxor, n),
428 (NodeBinaryLShift n) => doBinOp(Op.shl, n),
429 (NodeBinaryRShift n) => doBinOp(Op.shr, n),
430 (NodeBinaryLess n) => doBinOp(Op.lt, n),
431 (NodeBinaryLessEqu n) => doBinOp(Op.le, n),
432 (NodeBinaryGreat n) => doBinOp(Op.gt, n),
433 (NodeBinaryGreatEqu n) => doBinOp(Op.ge, n),
434 (NodeBinaryEqu n) => doBinOp(Op.eq, n),
435 (NodeBinaryNotEqu n) => doBinOp(Op.ne, n),
436 (NodeBinaryLogOr n) => doBinOp(Op.lor, n),
437 (NodeBinaryLogAnd n) => doBinOp(Op.land, n),
438 (NodeBinaryLogXor n) => doBinOp(Op.lxor, n),
439 (NodeFCall n) {
440 auto dest = allocSlot(n.loc, ddest);
441 if (auto id = cast(NodeId)n.fe) {
442 } else {
443 compileError(n.loc, "invalid function call");
445 ubyte[16] slt;
446 if (n.args.length > 16) compileError(n.loc, "too many arguments in function call");
447 foreach (immutable idx, Node a; n.args) slt[idx] = compileExpr(a);
448 auto fcs = reserveCallSlots(n.loc, cast(uint)n.args.length+Slot.Argument0+1);
450 foreach (immutable idx; 0..n.args.length) {
451 emit(Op.copy, cast(ubyte)(fcs+Slot.Argument0+idx), slt[idx], 1); //TODO: optimize
455 uint sidx = 0;
456 while (sidx < n.args.length) {
457 uint eidx = sidx+1;
458 while (eidx < n.args.length && slt[eidx] == slt[eidx-1]+1) ++eidx;
459 emit(Op.copy, cast(ubyte)(fcs+Slot.Argument0+sidx), slt[sidx], cast(ubyte)(eidx-sidx));
460 sidx = eidx;
463 foreach (immutable idx, Node a; n.args) freeSlot(slt[idx]);
464 // put script id
465 if (auto aptr = (cast(NodeId)n.fe).name in scripts) {
466 // known script
467 emit2Bytes(Op.ilit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)(*aptr));
468 } else {
469 auto snum = cast(uint)scriptPCs.length;
470 if (snum > 32767) compileError(n.loc, "too many scripts");
471 scriptPCs ~= 0;
472 scripts[(cast(NodeId)n.fe).name] = snum;
473 // unknown script
474 emit2Bytes(Op.ilit, cast(ubyte)(fcs+Slot.Argument0+n.args.length), cast(short)snum);
476 // emit call
477 emit(Op.call, dest, fcs, cast(ubyte)n.args.length);
478 return dest;
480 (NodeId n) {
481 switch (n.name) {
482 case "argument0": return cast(ubyte)(Slot.Argument0+0);
483 case "argument1": return cast(ubyte)(Slot.Argument0+1);
484 case "argument2": return cast(ubyte)(Slot.Argument0+2);
485 case "argument3": return cast(ubyte)(Slot.Argument0+3);
486 case "argument4": return cast(ubyte)(Slot.Argument0+4);
487 case "argument5": return cast(ubyte)(Slot.Argument0+5);
488 case "argument6": return cast(ubyte)(Slot.Argument0+6);
489 case "argument7": return cast(ubyte)(Slot.Argument0+7);
490 case "argument8": return cast(ubyte)(Slot.Argument0+8);
491 case "argument9": return cast(ubyte)(Slot.Argument0+9);
492 case "argument10": return cast(ubyte)(Slot.Argument0+10);
493 case "argument11": return cast(ubyte)(Slot.Argument0+11);
494 case "argument12": return cast(ubyte)(Slot.Argument0+12);
495 case "argument13": return cast(ubyte)(Slot.Argument0+13);
496 case "argument14": return cast(ubyte)(Slot.Argument0+14);
497 case "argument15": return cast(ubyte)(Slot.Argument0+15);
498 case "self": return cast(ubyte)(Slot.Self);
499 case "other": return cast(ubyte)(Slot.Other);
500 default:
502 if (auto v = n.name in locals) return *v;
503 return 0;
505 (NodeDot n) {
507 (NodeIndex n) {
508 //if (auto r = visitNodes(n.ei0, dg)) return r;
509 //if (auto r = visitNodes(n.ei1, dg)) return r;
510 //return visitNodes(n.e, dg);
512 () { assert(0, "unimplemented node: "~typeid(nn).name); },
516 void compile (Node nn) {
517 assert(nn !is null);
518 return selectNode!void(nn,
519 (NodeVarDecl n) {},
520 (NodeBlock n) {
521 foreach (Node st; n.stats) compile(st);
523 (NodeStatementEmpty n) {},
524 (NodeStatementExpr n) {
525 freeSlot(compileExpr(n.e));
527 (NodeReturn n) {
528 if (n.e is null) {
529 emit(Op.ret, Slot.RVal);
530 } else {
531 auto dest = compileExpr(n.e);
532 emit(Op.ret, dest);
533 freeSlot(dest);
536 (NodeWith n) {
537 assert(0);
539 (NodeIf n) {
540 auto cs = compileExpr(n.ec);
541 freeSlot(cs); // yep, free it here
542 emit(Op.xtrue);
543 uint jfc = 0;
544 // simple optimization
545 jfc = emitJumpChain(0, Op.jump);
546 compile(n.et);
547 if (n.ef !is null) {
548 auto exc = emitJumpChain(0, Op.jump);
549 fixJumpChain(jfc, pc);
550 jfc = exc;
551 compile(n.ef);
553 fixJumpChain(jfc, pc);
555 (NodeStatementBreak n) {
556 assert(0);
558 (NodeStatementContinue n) {
559 assert(0);
561 (NodeFor n) {
563 if (auto r = visitNodes(n.einit, dg)) return r;
564 if (auto r = visitNodes(n.econd, dg)) return r;
565 if (auto r = visitNodes(n.enext, dg)) return r;
566 return visitNodes(n.ebody, dg);
568 assert(0);
570 (NodeWhile n) {
571 assert(0);
573 (NodeDoUntil n) {
574 assert(0);
576 (NodeRepeat n) {
577 assert(0);
579 (NodeSwitch n) {
581 if (auto r = visitNodes(n.e, dg)) return r;
582 foreach (ref ci; n.cases) {
583 if (auto r = visitNodes(ci.e, dg)) return r;
584 if (auto r = visitNodes(ci.st, dg)) return r;
586 return null;
588 assert(0);
590 () { assert(0, "unimplemented node: "~typeid(nn).name); },
594 auto startpc = emit(Op.enter);
595 compile(fn.ebody);
596 emit(Op.ret);
597 // patch enter
598 code[startpc] = (maxUsedSlot<<8)|cast(ubyte)Op.enter;
599 if (fn.name !in scripts) {
600 auto snum = cast(uint)scriptPCs.length;
601 if (snum > 32767) compileError(fn.loc, "too many scripts");
602 scriptPCs ~= startpc;
603 scripts[fn.name] = snum;
607 static:
608 enum OpArgs {
609 None,
610 Dest,
611 DestOp0,
612 DestOp0Op1,
613 Dest2Bytes,
614 Dest3Bytes,
615 DestInt,
616 DestJump,
617 DestCall,
619 immutable OpArgs[ubyte] opargs;
620 shared static this () {
621 with(OpArgs) opargs = [
622 Op.nop: None,
623 Op.copy: DestOp0Op1,
624 Op.lnot: DestOp0, //: lognot
625 Op.neg: DestOp0,
626 Op.bneg: DestOp0,
628 Op.add: DestOp0Op1,
629 Op.sub: DestOp0Op1,
630 Op.mul: DestOp0Op1,
631 Op.mod: DestOp0Op1,
632 Op.div: DestOp0Op1,
633 Op.rdiv: DestOp0Op1,
634 Op.bor: DestOp0Op1,
635 Op.bxor: DestOp0Op1,
636 Op.band: DestOp0Op1,
637 Op.shl: DestOp0Op1,
638 Op.shr: DestOp0Op1,
639 Op.lt: DestOp0Op1,
640 Op.le: DestOp0Op1,
641 Op.gt: DestOp0Op1,
642 Op.ge: DestOp0Op1,
643 Op.eq: DestOp0Op1,
644 Op.ne: DestOp0Op1,
645 Op.lor: DestOp0Op1,
646 Op.land: DestOp0Op1,
647 Op.lxor: DestOp0Op1,
649 Op.plit: Dest2Bytes,
650 Op.ilit: DestInt,
651 Op.xlit: DestInt,
653 Op.jump: DestJump,
654 Op.xtrue: Dest,
655 Op.xfalse: Dest,
657 Op.call: DestCall,
658 //Op.tcall: DestCall,
660 Op.prim: DestCall,
661 //Op.tprim: DestCall,
663 Op.enter: Dest,
665 Op.ret: Dest,
667 Op.lref: DestOp0,
668 Op.oref: DestOp0,
669 Op.fref: DestOp0Op1,
670 Op.fcrf: DestOp0Op1,
671 Op.iref: DestOp0Op1,
672 Op.mref: DestOp0Op1,
674 Op.rload: DestOp0,
675 Op.rstore: DestOp0,
677 Op.oload: DestOp0Op1,
678 Op.iload: DestOp0Op1,
679 Op.mload: DestOp0Op1,
682 Op.siter: DestOp0,
683 Op.niter: DestJump,
684 Op.kiter: Dest,
686 Op.lirint: DestOp0, // dest = lrint(op0): do lrint() (or another fast float->int conversion)
692 // ////////////////////////////////////////////////////////////////////////// //
693 private:
694 ubyte opCode (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op&0xff); }
695 ubyte opDest (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>8)&0xff); }
696 ubyte opOp0 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>16)&0xff); }
697 ubyte opOp1 (uint op) pure nothrow @safe @nogc { pragma(inline, true); return ((op>>24)&0xff); }
698 short opILit (uint op) pure nothrow @safe @nogc { pragma(inline, true); return cast(short)((op>>16)&0xffff); }
699 uint op3Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>8); }
700 uint op2Byte (uint op) pure nothrow @safe @nogc { pragma(inline, true); return (op>>16); }
702 uint opMakeILit (ubyte op, byte dest, short val) pure nothrow @safe @nogc { pragma(inline, true); return ((val<<16)|((dest&0xff)<<8)|op); }
703 uint opMake3Byte (ubyte op, uint val) pure nothrow @safe @nogc { pragma(inline, true); assert(val <= 0xffffff); return (val<<8)|op; }