OSX/iOS: Fix SDK incompatibility.
[luajit-2.0.git] / src / lj_ir.h
blobcc73a849de58ba612f6520f140e7f86b8492e91d
1 /*
2 ** SSA IR (Intermediate Representation) format.
3 ** Copyright (C) 2005-2023 Mike Pall. See Copyright Notice in luajit.h
4 */
6 #ifndef _LJ_IR_H
7 #define _LJ_IR_H
9 #include "lj_obj.h"
11 /* -- IR instructions ----------------------------------------------------- */
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) \
22 _(ULT, N , ref, ref) \
23 _(UGE, N , ref, ref) \
24 _(ULE, N , ref, ref) \
25 _(UGT, N , ref, ref) \
27 _(EQ, C , ref, ref) \
28 _(NE, C , ref, ref) \
30 _(ABC, N , ref, ref) \
31 _(RETF, S , ref, ref) \
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 _(PROF, S , ___, ___) \
45 /* Constants. */ \
46 _(KPRI, N , ___, ___) \
47 _(KINT, N , cst, ___) \
48 _(KGC, N , cst, ___) \
49 _(KPTR, N , cst, ___) \
50 _(KKPTR, N , cst, ___) \
51 _(KNULL, N , cst, ___) \
52 _(KNUM, N , cst, ___) \
53 _(KINT64, N , cst, ___) \
54 _(KSLOT, N , ref, lit) \
56 /* Bit ops. */ \
57 _(BNOT, N , ref, ___) \
58 _(BSWAP, N , ref, ___) \
59 _(BAND, C , ref, ref) \
60 _(BOR, C , ref, ref) \
61 _(BXOR, C , ref, ref) \
62 _(BSHL, N , ref, ref) \
63 _(BSHR, N , ref, ref) \
64 _(BSAR, N , ref, ref) \
65 _(BROL, N , ref, ref) \
66 _(BROR, N , ref, ref) \
68 /* Arithmetic ops. ORDER ARITH */ \
69 _(ADD, C , ref, ref) \
70 _(SUB, N , ref, ref) \
71 _(MUL, C , ref, ref) \
72 _(DIV, N , ref, ref) \
73 _(MOD, N , ref, ref) \
74 _(POW, N , ref, ref) \
75 _(NEG, N , ref, ref) \
77 _(ABS, N , ref, ref) \
78 _(LDEXP, N , ref, ref) \
79 _(MIN, N , ref, ref) \
80 _(MAX, N , ref, ref) \
81 _(FPMATH, N , ref, lit) \
83 /* Overflow-checking arithmetic ops. */ \
84 _(ADDOV, CW, ref, ref) \
85 _(SUBOV, NW, ref, ref) \
86 _(MULOV, CW, ref, ref) \
88 /* Memory ops. A = array, H = hash, U = upvalue, F = field, S = stack. */ \
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 _(TMPREF, S , ref, lit) \
99 _(STRREF, N , ref, ref) \
100 _(LREF, L , ___, ___) \
102 /* Loads and Stores. These must be in the same order. */ \
103 _(ALOAD, L , ref, ___) \
104 _(HLOAD, L , ref, ___) \
105 _(ULOAD, L , ref, ___) \
106 _(FLOAD, L , ref, lit) \
107 _(XLOAD, L , ref, lit) \
108 _(SLOAD, L , lit, lit) \
109 _(VLOAD, L , ref, lit) \
110 _(ALEN, L , ref, ref) \
112 _(ASTORE, S , ref, ref) \
113 _(HSTORE, S , ref, ref) \
114 _(USTORE, S , ref, ref) \
115 _(FSTORE, S , ref, ref) \
116 _(XSTORE, S , ref, ref) \
118 /* Allocations. */ \
119 _(SNEW, N , ref, ref) /* CSE is ok, not marked as A. */ \
120 _(XSNEW, A , ref, ref) \
121 _(TNEW, AW, lit, lit) \
122 _(TDUP, AW, ref, ___) \
123 _(CNEW, AW, ref, ref) \
124 _(CNEWI, NW, ref, ref) /* CSE is ok, not marked as A. */ \
126 /* Buffer operations. */ \
127 _(BUFHDR, L , ref, lit) \
128 _(BUFPUT, LW, ref, ref) \
129 _(BUFSTR, AW, ref, ref) \
131 /* Barriers. */ \
132 _(TBAR, S , ref, ___) \
133 _(OBAR, S , ref, ref) \
134 _(XBAR, S , ___, ___) \
136 /* Type conversions. */ \
137 _(CONV, N , ref, lit) \
138 _(TOBIT, N , ref, ref) \
139 _(TOSTR, N , ref, lit) \
140 _(STRTO, N , ref, ___) \
142 /* Calls. */ \
143 _(CALLN, NW, ref, lit) \
144 _(CALLA, AW, ref, lit) \
145 _(CALLL, LW, ref, lit) \
146 _(CALLS, S , ref, lit) \
147 _(CALLXS, S , ref, ref) \
148 _(CARG, N , ref, ref) \
150 /* End of list. */
152 /* IR opcodes (max. 256). */
153 typedef enum {
154 #define IRENUM(name, m, m1, m2) IR_##name,
155 IRDEF(IRENUM)
156 #undef IRENUM
157 IR__MAX
158 } IROp;
160 /* Stored opcode. */
161 typedef uint8_t IROp1;
163 LJ_STATIC_ASSERT(((int)IR_EQ^1) == (int)IR_NE);
164 LJ_STATIC_ASSERT(((int)IR_LT^1) == (int)IR_GE);
165 LJ_STATIC_ASSERT(((int)IR_LE^1) == (int)IR_GT);
166 LJ_STATIC_ASSERT(((int)IR_LT^3) == (int)IR_GT);
167 LJ_STATIC_ASSERT(((int)IR_LT^4) == (int)IR_ULT);
169 /* Delta between xLOAD and xSTORE. */
170 #define IRDELTA_L2S ((int)IR_ASTORE - (int)IR_ALOAD)
172 LJ_STATIC_ASSERT((int)IR_HLOAD + IRDELTA_L2S == (int)IR_HSTORE);
173 LJ_STATIC_ASSERT((int)IR_ULOAD + IRDELTA_L2S == (int)IR_USTORE);
174 LJ_STATIC_ASSERT((int)IR_FLOAD + IRDELTA_L2S == (int)IR_FSTORE);
175 LJ_STATIC_ASSERT((int)IR_XLOAD + IRDELTA_L2S == (int)IR_XSTORE);
177 /* -- Named IR literals --------------------------------------------------- */
179 /* FPMATH sub-functions. ORDER FPM. */
180 #define IRFPMDEF(_) \
181 _(FLOOR) _(CEIL) _(TRUNC) /* Must be first and in this order. */ \
182 _(SQRT) _(LOG) _(LOG2) \
183 _(OTHER)
185 typedef enum {
186 #define FPMENUM(name) IRFPM_##name,
187 IRFPMDEF(FPMENUM)
188 #undef FPMENUM
189 IRFPM__MAX
190 } IRFPMathOp;
192 /* FLOAD fields. */
193 #define IRFLDEF(_) \
194 _(STR_LEN, offsetof(GCstr, len)) \
195 _(FUNC_ENV, offsetof(GCfunc, l.env)) \
196 _(FUNC_PC, offsetof(GCfunc, l.pc)) \
197 _(FUNC_FFID, offsetof(GCfunc, l.ffid)) \
198 _(THREAD_ENV, offsetof(lua_State, env)) \
199 _(TAB_META, offsetof(GCtab, metatable)) \
200 _(TAB_ARRAY, offsetof(GCtab, array)) \
201 _(TAB_NODE, offsetof(GCtab, node)) \
202 _(TAB_ASIZE, offsetof(GCtab, asize)) \
203 _(TAB_HMASK, offsetof(GCtab, hmask)) \
204 _(TAB_NOMM, offsetof(GCtab, nomm)) \
205 _(UDATA_META, offsetof(GCudata, metatable)) \
206 _(UDATA_UDTYPE, offsetof(GCudata, udtype)) \
207 _(UDATA_FILE, sizeof(GCudata)) \
208 _(SBUF_W, sizeof(GCudata) + offsetof(SBufExt, w)) \
209 _(SBUF_E, sizeof(GCudata) + offsetof(SBufExt, e)) \
210 _(SBUF_B, sizeof(GCudata) + offsetof(SBufExt, b)) \
211 _(SBUF_L, sizeof(GCudata) + offsetof(SBufExt, L)) \
212 _(SBUF_REF, sizeof(GCudata) + offsetof(SBufExt, cowref)) \
213 _(SBUF_R, sizeof(GCudata) + offsetof(SBufExt, r)) \
214 _(CDATA_CTYPEID, offsetof(GCcdata, ctypeid)) \
215 _(CDATA_PTR, sizeof(GCcdata)) \
216 _(CDATA_INT, sizeof(GCcdata)) \
217 _(CDATA_INT64, sizeof(GCcdata)) \
218 _(CDATA_INT64_4, sizeof(GCcdata) + 4)
220 typedef enum {
221 #define FLENUM(name, ofs) IRFL_##name,
222 IRFLDEF(FLENUM)
223 #undef FLENUM
224 IRFL__MAX
225 } IRFieldID;
227 /* TMPREF mode bits, stored in op2. */
228 #define IRTMPREF_IN1 0x01 /* First input value. */
229 #define IRTMPREF_OUT1 0x02 /* First output value. */
230 #define IRTMPREF_OUT2 0x04 /* Second output value. */
232 /* SLOAD mode bits, stored in op2. */
233 #define IRSLOAD_PARENT 0x01 /* Coalesce with parent trace. */
234 #define IRSLOAD_FRAME 0x02 /* Load 32 bits of ftsz. */
235 #define IRSLOAD_TYPECHECK 0x04 /* Needs type check. */
236 #define IRSLOAD_CONVERT 0x08 /* Number to integer conversion. */
237 #define IRSLOAD_READONLY 0x10 /* Read-only, omit slot store. */
238 #define IRSLOAD_INHERIT 0x20 /* Inherited by exits/side traces. */
239 #define IRSLOAD_KEYINDEX 0x40 /* Table traversal key index. */
241 /* XLOAD mode bits, stored in op2. */
242 #define IRXLOAD_READONLY 0x01 /* Load from read-only data. */
243 #define IRXLOAD_VOLATILE 0x02 /* Load from volatile data. */
244 #define IRXLOAD_UNALIGNED 0x04 /* Unaligned load. */
246 /* BUFHDR mode, stored in op2. */
247 #define IRBUFHDR_RESET 0 /* Reset buffer. */
248 #define IRBUFHDR_APPEND 1 /* Append to buffer. */
249 #define IRBUFHDR_WRITE 2 /* Write to string buffer. */
251 /* CONV mode, stored in op2. */
252 #define IRCONV_SRCMASK 0x001f /* Source IRType. */
253 #define IRCONV_DSTMASK 0x03e0 /* Dest. IRType (also in ir->t). */
254 #define IRCONV_DSH 5
255 #define IRCONV_NUM_INT ((IRT_NUM<<IRCONV_DSH)|IRT_INT)
256 #define IRCONV_INT_NUM ((IRT_INT<<IRCONV_DSH)|IRT_NUM)
257 #define IRCONV_SEXT 0x0800 /* Sign-extend integer to integer. */
258 #define IRCONV_MODEMASK 0x0fff
259 #define IRCONV_CONVMASK 0xf000
260 #define IRCONV_CSH 12
261 /* Number to integer conversion mode. Ordered by strength of the checks. */
262 #define IRCONV_TOBIT (0<<IRCONV_CSH) /* None. Cache only: TOBIT conv. */
263 #define IRCONV_ANY (1<<IRCONV_CSH) /* Any FP number is ok. */
264 #define IRCONV_INDEX (2<<IRCONV_CSH) /* Check + special backprop rules. */
265 #define IRCONV_CHECK (3<<IRCONV_CSH) /* Number checked for integerness. */
266 #define IRCONV_NONE IRCONV_ANY /* INT|*64 no conv, but change type. */
268 /* TOSTR mode, stored in op2. */
269 #define IRTOSTR_INT 0 /* Convert integer to string. */
270 #define IRTOSTR_NUM 1 /* Convert number to string. */
271 #define IRTOSTR_CHAR 2 /* Convert char value to string. */
273 /* -- IR operands --------------------------------------------------------- */
275 /* IR operand mode (2 bit). */
276 typedef enum {
277 IRMref, /* IR reference. */
278 IRMlit, /* 16 bit unsigned literal. */
279 IRMcst, /* Constant literal: i, gcr or ptr. */
280 IRMnone /* Unused operand. */
281 } IRMode;
282 #define IRM___ IRMnone
284 /* Mode bits: Commutative, {Normal/Ref, Alloc, Load, Store}, Non-weak guard. */
285 #define IRM_C 0x10
287 #define IRM_N 0x00
288 #define IRM_R IRM_N
289 #define IRM_A 0x20
290 #define IRM_L 0x40
291 #define IRM_S 0x60
293 #define IRM_W 0x80
295 #define IRM_NW (IRM_N|IRM_W)
296 #define IRM_CW (IRM_C|IRM_W)
297 #define IRM_AW (IRM_A|IRM_W)
298 #define IRM_LW (IRM_L|IRM_W)
300 #define irm_op1(m) ((IRMode)((m)&3))
301 #define irm_op2(m) ((IRMode)(((m)>>2)&3))
302 #define irm_iscomm(m) ((m) & IRM_C)
303 #define irm_kind(m) ((m) & IRM_S)
305 #define IRMODE(name, m, m1, m2) (((IRM##m1)|((IRM##m2)<<2)|(IRM_##m))^IRM_W),
307 LJ_DATA const uint8_t lj_ir_mode[IR__MAX+1];
309 /* -- IR instruction types ------------------------------------------------ */
311 #define IRTSIZE_PGC (LJ_GC64 ? 8 : 4)
313 /* Map of itypes to non-negative numbers and their sizes. ORDER LJ_T.
314 ** LJ_TUPVAL/LJ_TTRACE never appear in a TValue. Use these itypes for
315 ** IRT_P32 and IRT_P64, which never escape the IR.
316 ** The various integers are only used in the IR and can only escape to
317 ** a TValue after implicit or explicit conversion. Their types must be
318 ** contiguous and next to IRT_NUM (see the typerange macros below).
320 #define IRTDEF(_) \
321 _(NIL, 4) _(FALSE, 4) _(TRUE, 4) _(LIGHTUD, LJ_64 ? 8 : 4) \
322 _(STR, IRTSIZE_PGC) _(P32, 4) _(THREAD, IRTSIZE_PGC) _(PROTO, IRTSIZE_PGC) \
323 _(FUNC, IRTSIZE_PGC) _(P64, 8) _(CDATA, IRTSIZE_PGC) _(TAB, IRTSIZE_PGC) \
324 _(UDATA, IRTSIZE_PGC) \
325 _(FLOAT, 4) _(NUM, 8) _(I8, 1) _(U8, 1) _(I16, 2) _(U16, 2) \
326 _(INT, 4) _(U32, 4) _(I64, 8) _(U64, 8) \
327 _(SOFTFP, 4) /* There is room for 8 more types. */
329 /* IR result type and flags (8 bit). */
330 typedef enum {
331 #define IRTENUM(name, size) IRT_##name,
332 IRTDEF(IRTENUM)
333 #undef IRTENUM
334 IRT__MAX,
336 /* Native pointer type and the corresponding integer type. */
337 IRT_PTR = LJ_64 ? IRT_P64 : IRT_P32,
338 IRT_PGC = LJ_GC64 ? IRT_P64 : IRT_P32,
339 IRT_IGC = LJ_GC64 ? IRT_I64 : IRT_INT,
340 IRT_INTP = LJ_64 ? IRT_I64 : IRT_INT,
341 IRT_UINTP = LJ_64 ? IRT_U64 : IRT_U32,
343 /* Additional flags. */
344 IRT_MARK = 0x20, /* Marker for misc. purposes. */
345 IRT_ISPHI = 0x40, /* Instruction is left or right PHI operand. */
346 IRT_GUARD = 0x80, /* Instruction is a guard. */
348 /* Masks. */
349 IRT_TYPE = 0x1f,
350 IRT_T = 0xff
351 } IRType;
353 #define irtype_ispri(irt) ((uint32_t)(irt) <= IRT_TRUE)
355 /* Stored IRType. */
356 typedef struct IRType1 { uint8_t irt; } IRType1;
358 #define IRT(o, t) ((uint32_t)(((o)<<8) | (t)))
359 #define IRTI(o) (IRT((o), IRT_INT))
360 #define IRTN(o) (IRT((o), IRT_NUM))
361 #define IRTG(o, t) (IRT((o), IRT_GUARD|(t)))
362 #define IRTGI(o) (IRT((o), IRT_GUARD|IRT_INT))
364 #define irt_t(t) ((IRType)(t).irt)
365 #define irt_type(t) ((IRType)((t).irt & IRT_TYPE))
366 #define irt_sametype(t1, t2) ((((t1).irt ^ (t2).irt) & IRT_TYPE) == 0)
367 #define irt_typerange(t, first, last) \
368 ((uint32_t)((t).irt & IRT_TYPE) - (uint32_t)(first) <= (uint32_t)(last-first))
370 #define irt_isnil(t) (irt_type(t) == IRT_NIL)
371 #define irt_ispri(t) ((uint32_t)irt_type(t) <= IRT_TRUE)
372 #define irt_islightud(t) (irt_type(t) == IRT_LIGHTUD)
373 #define irt_isstr(t) (irt_type(t) == IRT_STR)
374 #define irt_istab(t) (irt_type(t) == IRT_TAB)
375 #define irt_iscdata(t) (irt_type(t) == IRT_CDATA)
376 #define irt_isfloat(t) (irt_type(t) == IRT_FLOAT)
377 #define irt_isnum(t) (irt_type(t) == IRT_NUM)
378 #define irt_isint(t) (irt_type(t) == IRT_INT)
379 #define irt_isi8(t) (irt_type(t) == IRT_I8)
380 #define irt_isu8(t) (irt_type(t) == IRT_U8)
381 #define irt_isi16(t) (irt_type(t) == IRT_I16)
382 #define irt_isu16(t) (irt_type(t) == IRT_U16)
383 #define irt_isu32(t) (irt_type(t) == IRT_U32)
384 #define irt_isi64(t) (irt_type(t) == IRT_I64)
385 #define irt_isu64(t) (irt_type(t) == IRT_U64)
386 #define irt_isp32(t) (irt_type(t) == IRT_P32)
388 #define irt_isfp(t) (irt_isnum(t) || irt_isfloat(t))
389 #define irt_isinteger(t) (irt_typerange((t), IRT_I8, IRT_INT))
390 #define irt_isgcv(t) (irt_typerange((t), IRT_STR, IRT_UDATA))
391 #define irt_isaddr(t) (irt_typerange((t), IRT_LIGHTUD, IRT_UDATA))
392 #define irt_isint64(t) (irt_typerange((t), IRT_I64, IRT_U64))
394 #if LJ_GC64
395 /* Include IRT_NIL, so IR(ASMREF_L) (aka REF_NIL) is considered 64 bit. */
396 #define IRT_IS64 \
397 ((1u<<IRT_NUM)|(1u<<IRT_I64)|(1u<<IRT_U64)|(1u<<IRT_P64)|\
398 (1u<<IRT_LIGHTUD)|(1u<<IRT_STR)|(1u<<IRT_THREAD)|(1u<<IRT_PROTO)|\
399 (1u<<IRT_FUNC)|(1u<<IRT_CDATA)|(1u<<IRT_TAB)|(1u<<IRT_UDATA)|\
400 (1u<<IRT_NIL))
401 #elif LJ_64
402 #define IRT_IS64 \
403 ((1u<<IRT_NUM)|(1u<<IRT_I64)|(1u<<IRT_U64)|(1u<<IRT_P64)|(1u<<IRT_LIGHTUD))
404 #else
405 #define IRT_IS64 \
406 ((1u<<IRT_NUM)|(1u<<IRT_I64)|(1u<<IRT_U64))
407 #endif
409 #define irt_is64(t) ((IRT_IS64 >> irt_type(t)) & 1)
410 #define irt_is64orfp(t) (((IRT_IS64|(1u<<IRT_FLOAT))>>irt_type(t)) & 1)
412 #define irt_size(t) (lj_ir_type_size[irt_t((t))])
414 LJ_DATA const uint8_t lj_ir_type_size[];
416 static LJ_AINLINE IRType itype2irt(const TValue *tv)
418 if (tvisint(tv))
419 return IRT_INT;
420 else if (tvisnum(tv))
421 return IRT_NUM;
422 #if LJ_64 && !LJ_GC64
423 else if (tvislightud(tv))
424 return IRT_LIGHTUD;
425 #endif
426 else
427 return (IRType)~itype(tv);
430 static LJ_AINLINE uint32_t irt_toitype_(IRType t)
432 lj_assertX(!LJ_64 || LJ_GC64 || t != IRT_LIGHTUD,
433 "no plain type tag for lightuserdata");
434 if (LJ_DUALNUM && t > IRT_NUM) {
435 return LJ_TISNUM;
436 } else {
437 lj_assertX(t <= IRT_NUM, "no plain type tag for IR type %d", t);
438 return ~(uint32_t)t;
442 #define irt_toitype(t) irt_toitype_(irt_type((t)))
444 #define irt_isguard(t) ((t).irt & IRT_GUARD)
445 #define irt_ismarked(t) ((t).irt & IRT_MARK)
446 #define irt_setmark(t) ((t).irt |= IRT_MARK)
447 #define irt_clearmark(t) ((t).irt &= ~IRT_MARK)
448 #define irt_isphi(t) ((t).irt & IRT_ISPHI)
449 #define irt_setphi(t) ((t).irt |= IRT_ISPHI)
450 #define irt_clearphi(t) ((t).irt &= ~IRT_ISPHI)
452 /* Stored combined IR opcode and type. */
453 typedef uint16_t IROpT;
455 /* -- IR references ------------------------------------------------------- */
457 /* IR references. */
458 typedef uint16_t IRRef1; /* One stored reference. */
459 typedef uint32_t IRRef2; /* Two stored references. */
460 typedef uint32_t IRRef; /* Used to pass around references. */
462 /* Fixed references. */
463 enum {
464 REF_BIAS = 0x8000,
465 REF_TRUE = REF_BIAS-3,
466 REF_FALSE = REF_BIAS-2,
467 REF_NIL = REF_BIAS-1, /* \--- Constants grow downwards. */
468 REF_BASE = REF_BIAS, /* /--- IR grows upwards. */
469 REF_FIRST = REF_BIAS+1,
470 REF_DROP = 0xffff
473 /* Note: IRMlit operands must be < REF_BIAS, too!
474 ** This allows for fast and uniform manipulation of all operands
475 ** without looking up the operand mode in lj_ir_mode:
476 ** - CSE calculates the maximum reference of two operands.
477 ** This must work with mixed reference/literal operands, too.
478 ** - DCE marking only checks for operand >= REF_BIAS.
479 ** - LOOP needs to substitute reference operands.
480 ** Constant references and literals must not be modified.
483 #define IRREF2(lo, hi) ((IRRef2)(lo) | ((IRRef2)(hi) << 16))
485 #define irref_isk(ref) ((ref) < REF_BIAS)
487 /* Tagged IR references (32 bit).
489 ** +-------+-------+---------------+
490 ** | irt | flags | ref |
491 ** +-------+-------+---------------+
493 ** The tag holds a copy of the IRType and speeds up IR type checks.
495 typedef uint32_t TRef;
497 #define TREF_REFMASK 0x0000ffff
498 #define TREF_FRAME 0x00010000
499 #define TREF_CONT 0x00020000
500 #define TREF_KEYINDEX 0x00100000
502 #define TREF(ref, t) ((TRef)((ref) + ((t)<<24)))
504 #define tref_ref(tr) ((IRRef1)(tr))
505 #define tref_t(tr) ((IRType)((tr)>>24))
506 #define tref_type(tr) ((IRType)(((tr)>>24) & IRT_TYPE))
507 #define tref_typerange(tr, first, last) \
508 ((((tr)>>24) & IRT_TYPE) - (TRef)(first) <= (TRef)(last-first))
510 #define tref_istype(tr, t) (((tr) & (IRT_TYPE<<24)) == ((t)<<24))
511 #define tref_isnil(tr) (tref_istype((tr), IRT_NIL))
512 #define tref_isfalse(tr) (tref_istype((tr), IRT_FALSE))
513 #define tref_istrue(tr) (tref_istype((tr), IRT_TRUE))
514 #define tref_islightud(tr) (tref_istype((tr), IRT_LIGHTUD))
515 #define tref_isstr(tr) (tref_istype((tr), IRT_STR))
516 #define tref_isfunc(tr) (tref_istype((tr), IRT_FUNC))
517 #define tref_iscdata(tr) (tref_istype((tr), IRT_CDATA))
518 #define tref_istab(tr) (tref_istype((tr), IRT_TAB))
519 #define tref_isudata(tr) (tref_istype((tr), IRT_UDATA))
520 #define tref_isnum(tr) (tref_istype((tr), IRT_NUM))
521 #define tref_isint(tr) (tref_istype((tr), IRT_INT))
523 #define tref_isbool(tr) (tref_typerange((tr), IRT_FALSE, IRT_TRUE))
524 #define tref_ispri(tr) (tref_typerange((tr), IRT_NIL, IRT_TRUE))
525 #define tref_istruecond(tr) (!tref_typerange((tr), IRT_NIL, IRT_FALSE))
526 #define tref_isinteger(tr) (tref_typerange((tr), IRT_I8, IRT_INT))
527 #define tref_isnumber(tr) (tref_typerange((tr), IRT_NUM, IRT_INT))
528 #define tref_isnumber_str(tr) (tref_isnumber((tr)) || tref_isstr((tr)))
529 #define tref_isgcv(tr) (tref_typerange((tr), IRT_STR, IRT_UDATA))
531 #define tref_isk(tr) (irref_isk(tref_ref((tr))))
532 #define tref_isk2(tr1, tr2) (irref_isk(tref_ref((tr1) | (tr2))))
534 #define TREF_PRI(t) (TREF(REF_NIL-(t), (t)))
535 #define TREF_NIL (TREF_PRI(IRT_NIL))
536 #define TREF_FALSE (TREF_PRI(IRT_FALSE))
537 #define TREF_TRUE (TREF_PRI(IRT_TRUE))
539 /* -- IR format ----------------------------------------------------------- */
541 /* IR instruction format (64 bit).
543 ** 16 16 8 8 8 8
544 ** +-------+-------+---+---+---+---+
545 ** | op1 | op2 | t | o | r | s |
546 ** +-------+-------+---+---+---+---+
547 ** | op12/i/gco32 | ot | prev | (alternative fields in union)
548 ** +-------+-------+---+---+---+---+
549 ** | TValue/gco64 | (2nd IR slot for 64 bit constants)
550 ** +---------------+-------+-------+
551 ** 32 16 16
553 ** prev is only valid prior to register allocation and then reused for r + s.
556 typedef union IRIns {
557 struct {
558 LJ_ENDIAN_LOHI(
559 IRRef1 op1; /* IR operand 1. */
560 , IRRef1 op2; /* IR operand 2. */
562 IROpT ot; /* IR opcode and type (overlaps t and o). */
563 IRRef1 prev; /* Previous ins in same chain (overlaps r and s). */
565 struct {
566 IRRef2 op12; /* IR operand 1 and 2 (overlaps op1 and op2). */
567 LJ_ENDIAN_LOHI(
568 IRType1 t; /* IR type. */
569 , IROp1 o; /* IR opcode. */
571 LJ_ENDIAN_LOHI(
572 uint8_t r; /* Register allocation (overlaps prev). */
573 , uint8_t s; /* Spill slot allocation (overlaps prev). */
576 int32_t i; /* 32 bit signed integer literal (overlaps op12). */
577 GCRef gcr; /* GCobj constant (overlaps op12 or entire slot). */
578 MRef ptr; /* Pointer constant (overlaps op12 or entire slot). */
579 TValue tv; /* TValue constant (overlaps entire slot). */
580 } IRIns;
582 #define ir_isk64(ir) \
583 ((ir)->o == IR_KNUM || (ir)->o == IR_KINT64 || \
584 (LJ_GC64 && \
585 ((ir)->o == IR_KGC || (ir)->o == IR_KPTR || (ir)->o == IR_KKPTR)))
587 #define ir_kgc(ir) check_exp((ir)->o == IR_KGC, gcref((ir)[LJ_GC64].gcr))
588 #define ir_kstr(ir) (gco2str(ir_kgc((ir))))
589 #define ir_ktab(ir) (gco2tab(ir_kgc((ir))))
590 #define ir_kfunc(ir) (gco2func(ir_kgc((ir))))
591 #define ir_kcdata(ir) (gco2cd(ir_kgc((ir))))
592 #define ir_knum(ir) check_exp((ir)->o == IR_KNUM, &(ir)[1].tv)
593 #define ir_kint64(ir) check_exp((ir)->o == IR_KINT64, &(ir)[1].tv)
594 #define ir_k64(ir) check_exp(ir_isk64(ir), &(ir)[1].tv)
595 #define ir_kptr(ir) \
596 check_exp((ir)->o == IR_KPTR || (ir)->o == IR_KKPTR, \
597 mref((ir)[LJ_GC64].ptr, void))
599 /* A store or any other op with a non-weak guard has a side-effect. */
600 static LJ_AINLINE int ir_sideeff(IRIns *ir)
602 return (((ir->t.irt | ~IRT_GUARD) & lj_ir_mode[ir->o]) >= IRM_S);
605 LJ_STATIC_ASSERT((int)IRT_GUARD == (int)IRM_W);
607 /* Replace IR instruction with NOP. */
608 static LJ_AINLINE void lj_ir_nop(IRIns *ir)
610 ir->ot = IRT(IR_NOP, IRT_NIL);
611 ir->op1 = ir->op2 = 0;
612 ir->prev = 0;
615 #endif