1 | /* |
2 | ** SSA IR (Intermediate Representation) format. |
3 | ** Copyright (C) 2005-2014 Mike Pall. See Copyright Notice in luajit.h |
4 | */ |
5 | |
6 | #ifndef _LJ_IR_H |
7 | #define _LJ_IR_H |
8 | |
9 | #include "lj_obj.h" |
10 | |
11 | /* -- IR instructions ----------------------------------------------------- */ |
12 | |
13 | /* IR instruction definition. Order matters, see below. ORDER IR */ |
14 | #define IRDEF(_) \ |
15 | /* Guarded assertions. */ \ |
16 | /* Must be properly aligned to flip opposites (^1) and (un)ordered (^4). */ \ |
17 | _(LT, N , ref, ref) \ |
18 | _(GE, N , ref, ref) \ |
19 | _(LE, N , ref, ref) \ |
20 | _(GT, N , ref, ref) \ |
21 | \ |
22 | _(ULT, N , ref, ref) \ |
23 | _(UGE, N , ref, ref) \ |
24 | _(ULE, N , ref, ref) \ |
25 | _(UGT, N , ref, ref) \ |
26 | \ |
27 | _(EQ, C , ref, ref) \ |
28 | _(NE, C , ref, ref) \ |
29 | \ |
30 | _(ABC, N , ref, ref) \ |
31 | _(RETF, S , ref, ref) \ |
32 | \ |
33 | /* Miscellaneous ops. */ \ |
34 | _(NOP, N , ___, ___) \ |
35 | _(BASE, N , lit, lit) \ |
36 | _(PVAL, N , lit, ___) \ |
37 | _(GCSTEP, S , ___, ___) \ |
38 | _(HIOP, S , ref, ref) \ |
39 | _(LOOP, S , ___, ___) \ |
40 | _(USE, S , ref, ___) \ |
41 | _(PHI, S , ref, ref) \ |
42 | _(RENAME, S , ref, lit) \ |
43 | \ |
44 | /* Constants. */ \ |
45 | _(KPRI, N , ___, ___) \ |
46 | _(KINT, N , cst, ___) \ |
47 | _(KGC, N , cst, ___) \ |
48 | _(KPTR, N , cst, ___) \ |
49 | _(KKPTR, N , cst, ___) \ |
50 | _(KNULL, N , cst, ___) \ |
51 | _(KNUM, N , cst, ___) \ |
52 | _(KINT64, N , cst, ___) \ |
53 | _(KSLOT, N , ref, lit) \ |
54 | \ |
55 | /* Bit ops. */ \ |
56 | _(BNOT, N , ref, ___) \ |
57 | _(BSWAP, N , ref, ___) \ |
58 | _(BAND, C , ref, ref) \ |
59 | _(BOR, C , ref, ref) \ |
60 | _(BXOR, C , ref, ref) \ |
61 | _(BSHL, N , ref, ref) \ |
62 | _(BSHR, N , ref, ref) \ |
63 | _(BSAR, N , ref, ref) \ |
64 | _(BROL, N , ref, ref) \ |
65 | _(BROR, N , ref, ref) \ |
66 | \ |
67 | /* Arithmetic ops. ORDER ARITH */ \ |
68 | _(ADD, C , ref, ref) \ |
69 | _(SUB, N , ref, ref) \ |
70 | _(MUL, C , ref, ref) \ |
71 | _(DIV, N , ref, ref) \ |
72 | _(MOD, N , ref, ref) \ |
73 | _(POW, N , ref, ref) \ |
74 | _(NEG, N , ref, ref) \ |
75 | \ |
76 | _(ABS, N , ref, ref) \ |
77 | _(ATAN2, N , ref, ref) \ |
78 | _(LDEXP, N , ref, ref) \ |
79 | _(MIN, C , ref, ref) \ |
80 | _(MAX, C , ref, ref) \ |
81 | _(FPMATH, N , ref, lit) \ |
82 | \ |
83 | /* Overflow-checking arithmetic ops. */ \ |
84 | _(ADDOV, CW, ref, ref) \ |
85 | _(SUBOV, NW, ref, ref) \ |
86 | _(MULOV, CW, ref, ref) \ |
87 | \ |
88 | /* Memory ops. A = array, H = hash, U = upvalue, F = field, S = stack. */ \ |
89 | \ |
90 | /* Memory references. */ \ |
91 | _(AREF, R , ref, ref) \ |
92 | _(HREFK, R , ref, ref) \ |
93 | _(HREF, L , ref, ref) \ |
94 | _(NEWREF, S , ref, ref) \ |
95 | _(UREFO, LW, ref, lit) \ |
96 | _(UREFC, LW, ref, lit) \ |
97 | _(FREF, R , ref, lit) \ |
98 | _(STRREF, N , ref, ref) \ |
99 | \ |
100 | /* Loads and Stores. These must be in the same order. */ \ |
101 | _(ALOAD, L , ref, ___) \ |
102 | _(HLOAD, L , ref, ___) \ |
103 | _(ULOAD, L , ref, ___) \ |
104 | _(FLOAD, L , ref, lit) \ |
105 | _(XLOAD, L , ref, lit) \ |
106 | _(SLOAD, L , lit, lit) \ |
107 | _(VLOAD, L , ref, ___) \ |
108 | \ |
109 | _(ASTORE, S , ref, ref) \ |
110 | _(HSTORE, S , ref, ref) \ |
111 | _(USTORE, S , ref, ref) \ |
112 | _(FSTORE, S , ref, ref) \ |
113 | _(XSTORE, S , ref, ref) \ |
114 | \ |
115 | /* Allocations. */ \ |
116 | _(SNEW, N , ref, ref) /* CSE is ok, not marked as A. */ \ |
117 | _(XSNEW, A , ref, ref) \ |
118 | _(TNEW, AW, lit, lit) \ |
119 | _(TDUP, AW, ref, ___) \ |
120 | _(CNEW, AW, ref, ref) \ |
121 | _(CNEWI, NW, ref, ref) /* CSE is ok, not marked as A. */ \ |
122 | \ |
123 | /* Barriers. */ \ |
124 | _(TBAR, S , ref, ___) \ |
125 | _(OBAR, S , ref, ref) \ |
126 | _(XBAR, S , ___, ___) \ |
127 | \ |
128 | /* Type conversions. */ \ |
129 | _(CONV, NW, ref, lit) \ |
130 | _(TOBIT, N , ref, ref) \ |
131 | _(TOSTR, N , ref, ___) \ |
132 | _(STRTO, N , ref, ___) \ |
133 | \ |
134 | /* Calls. */ \ |
135 | _(CALLN, N , ref, lit) \ |
136 | _(CALLL, L , ref, lit) \ |
137 | _(CALLS, S , ref, lit) \ |
138 | _(CALLXS, S , ref, ref) \ |
139 | _(CARG, N , ref, ref) \ |
140 | \ |
141 | /* End of list. */ |
142 | |
143 | /* IR opcodes (max. 256). */ |
144 | typedef enum { |
145 | #define IRENUM(name, m, m1, m2) IR_##name, |
146 | IRDEF(IRENUM) |
147 | #undef IRENUM |
148 | IR__MAX |
149 | } IROp; |
150 | |
151 | /* Stored opcode. */ |
152 | typedef uint8_t IROp1; |
153 | |
154 | LJ_STATIC_ASSERT(((int)IR_EQ^1) == (int)IR_NE); |
155 | LJ_STATIC_ASSERT(((int)IR_LT^1) == (int)IR_GE); |
156 | LJ_STATIC_ASSERT(((int)IR_LE^1) == (int)IR_GT); |
157 | LJ_STATIC_ASSERT(((int)IR_LT^3) == (int)IR_GT); |
158 | LJ_STATIC_ASSERT(((int)IR_LT^4) == (int)IR_ULT); |
159 | |
160 | /* Delta between xLOAD and xSTORE. */ |
161 | #define IRDELTA_L2S ((int)IR_ASTORE - (int)IR_ALOAD) |
162 | |
163 | LJ_STATIC_ASSERT((int)IR_HLOAD + IRDELTA_L2S == (int)IR_HSTORE); |
164 | LJ_STATIC_ASSERT((int)IR_ULOAD + IRDELTA_L2S == (int)IR_USTORE); |
165 | LJ_STATIC_ASSERT((int)IR_FLOAD + IRDELTA_L2S == (int)IR_FSTORE); |
166 | LJ_STATIC_ASSERT((int)IR_XLOAD + IRDELTA_L2S == (int)IR_XSTORE); |
167 | |
168 | /* -- Named IR literals --------------------------------------------------- */ |
169 | |
170 | /* FPMATH sub-functions. ORDER FPM. */ |
171 | #define IRFPMDEF(_) \ |
172 | _(FLOOR) _(CEIL) _(TRUNC) /* Must be first and in this order. */ \ |
173 | _(SQRT) _(EXP) _(EXP2) _(LOG) _(LOG2) _(LOG10) \ |
174 | _(SIN) _(COS) _(TAN) \ |
175 | _(OTHER) |
176 | |
177 | typedef enum { |
178 | #define (name) IRFPM_##name, |
179 | IRFPMDEF(FPMENUM) |
180 | #undef FPMENUM |
181 | IRFPM__MAX |
182 | } IRFPMathOp; |
183 | |
184 | /* FLOAD fields. */ |
185 | #define IRFLDEF(_) \ |
186 | _(STR_LEN, offsetof(GCstr, len)) \ |
187 | _(FUNC_ENV, offsetof(GCfunc, l.env)) \ |
188 | _(FUNC_PC, offsetof(GCfunc, l.pc)) \ |
189 | _(TAB_META, offsetof(GCtab, metatable)) \ |
190 | _(TAB_ARRAY, offsetof(GCtab, array)) \ |
191 | _(TAB_NODE, offsetof(GCtab, node)) \ |
192 | _(TAB_ASIZE, offsetof(GCtab, asize)) \ |
193 | _(TAB_HMASK, offsetof(GCtab, hmask)) \ |
194 | _(TAB_NOMM, offsetof(GCtab, nomm)) \ |
195 | _(UDATA_META, offsetof(GCudata, metatable)) \ |
196 | _(UDATA_UDTYPE, offsetof(GCudata, udtype)) \ |
197 | _(UDATA_FILE, sizeof(GCudata)) \ |
198 | _(CDATA_CTYPEID, offsetof(GCcdata, ctypeid)) \ |
199 | _(CDATA_PTR, sizeof(GCcdata)) \ |
200 | _(CDATA_INT, sizeof(GCcdata)) \ |
201 | _(CDATA_INT64, sizeof(GCcdata)) \ |
202 | _(CDATA_INT64_4, sizeof(GCcdata) + 4) |
203 | |
204 | typedef enum { |
205 | #define FLENUM(name, ofs) IRFL_##name, |
206 | IRFLDEF(FLENUM) |
207 | #undef FLENUM |
208 | IRFL__MAX |
209 | } IRFieldID; |
210 | |
211 | /* SLOAD mode bits, stored in op2. */ |
212 | #define IRSLOAD_PARENT 0x01 /* Coalesce with parent trace. */ |
213 | #define IRSLOAD_FRAME 0x02 /* Load hiword of frame. */ |
214 | #define IRSLOAD_TYPECHECK 0x04 /* Needs type check. */ |
215 | #define IRSLOAD_CONVERT 0x08 /* Number to integer conversion. */ |
216 | #define IRSLOAD_READONLY 0x10 /* Read-only, omit slot store. */ |
217 | #define IRSLOAD_INHERIT 0x20 /* Inherited by exits/side traces. */ |
218 | |
219 | /* XLOAD mode, stored in op2. */ |
220 | #define IRXLOAD_READONLY 1 /* Load from read-only data. */ |
221 | #define IRXLOAD_VOLATILE 2 /* Load from volatile data. */ |
222 | #define IRXLOAD_UNALIGNED 4 /* Unaligned load. */ |
223 | |
224 | /* CONV mode, stored in op2. */ |
225 | #define IRCONV_SRCMASK 0x001f /* Source IRType. */ |
226 | #define IRCONV_DSTMASK 0x03e0 /* Dest. IRType (also in ir->t). */ |
227 | #define IRCONV_DSH 5 |
228 | #define IRCONV_NUM_INT ((IRT_NUM<<IRCONV_DSH)|IRT_INT) |
229 | #define IRCONV_INT_NUM ((IRT_INT<<IRCONV_DSH)|IRT_NUM) |
230 | #define IRCONV_TRUNC 0x0400 /* Truncate number to integer. */ |
231 | #define IRCONV_SEXT 0x0800 /* Sign-extend integer to integer. */ |
232 | #define IRCONV_MODEMASK 0x0fff |
233 | #define IRCONV_CONVMASK 0xf000 |
234 | #define IRCONV_CSH 12 |
235 | /* Number to integer conversion mode. Ordered by strength of the checks. */ |
236 | #define IRCONV_TOBIT (0<<IRCONV_CSH) /* None. Cache only: TOBIT conv. */ |
237 | #define IRCONV_ANY (1<<IRCONV_CSH) /* Any FP number is ok. */ |
238 | #define IRCONV_INDEX (2<<IRCONV_CSH) /* Check + special backprop rules. */ |
239 | #define IRCONV_CHECK (3<<IRCONV_CSH) /* Number checked for integerness. */ |
240 | |
241 | /* -- IR operands --------------------------------------------------------- */ |
242 | |
243 | /* IR operand mode (2 bit). */ |
244 | typedef enum { |
245 | IRMref, /* IR reference. */ |
246 | IRMlit, /* 16 bit unsigned literal. */ |
247 | IRMcst, /* Constant literal: i, gcr or ptr. */ |
248 | IRMnone /* Unused operand. */ |
249 | } IRMode; |
250 | #define IRM___ IRMnone |
251 | |
252 | /* Mode bits: Commutative, {Normal/Ref, Alloc, Load, Store}, Non-weak guard. */ |
253 | #define IRM_C 0x10 |
254 | |
255 | #define IRM_N 0x00 |
256 | #define IRM_R IRM_N |
257 | #define IRM_A 0x20 |
258 | #define IRM_L 0x40 |
259 | #define IRM_S 0x60 |
260 | |
261 | #define IRM_W 0x80 |
262 | |
263 | #define IRM_NW (IRM_N|IRM_W) |
264 | #define IRM_CW (IRM_C|IRM_W) |
265 | #define IRM_AW (IRM_A|IRM_W) |
266 | #define IRM_LW (IRM_L|IRM_W) |
267 | |
268 | #define irm_op1(m) ((IRMode)((m)&3)) |
269 | #define irm_op2(m) ((IRMode)(((m)>>2)&3)) |
270 | #define irm_iscomm(m) ((m) & IRM_C) |
271 | #define irm_kind(m) ((m) & IRM_S) |
272 | |
273 | #define IRMODE(name, m, m1, m2) (((IRM##m1)|((IRM##m2)<<2)|(IRM_##m))^IRM_W), |
274 | |
275 | LJ_DATA const uint8_t lj_ir_mode[IR__MAX+1]; |
276 | |
277 | /* -- IR instruction types ------------------------------------------------ */ |
278 | |
279 | /* Map of itypes to non-negative numbers. ORDER LJ_T. |
280 | ** LJ_TUPVAL/LJ_TTRACE never appear in a TValue. Use these itypes for |
281 | ** IRT_P32 and IRT_P64, which never escape the IR. |
282 | ** The various integers are only used in the IR and can only escape to |
283 | ** a TValue after implicit or explicit conversion. Their types must be |
284 | ** contiguous and next to IRT_NUM (see the typerange macros below). |
285 | */ |
286 | #define IRTDEF(_) \ |
287 | _(NIL, 4) _(FALSE, 4) _(TRUE, 4) _(LIGHTUD, LJ_64 ? 8 : 4) _(STR, 4) \ |
288 | _(P32, 4) _(THREAD, 4) _(PROTO, 4) _(FUNC, 4) _(P64, 8) _(CDATA, 4) \ |
289 | _(TAB, 4) _(UDATA, 4) \ |
290 | _(FLOAT, 4) _(NUM, 8) _(I8, 1) _(U8, 1) _(I16, 2) _(U16, 2) \ |
291 | _(INT, 4) _(U32, 4) _(I64, 8) _(U64, 8) \ |
292 | _(SOFTFP, 4) /* There is room for 9 more types. */ |
293 | |
294 | /* IR result type and flags (8 bit). */ |
295 | typedef enum { |
296 | #define IRTENUM(name, size) IRT_##name, |
297 | IRTDEF(IRTENUM) |
298 | #undef IRTENUM |
299 | IRT__MAX, |
300 | |
301 | /* Native pointer type and the corresponding integer type. */ |
302 | IRT_PTR = LJ_64 ? IRT_P64 : IRT_P32, |
303 | IRT_INTP = LJ_64 ? IRT_I64 : IRT_INT, |
304 | IRT_UINTP = LJ_64 ? IRT_U64 : IRT_U32, |
305 | |
306 | /* Additional flags. */ |
307 | IRT_MARK = 0x20, /* Marker for misc. purposes. */ |
308 | IRT_ISPHI = 0x40, /* Instruction is left or right PHI operand. */ |
309 | IRT_GUARD = 0x80, /* Instruction is a guard. */ |
310 | |
311 | /* Masks. */ |
312 | IRT_TYPE = 0x1f, |
313 | IRT_T = 0xff |
314 | } IRType; |
315 | |
316 | #define irtype_ispri(irt) ((uint32_t)(irt) <= IRT_TRUE) |
317 | |
318 | /* Stored IRType. */ |
319 | typedef struct IRType1 { uint8_t irt; } IRType1; |
320 | |
321 | #define IRT(o, t) ((uint32_t)(((o)<<8) | (t))) |
322 | #define IRTI(o) (IRT((o), IRT_INT)) |
323 | #define IRTN(o) (IRT((o), IRT_NUM)) |
324 | #define IRTG(o, t) (IRT((o), IRT_GUARD|(t))) |
325 | #define IRTGI(o) (IRT((o), IRT_GUARD|IRT_INT)) |
326 | |
327 | #define irt_t(t) ((IRType)(t).irt) |
328 | #define irt_type(t) ((IRType)((t).irt & IRT_TYPE)) |
329 | #define irt_sametype(t1, t2) ((((t1).irt ^ (t2).irt) & IRT_TYPE) == 0) |
330 | #define irt_typerange(t, first, last) \ |
331 | ((uint32_t)((t).irt & IRT_TYPE) - (uint32_t)(first) <= (uint32_t)(last-first)) |
332 | |
333 | #define irt_isnil(t) (irt_type(t) == IRT_NIL) |
334 | #define irt_ispri(t) ((uint32_t)irt_type(t) <= IRT_TRUE) |
335 | #define irt_islightud(t) (irt_type(t) == IRT_LIGHTUD) |
336 | #define irt_isstr(t) (irt_type(t) == IRT_STR) |
337 | #define irt_istab(t) (irt_type(t) == IRT_TAB) |
338 | #define irt_iscdata(t) (irt_type(t) == IRT_CDATA) |
339 | #define irt_isfloat(t) (irt_type(t) == IRT_FLOAT) |
340 | #define irt_isnum(t) (irt_type(t) == IRT_NUM) |
341 | #define irt_isint(t) (irt_type(t) == IRT_INT) |
342 | #define irt_isi8(t) (irt_type(t) == IRT_I8) |
343 | #define irt_isu8(t) (irt_type(t) == IRT_U8) |
344 | #define irt_isi16(t) (irt_type(t) == IRT_I16) |
345 | #define irt_isu16(t) (irt_type(t) == IRT_U16) |
346 | #define irt_isu32(t) (irt_type(t) == IRT_U32) |
347 | #define irt_isi64(t) (irt_type(t) == IRT_I64) |
348 | #define irt_isu64(t) (irt_type(t) == IRT_U64) |
349 | |
350 | #define irt_isfp(t) (irt_isnum(t) || irt_isfloat(t)) |
351 | #define irt_isinteger(t) (irt_typerange((t), IRT_I8, IRT_INT)) |
352 | #define irt_isgcv(t) (irt_typerange((t), IRT_STR, IRT_UDATA)) |
353 | #define irt_isaddr(t) (irt_typerange((t), IRT_LIGHTUD, IRT_UDATA)) |
354 | #define irt_isint64(t) (irt_typerange((t), IRT_I64, IRT_U64)) |
355 | |
356 | #if LJ_64 |
357 | #define IRT_IS64 \ |
358 | ((1u<<IRT_NUM)|(1u<<IRT_I64)|(1u<<IRT_U64)|(1u<<IRT_P64)|(1u<<IRT_LIGHTUD)) |
359 | #else |
360 | #define IRT_IS64 \ |
361 | ((1u<<IRT_NUM)|(1u<<IRT_I64)|(1u<<IRT_U64)) |
362 | #endif |
363 | |
364 | #define irt_is64(t) ((IRT_IS64 >> irt_type(t)) & 1) |
365 | #define irt_is64orfp(t) (((IRT_IS64|(1u<<IRT_FLOAT))>>irt_type(t)) & 1) |
366 | |
367 | #define irt_size(t) (lj_ir_type_size[irt_t((t))]) |
368 | |
369 | LJ_DATA const uint8_t lj_ir_type_size[]; |
370 | |
371 | static LJ_AINLINE IRType itype2irt(const TValue *tv) |
372 | { |
373 | if (tvisint(tv)) |
374 | return IRT_INT; |
375 | else if (tvisnum(tv)) |
376 | return IRT_NUM; |
377 | #if LJ_64 |
378 | else if (tvislightud(tv)) |
379 | return IRT_LIGHTUD; |
380 | #endif |
381 | else |
382 | return (IRType)~itype(tv); |
383 | } |
384 | |
385 | static LJ_AINLINE uint32_t irt_toitype_(IRType t) |
386 | { |
387 | lua_assert(!LJ_64 || t != IRT_LIGHTUD); |
388 | if (LJ_DUALNUM && t > IRT_NUM) { |
389 | return LJ_TISNUM; |
390 | } else { |
391 | lua_assert(t <= IRT_NUM); |
392 | return ~(uint32_t)t; |
393 | } |
394 | } |
395 | |
396 | #define irt_toitype(t) irt_toitype_(irt_type((t))) |
397 | |
398 | #define irt_isguard(t) ((t).irt & IRT_GUARD) |
399 | #define irt_ismarked(t) ((t).irt & IRT_MARK) |
400 | #define irt_setmark(t) ((t).irt |= IRT_MARK) |
401 | #define irt_clearmark(t) ((t).irt &= ~IRT_MARK) |
402 | #define irt_isphi(t) ((t).irt & IRT_ISPHI) |
403 | #define irt_setphi(t) ((t).irt |= IRT_ISPHI) |
404 | #define irt_clearphi(t) ((t).irt &= ~IRT_ISPHI) |
405 | |
406 | /* Stored combined IR opcode and type. */ |
407 | typedef uint16_t IROpT; |
408 | |
409 | /* -- IR references ------------------------------------------------------- */ |
410 | |
411 | /* IR references. */ |
412 | typedef uint16_t IRRef1; /* One stored reference. */ |
413 | typedef uint32_t IRRef2; /* Two stored references. */ |
414 | typedef uint32_t IRRef; /* Used to pass around references. */ |
415 | |
416 | /* Fixed references. */ |
417 | enum { |
418 | REF_BIAS = 0x8000, |
419 | REF_TRUE = REF_BIAS-3, |
420 | REF_FALSE = REF_BIAS-2, |
421 | REF_NIL = REF_BIAS-1, /* \--- Constants grow downwards. */ |
422 | REF_BASE = REF_BIAS, /* /--- IR grows upwards. */ |
423 | REF_FIRST = REF_BIAS+1, |
424 | REF_DROP = 0xffff |
425 | }; |
426 | |
427 | /* Note: IRMlit operands must be < REF_BIAS, too! |
428 | ** This allows for fast and uniform manipulation of all operands |
429 | ** without looking up the operand mode in lj_ir_mode: |
430 | ** - CSE calculates the maximum reference of two operands. |
431 | ** This must work with mixed reference/literal operands, too. |
432 | ** - DCE marking only checks for operand >= REF_BIAS. |
433 | ** - LOOP needs to substitute reference operands. |
434 | ** Constant references and literals must not be modified. |
435 | */ |
436 | |
437 | #define IRREF2(lo, hi) ((IRRef2)(lo) | ((IRRef2)(hi) << 16)) |
438 | |
439 | #define irref_isk(ref) ((ref) < REF_BIAS) |
440 | |
441 | /* Tagged IR references (32 bit). |
442 | ** |
443 | ** +-------+-------+---------------+ |
444 | ** | irt | flags | ref | |
445 | ** +-------+-------+---------------+ |
446 | ** |
447 | ** The tag holds a copy of the IRType and speeds up IR type checks. |
448 | */ |
449 | typedef uint32_t TRef; |
450 | |
451 | #define TREF_REFMASK 0x0000ffff |
452 | #define TREF_FRAME 0x00010000 |
453 | #define TREF_CONT 0x00020000 |
454 | |
455 | #define TREF(ref, t) ((TRef)((ref) + ((t)<<24))) |
456 | |
457 | #define tref_ref(tr) ((IRRef1)(tr)) |
458 | #define tref_t(tr) ((IRType)((tr)>>24)) |
459 | #define tref_type(tr) ((IRType)(((tr)>>24) & IRT_TYPE)) |
460 | #define tref_typerange(tr, first, last) \ |
461 | ((((tr)>>24) & IRT_TYPE) - (TRef)(first) <= (TRef)(last-first)) |
462 | |
463 | #define tref_istype(tr, t) (((tr) & (IRT_TYPE<<24)) == ((t)<<24)) |
464 | #define tref_isnil(tr) (tref_istype((tr), IRT_NIL)) |
465 | #define tref_isfalse(tr) (tref_istype((tr), IRT_FALSE)) |
466 | #define tref_istrue(tr) (tref_istype((tr), IRT_TRUE)) |
467 | #define tref_isstr(tr) (tref_istype((tr), IRT_STR)) |
468 | #define tref_isfunc(tr) (tref_istype((tr), IRT_FUNC)) |
469 | #define tref_iscdata(tr) (tref_istype((tr), IRT_CDATA)) |
470 | #define tref_istab(tr) (tref_istype((tr), IRT_TAB)) |
471 | #define tref_isudata(tr) (tref_istype((tr), IRT_UDATA)) |
472 | #define tref_isnum(tr) (tref_istype((tr), IRT_NUM)) |
473 | #define tref_isint(tr) (tref_istype((tr), IRT_INT)) |
474 | |
475 | #define tref_isbool(tr) (tref_typerange((tr), IRT_FALSE, IRT_TRUE)) |
476 | #define tref_ispri(tr) (tref_typerange((tr), IRT_NIL, IRT_TRUE)) |
477 | #define tref_istruecond(tr) (!tref_typerange((tr), IRT_NIL, IRT_FALSE)) |
478 | #define tref_isinteger(tr) (tref_typerange((tr), IRT_I8, IRT_INT)) |
479 | #define tref_isnumber(tr) (tref_typerange((tr), IRT_NUM, IRT_INT)) |
480 | #define tref_isnumber_str(tr) (tref_isnumber((tr)) || tref_isstr((tr))) |
481 | #define tref_isgcv(tr) (tref_typerange((tr), IRT_STR, IRT_UDATA)) |
482 | |
483 | #define tref_isk(tr) (irref_isk(tref_ref((tr)))) |
484 | #define tref_isk2(tr1, tr2) (irref_isk(tref_ref((tr1) | (tr2)))) |
485 | |
486 | #define TREF_PRI(t) (TREF(REF_NIL-(t), (t))) |
487 | #define TREF_NIL (TREF_PRI(IRT_NIL)) |
488 | #define TREF_FALSE (TREF_PRI(IRT_FALSE)) |
489 | #define TREF_TRUE (TREF_PRI(IRT_TRUE)) |
490 | |
491 | /* -- IR format ----------------------------------------------------------- */ |
492 | |
493 | /* IR instruction format (64 bit). |
494 | ** |
495 | ** 16 16 8 8 8 8 |
496 | ** +-------+-------+---+---+---+---+ |
497 | ** | op1 | op2 | t | o | r | s | |
498 | ** +-------+-------+---+---+---+---+ |
499 | ** | op12/i/gco | ot | prev | (alternative fields in union) |
500 | ** +---------------+-------+-------+ |
501 | ** 32 16 16 |
502 | ** |
503 | ** prev is only valid prior to register allocation and then reused for r + s. |
504 | */ |
505 | |
506 | typedef union IRIns { |
507 | struct { |
508 | LJ_ENDIAN_LOHI( |
509 | IRRef1 op1; /* IR operand 1. */ |
510 | , IRRef1 op2; /* IR operand 2. */ |
511 | ) |
512 | IROpT ot; /* IR opcode and type (overlaps t and o). */ |
513 | IRRef1 prev; /* Previous ins in same chain (overlaps r and s). */ |
514 | }; |
515 | struct { |
516 | IRRef2 op12; /* IR operand 1 and 2 (overlaps op1 and op2). */ |
517 | LJ_ENDIAN_LOHI( |
518 | IRType1 t; /* IR type. */ |
519 | , IROp1 o; /* IR opcode. */ |
520 | ) |
521 | LJ_ENDIAN_LOHI( |
522 | uint8_t r; /* Register allocation (overlaps prev). */ |
523 | , uint8_t s; /* Spill slot allocation (overlaps prev). */ |
524 | ) |
525 | }; |
526 | int32_t i; /* 32 bit signed integer literal (overlaps op12). */ |
527 | GCRef gcr; /* GCobj constant (overlaps op12). */ |
528 | MRef ptr; /* Pointer constant (overlaps op12). */ |
529 | } IRIns; |
530 | |
531 | #define ir_kgc(ir) check_exp((ir)->o == IR_KGC, gcref((ir)->gcr)) |
532 | #define ir_kstr(ir) (gco2str(ir_kgc((ir)))) |
533 | #define ir_ktab(ir) (gco2tab(ir_kgc((ir)))) |
534 | #define ir_kfunc(ir) (gco2func(ir_kgc((ir)))) |
535 | #define ir_kcdata(ir) (gco2cd(ir_kgc((ir)))) |
536 | #define ir_knum(ir) check_exp((ir)->o == IR_KNUM, mref((ir)->ptr, cTValue)) |
537 | #define ir_kint64(ir) check_exp((ir)->o == IR_KINT64, mref((ir)->ptr,cTValue)) |
538 | #define ir_k64(ir) \ |
539 | check_exp((ir)->o == IR_KNUM || (ir)->o == IR_KINT64, mref((ir)->ptr,cTValue)) |
540 | #define ir_kptr(ir) \ |
541 | check_exp((ir)->o == IR_KPTR || (ir)->o == IR_KKPTR, mref((ir)->ptr, void)) |
542 | |
543 | /* A store or any other op with a non-weak guard has a side-effect. */ |
544 | static LJ_AINLINE int ir_sideeff(IRIns *ir) |
545 | { |
546 | return (((ir->t.irt | ~IRT_GUARD) & lj_ir_mode[ir->o]) >= IRM_S); |
547 | } |
548 | |
549 | LJ_STATIC_ASSERT((int)IRT_GUARD == (int)IRM_W); |
550 | |
551 | #endif |
552 | |