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