Home | History | Annotate | Download | only in src
      1 /*
      2 ** $Id: lopcodes.h,v 1.142.1.1 2013/04/12 18:48:47 roberto Exp $
      3 ** Opcodes for Lua virtual machine
      4 ** See Copyright Notice in lua.h
      5 */
      6 
      7 #ifndef lopcodes_h
      8 #define lopcodes_h
      9 
     10 #include "llimits.h"
     11 
     12 
     13 /*===========================================================================
     14   We assume that instructions are unsigned numbers.
     15   All instructions have an opcode in the first 6 bits.
     16   Instructions can have the following fields:
     17 	`A' : 8 bits
     18 	`B' : 9 bits
     19 	`C' : 9 bits
     20 	'Ax' : 26 bits ('A', 'B', and 'C' together)
     21 	`Bx' : 18 bits (`B' and `C' together)
     22 	`sBx' : signed Bx
     23 
     24   A signed argument is represented in excess K; that is, the number
     25   value is the unsigned value minus K. K is exactly the maximum value
     26   for that argument (so that -max is represented by 0, and +max is
     27   represented by 2*max), which is half the maximum for the corresponding
     28   unsigned argument.
     29 ===========================================================================*/
     30 
     31 
     32 enum OpMode {iABC, iABx, iAsBx, iAx};  /* basic instruction format */
     33 
     34 
     35 /*
     36 ** size and position of opcode arguments.
     37 */
     38 #define SIZE_C		9
     39 #define SIZE_B		9
     40 #define SIZE_Bx		(SIZE_C + SIZE_B)
     41 #define SIZE_A		8
     42 #define SIZE_Ax		(SIZE_C + SIZE_B + SIZE_A)
     43 
     44 #define SIZE_OP		6
     45 
     46 #define POS_OP		0
     47 #define POS_A		(POS_OP + SIZE_OP)
     48 #define POS_C		(POS_A + SIZE_A)
     49 #define POS_B		(POS_C + SIZE_C)
     50 #define POS_Bx		POS_C
     51 #define POS_Ax		POS_A
     52 
     53 
     54 /*
     55 ** limits for opcode arguments.
     56 ** we use (signed) int to manipulate most arguments,
     57 ** so they must fit in LUAI_BITSINT-1 bits (-1 for sign)
     58 */
     59 #if SIZE_Bx < LUAI_BITSINT-1
     60 #define MAXARG_Bx        ((1<<SIZE_Bx)-1)
     61 #define MAXARG_sBx        (MAXARG_Bx>>1)         /* `sBx' is signed */
     62 #else
     63 #define MAXARG_Bx        MAX_INT
     64 #define MAXARG_sBx        MAX_INT
     65 #endif
     66 
     67 #if SIZE_Ax < LUAI_BITSINT-1
     68 #define MAXARG_Ax	((1<<SIZE_Ax)-1)
     69 #else
     70 #define MAXARG_Ax	MAX_INT
     71 #endif
     72 
     73 
     74 #define MAXARG_A        ((1<<SIZE_A)-1)
     75 #define MAXARG_B        ((1<<SIZE_B)-1)
     76 #define MAXARG_C        ((1<<SIZE_C)-1)
     77 
     78 
     79 /* creates a mask with `n' 1 bits at position `p' */
     80 #define MASK1(n,p)	((~((~(Instruction)0)<<(n)))<<(p))
     81 
     82 /* creates a mask with `n' 0 bits at position `p' */
     83 #define MASK0(n,p)	(~MASK1(n,p))
     84 
     85 /*
     86 ** the following macros help to manipulate instructions
     87 */
     88 
     89 #define GET_OPCODE(i)	(cast(OpCode, ((i)>>POS_OP) & MASK1(SIZE_OP,0)))
     90 #define SET_OPCODE(i,o)	((i) = (((i)&MASK0(SIZE_OP,POS_OP)) | \
     91 		((cast(Instruction, o)<<POS_OP)&MASK1(SIZE_OP,POS_OP))))
     92 
     93 #define getarg(i,pos,size)	(cast(int, ((i)>>pos) & MASK1(size,0)))
     94 #define setarg(i,v,pos,size)	((i) = (((i)&MASK0(size,pos)) | \
     95                 ((cast(Instruction, v)<<pos)&MASK1(size,pos))))
     96 
     97 #define GETARG_A(i)	getarg(i, POS_A, SIZE_A)
     98 #define SETARG_A(i,v)	setarg(i, v, POS_A, SIZE_A)
     99 
    100 #define GETARG_B(i)	getarg(i, POS_B, SIZE_B)
    101 #define SETARG_B(i,v)	setarg(i, v, POS_B, SIZE_B)
    102 
    103 #define GETARG_C(i)	getarg(i, POS_C, SIZE_C)
    104 #define SETARG_C(i,v)	setarg(i, v, POS_C, SIZE_C)
    105 
    106 #define GETARG_Bx(i)	getarg(i, POS_Bx, SIZE_Bx)
    107 #define SETARG_Bx(i,v)	setarg(i, v, POS_Bx, SIZE_Bx)
    108 
    109 #define GETARG_Ax(i)	getarg(i, POS_Ax, SIZE_Ax)
    110 #define SETARG_Ax(i,v)	setarg(i, v, POS_Ax, SIZE_Ax)
    111 
    112 #define GETARG_sBx(i)	(GETARG_Bx(i)-MAXARG_sBx)
    113 #define SETARG_sBx(i,b)	SETARG_Bx((i),cast(unsigned int, (b)+MAXARG_sBx))
    114 
    115 
    116 #define CREATE_ABC(o,a,b,c)	((cast(Instruction, o)<<POS_OP) \
    117 			| (cast(Instruction, a)<<POS_A) \
    118 			| (cast(Instruction, b)<<POS_B) \
    119 			| (cast(Instruction, c)<<POS_C))
    120 
    121 #define CREATE_ABx(o,a,bc)	((cast(Instruction, o)<<POS_OP) \
    122 			| (cast(Instruction, a)<<POS_A) \
    123 			| (cast(Instruction, bc)<<POS_Bx))
    124 
    125 #define CREATE_Ax(o,a)		((cast(Instruction, o)<<POS_OP) \
    126 			| (cast(Instruction, a)<<POS_Ax))
    127 
    128 
    129 /*
    130 ** Macros to operate RK indices
    131 */
    132 
    133 /* this bit 1 means constant (0 means register) */
    134 #define BITRK		(1 << (SIZE_B - 1))
    135 
    136 /* test whether value is a constant */
    137 #define ISK(x)		((x) & BITRK)
    138 
    139 /* gets the index of the constant */
    140 #define INDEXK(r)	((int)(r) & ~BITRK)
    141 
    142 #define MAXINDEXRK	(BITRK - 1)
    143 
    144 /* code a constant index as a RK value */
    145 #define RKASK(x)	((x) | BITRK)
    146 
    147 
    148 /*
    149 ** invalid register that fits in 8 bits
    150 */
    151 #define NO_REG		MAXARG_A
    152 
    153 
    154 /*
    155 ** R(x) - register
    156 ** Kst(x) - constant (in constant table)
    157 ** RK(x) == if ISK(x) then Kst(INDEXK(x)) else R(x)
    158 */
    159 
    160 
    161 /*
    162 ** grep "ORDER OP" if you change these enums
    163 */
    164 
    165 typedef enum {
    166 /*----------------------------------------------------------------------
    167 name		args	description
    168 ------------------------------------------------------------------------*/
    169 OP_MOVE,/*	A B	R(A) := R(B)					*/
    170 OP_LOADK,/*	A Bx	R(A) := Kst(Bx)					*/
    171 OP_LOADKX,/*	A 	R(A) := Kst(extra arg)				*/
    172 OP_LOADBOOL,/*	A B C	R(A) := (Bool)B; if (C) pc++			*/
    173 OP_LOADNIL,/*	A B	R(A), R(A+1), ..., R(A+B) := nil		*/
    174 OP_GETUPVAL,/*	A B	R(A) := UpValue[B]				*/
    175 
    176 OP_GETTABUP,/*	A B C	R(A) := UpValue[B][RK(C)]			*/
    177 OP_GETTABLE,/*	A B C	R(A) := R(B)[RK(C)]				*/
    178 
    179 OP_SETTABUP,/*	A B C	UpValue[A][RK(B)] := RK(C)			*/
    180 OP_SETUPVAL,/*	A B	UpValue[B] := R(A)				*/
    181 OP_SETTABLE,/*	A B C	R(A)[RK(B)] := RK(C)				*/
    182 
    183 OP_NEWTABLE,/*	A B C	R(A) := {} (size = B,C)				*/
    184 
    185 OP_SELF,/*	A B C	R(A+1) := R(B); R(A) := R(B)[RK(C)]		*/
    186 
    187 OP_ADD,/*	A B C	R(A) := RK(B) + RK(C)				*/
    188 OP_SUB,/*	A B C	R(A) := RK(B) - RK(C)				*/
    189 OP_MUL,/*	A B C	R(A) := RK(B) * RK(C)				*/
    190 OP_DIV,/*	A B C	R(A) := RK(B) / RK(C)				*/
    191 OP_MOD,/*	A B C	R(A) := RK(B) % RK(C)				*/
    192 OP_POW,/*	A B C	R(A) := RK(B) ^ RK(C)				*/
    193 OP_UNM,/*	A B	R(A) := -R(B)					*/
    194 OP_NOT,/*	A B	R(A) := not R(B)				*/
    195 OP_LEN,/*	A B	R(A) := length of R(B)				*/
    196 
    197 OP_CONCAT,/*	A B C	R(A) := R(B).. ... ..R(C)			*/
    198 
    199 OP_JMP,/*	A sBx	pc+=sBx; if (A) close all upvalues >= R(A) + 1	*/
    200 OP_EQ,/*	A B C	if ((RK(B) == RK(C)) ~= A) then pc++		*/
    201 OP_LT,/*	A B C	if ((RK(B) <  RK(C)) ~= A) then pc++		*/
    202 OP_LE,/*	A B C	if ((RK(B) <= RK(C)) ~= A) then pc++		*/
    203 
    204 OP_TEST,/*	A C	if not (R(A) <=> C) then pc++			*/
    205 OP_TESTSET,/*	A B C	if (R(B) <=> C) then R(A) := R(B) else pc++	*/
    206 
    207 OP_CALL,/*	A B C	R(A), ... ,R(A+C-2) := R(A)(R(A+1), ... ,R(A+B-1)) */
    208 OP_TAILCALL,/*	A B C	return R(A)(R(A+1), ... ,R(A+B-1))		*/
    209 OP_RETURN,/*	A B	return R(A), ... ,R(A+B-2)	(see note)	*/
    210 
    211 OP_FORLOOP,/*	A sBx	R(A)+=R(A+2);
    212 			if R(A) <?= R(A+1) then { pc+=sBx; R(A+3)=R(A) }*/
    213 OP_FORPREP,/*	A sBx	R(A)-=R(A+2); pc+=sBx				*/
    214 
    215 OP_TFORCALL,/*	A C	R(A+3), ... ,R(A+2+C) := R(A)(R(A+1), R(A+2));	*/
    216 OP_TFORLOOP,/*	A sBx	if R(A+1) ~= nil then { R(A)=R(A+1); pc += sBx }*/
    217 
    218 OP_SETLIST,/*	A B C	R(A)[(C-1)*FPF+i] := R(A+i), 1 <= i <= B	*/
    219 
    220 OP_CLOSURE,/*	A Bx	R(A) := closure(KPROTO[Bx])			*/
    221 
    222 OP_VARARG,/*	A B	R(A), R(A+1), ..., R(A+B-2) = vararg		*/
    223 
    224 OP_EXTRAARG/*	Ax	extra (larger) argument for previous opcode	*/
    225 } OpCode;
    226 
    227 
    228 #define NUM_OPCODES	(cast(int, OP_EXTRAARG) + 1)
    229 
    230 
    231 
    232 /*===========================================================================
    233   Notes:
    234   (*) In OP_CALL, if (B == 0) then B = top. If (C == 0), then `top' is
    235   set to last_result+1, so next open instruction (OP_CALL, OP_RETURN,
    236   OP_SETLIST) may use `top'.
    237 
    238   (*) In OP_VARARG, if (B == 0) then use actual number of varargs and
    239   set top (like in OP_CALL with C == 0).
    240 
    241   (*) In OP_RETURN, if (B == 0) then return up to `top'.
    242 
    243   (*) In OP_SETLIST, if (B == 0) then B = `top'; if (C == 0) then next
    244   'instruction' is EXTRAARG(real C).
    245 
    246   (*) In OP_LOADKX, the next 'instruction' is always EXTRAARG.
    247 
    248   (*) For comparisons, A specifies what condition the test should accept
    249   (true or false).
    250 
    251   (*) All `skips' (pc++) assume that next instruction is a jump.
    252 
    253 ===========================================================================*/
    254 
    255 
    256 /*
    257 ** masks for instruction properties. The format is:
    258 ** bits 0-1: op mode
    259 ** bits 2-3: C arg mode
    260 ** bits 4-5: B arg mode
    261 ** bit 6: instruction set register A
    262 ** bit 7: operator is a test (next instruction must be a jump)
    263 */
    264 
    265 enum OpArgMask {
    266   OpArgN,  /* argument is not used */
    267   OpArgU,  /* argument is used */
    268   OpArgR,  /* argument is a register or a jump offset */
    269   OpArgK   /* argument is a constant or register/constant */
    270 };
    271 
    272 LUAI_DDEC const lu_byte luaP_opmodes[NUM_OPCODES];
    273 
    274 #define getOpMode(m)	(cast(enum OpMode, luaP_opmodes[m] & 3))
    275 #define getBMode(m)	(cast(enum OpArgMask, (luaP_opmodes[m] >> 4) & 3))
    276 #define getCMode(m)	(cast(enum OpArgMask, (luaP_opmodes[m] >> 2) & 3))
    277 #define testAMode(m)	(luaP_opmodes[m] & (1 << 6))
    278 #define testTMode(m)	(luaP_opmodes[m] & (1 << 7))
    279 
    280 
    281 LUAI_DDEC const char *const luaP_opnames[NUM_OPCODES+1];  /* opcode names */
    282 
    283 
    284 /* number of list items to accumulate before a SETLIST instruction */
    285 #define LFIELDS_PER_FLUSH	50
    286 
    287 
    288 #endif
    289