Annotation of embedaddon/pcre/sljit/sljitNativeARM_Thumb2.c, revision 1.1.1.4

1.1       misho       1: /*
                      2:  *    Stack-less Just-In-Time compiler
                      3:  *
1.1.1.2   misho       4:  *    Copyright 2009-2012 Zoltan Herczeg (hzmester@freemail.hu). All rights reserved.
1.1       misho       5:  *
                      6:  * Redistribution and use in source and binary forms, with or without modification, are
                      7:  * permitted provided that the following conditions are met:
                      8:  *
                      9:  *   1. Redistributions of source code must retain the above copyright notice, this list of
                     10:  *      conditions and the following disclaimer.
                     11:  *
                     12:  *   2. Redistributions in binary form must reproduce the above copyright notice, this list
                     13:  *      of conditions and the following disclaimer in the documentation and/or other materials
                     14:  *      provided with the distribution.
                     15:  *
                     16:  * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDER(S) AND CONTRIBUTORS ``AS IS'' AND ANY
                     17:  * EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
                     18:  * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT
                     19:  * SHALL THE COPYRIGHT HOLDER(S) OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
                     20:  * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED
                     21:  * TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR
                     22:  * BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
                     23:  * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
                     24:  * ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
                     25:  */
                     26: 
1.1.1.4 ! misho      27: SLJIT_API_FUNC_ATTRIBUTE SLJIT_CONST char* sljit_get_platform_name(void)
1.1       misho      28: {
1.1.1.2   misho      29:        return "ARM-Thumb2" SLJIT_CPUINFO;
1.1       misho      30: }
                     31: 
1.1.1.4 ! misho      32: /* Length of an instruction word. */
        !            33: typedef sljit_ui sljit_ins;
        !            34: 
1.1       misho      35: /* Last register + 1. */
                     36: #define TMP_REG1       (SLJIT_NO_REGISTERS + 1)
                     37: #define TMP_REG2       (SLJIT_NO_REGISTERS + 2)
                     38: #define TMP_REG3       (SLJIT_NO_REGISTERS + 3)
                     39: #define TMP_PC         (SLJIT_NO_REGISTERS + 4)
                     40: 
1.1.1.4 ! misho      41: #define TMP_FREG1      (0)
        !            42: #define TMP_FREG2      (SLJIT_FLOAT_REG6 + 1)
1.1       misho      43: 
1.1.1.2   misho      44: /* See sljit_emit_enter and sljit_emit_op0 if you want to change them. */
1.1       misho      45: static SLJIT_CONST sljit_ub reg_map[SLJIT_NO_REGISTERS + 5] = {
1.1.1.4 ! misho      46:        0, 0, 1, 2, 12, 5, 6, 7, 8, 10, 11, 13, 3, 4, 14, 15
1.1       misho      47: };
                     48: 
                     49: #define COPY_BITS(src, from, to, bits) \
                     50:        ((from >= to ? (src >> (from - to)) : (src << (to - from))) & (((1 << bits) - 1) << to))
                     51: 
                     52: /* Thumb16 encodings. */
                     53: #define RD3(rd) (reg_map[rd])
                     54: #define RN3(rn) (reg_map[rn] << 3)
                     55: #define RM3(rm) (reg_map[rm] << 6)
                     56: #define RDN3(rdn) (reg_map[rdn] << 8)
                     57: #define IMM3(imm) (imm << 6)
                     58: #define IMM8(imm) (imm)
                     59: 
                     60: /* Thumb16 helpers. */
                     61: #define SET_REGS44(rd, rn) \
                     62:        ((reg_map[rn] << 3) | (reg_map[rd] & 0x7) | ((reg_map[rd] & 0x8) << 4))
                     63: #define IS_2_LO_REGS(reg1, reg2) \
                     64:        (reg_map[reg1] <= 7 && reg_map[reg2] <= 7)
                     65: #define IS_3_LO_REGS(reg1, reg2, reg3) \
                     66:        (reg_map[reg1] <= 7 && reg_map[reg2] <= 7 && reg_map[reg3] <= 7)
                     67: 
                     68: /* Thumb32 encodings. */
                     69: #define RD4(rd) (reg_map[rd] << 8)
                     70: #define RN4(rn) (reg_map[rn] << 16)
                     71: #define RM4(rm) (reg_map[rm])
                     72: #define RT4(rt) (reg_map[rt] << 12)
                     73: #define DD4(dd) ((dd) << 12)
                     74: #define DN4(dn) ((dn) << 16)
                     75: #define DM4(dm) (dm)
                     76: #define IMM5(imm) \
                     77:        (COPY_BITS(imm, 2, 12, 3) | ((imm & 0x3) << 6))
                     78: #define IMM12(imm) \
                     79:        (COPY_BITS(imm, 11, 26, 1) | COPY_BITS(imm, 8, 12, 3) | (imm & 0xff))
                     80: 
                     81: /* --------------------------------------------------------------------- */
                     82: /*  Instrucion forms                                                     */
                     83: /* --------------------------------------------------------------------- */
                     84: 
                     85: /* dot '.' changed to _
                     86:    I immediate form (possibly followed by number of immediate bits). */
                     87: #define ADCI           0xf1400000
                     88: #define ADCS           0x4140
                     89: #define ADC_W          0xeb400000
                     90: #define ADD            0x4400
                     91: #define ADDS           0x1800
                     92: #define ADDSI3         0x1c00
                     93: #define ADDSI8         0x3000
                     94: #define ADD_W          0xeb000000
                     95: #define ADDWI          0xf2000000
                     96: #define ADD_SP         0xb000
                     97: #define ADD_W          0xeb000000
                     98: #define ADD_WI         0xf1000000
                     99: #define ANDI           0xf0000000
                    100: #define ANDS           0x4000
                    101: #define AND_W          0xea000000
                    102: #define ASRS           0x4100
                    103: #define ASRSI          0x1000
                    104: #define ASR_W          0xfa40f000
                    105: #define ASR_WI         0xea4f0020
                    106: #define BICI           0xf0200000
                    107: #define BKPT           0xbe00
                    108: #define BLX            0x4780
                    109: #define BX             0x4700
                    110: #define CLZ            0xfab0f080
                    111: #define CMPI           0x2800
                    112: #define CMP_W          0xebb00f00
                    113: #define EORI           0xf0800000
                    114: #define EORS           0x4040
                    115: #define EOR_W          0xea800000
                    116: #define IT             0xbf00
                    117: #define LSLS           0x4080
                    118: #define LSLSI          0x0000
                    119: #define LSL_W          0xfa00f000
                    120: #define LSL_WI         0xea4f0000
                    121: #define LSRS           0x40c0
                    122: #define LSRSI          0x0800
                    123: #define LSR_W          0xfa20f000
                    124: #define LSR_WI         0xea4f0010
                    125: #define MOV            0x4600
1.1.1.2   misho     126: #define MOVS           0x0000
1.1       misho     127: #define MOVSI          0x2000
                    128: #define MOVT           0xf2c00000
                    129: #define MOVW           0xf2400000
1.1.1.2   misho     130: #define MOV_W          0xea4f0000
1.1       misho     131: #define MOV_WI         0xf04f0000
                    132: #define MUL            0xfb00f000
                    133: #define MVNS           0x43c0
                    134: #define MVN_W          0xea6f0000
                    135: #define MVN_WI         0xf06f0000
                    136: #define NOP            0xbf00
                    137: #define ORNI           0xf0600000
                    138: #define ORRI           0xf0400000
                    139: #define ORRS           0x4300
                    140: #define ORR_W          0xea400000
                    141: #define POP            0xbd00
                    142: #define POP_W          0xe8bd0000
                    143: #define PUSH           0xb500
                    144: #define PUSH_W         0xe92d0000
                    145: #define RSB_WI         0xf1c00000
                    146: #define RSBSI          0x4240
                    147: #define SBCI           0xf1600000
                    148: #define SBCS           0x4180
                    149: #define SBC_W          0xeb600000
                    150: #define SMULL          0xfb800000
                    151: #define STR_SP         0x9000
                    152: #define SUBS           0x1a00
                    153: #define SUBSI3         0x1e00
                    154: #define SUBSI8         0x3800
                    155: #define SUB_W          0xeba00000
                    156: #define SUBWI          0xf2a00000
                    157: #define SUB_SP         0xb080
                    158: #define SUB_WI         0xf1a00000
                    159: #define SXTB           0xb240
                    160: #define SXTB_W         0xfa4ff080
                    161: #define SXTH           0xb200
                    162: #define SXTH_W         0xfa0ff080
                    163: #define TST            0x4200
1.1.1.2   misho     164: #define UMULL          0xfba00000
1.1       misho     165: #define UXTB           0xb2c0
                    166: #define UXTB_W         0xfa5ff080
                    167: #define UXTH           0xb280
                    168: #define UXTH_W         0xfa1ff080
1.1.1.4 ! misho     169: #define VABS_F32       0xeeb00ac0
        !           170: #define VADD_F32       0xee300a00
        !           171: #define VCMP_F32       0xeeb40a40
        !           172: #define VDIV_F32       0xee800a00
        !           173: #define VMOV_F32       0xeeb00a40
1.1       misho     174: #define VMRS           0xeef1fa10
1.1.1.4 ! misho     175: #define VMUL_F32       0xee200a00
        !           176: #define VNEG_F32       0xeeb10a40
        !           177: #define VSTR_F32       0xed000a00
        !           178: #define VSUB_F32       0xee300a40
1.1       misho     179: 
1.1.1.4 ! misho     180: static sljit_si push_inst16(struct sljit_compiler *compiler, sljit_ins inst)
1.1       misho     181: {
                    182:        sljit_uh *ptr;
                    183:        SLJIT_ASSERT(!(inst & 0xffff0000));
                    184: 
                    185:        ptr = (sljit_uh*)ensure_buf(compiler, sizeof(sljit_uh));
                    186:        FAIL_IF(!ptr);
                    187:        *ptr = inst;
                    188:        compiler->size++;
                    189:        return SLJIT_SUCCESS;
                    190: }
                    191: 
1.1.1.4 ! misho     192: static sljit_si push_inst32(struct sljit_compiler *compiler, sljit_ins inst)
1.1       misho     193: {
                    194:        sljit_uh *ptr = (sljit_uh*)ensure_buf(compiler, sizeof(sljit_ins));
                    195:        FAIL_IF(!ptr);
                    196:        *ptr++ = inst >> 16;
                    197:        *ptr = inst;
                    198:        compiler->size += 2;
                    199:        return SLJIT_SUCCESS;
                    200: }
                    201: 
1.1.1.4 ! misho     202: static SLJIT_INLINE sljit_si emit_imm32_const(struct sljit_compiler *compiler, sljit_si dst, sljit_uw imm)
1.1       misho     203: {
                    204:        FAIL_IF(push_inst32(compiler, MOVW | RD4(dst) |
                    205:                COPY_BITS(imm, 12, 16, 4) | COPY_BITS(imm, 11, 26, 1) | COPY_BITS(imm, 8, 12, 3) | (imm & 0xff)));
                    206:        return push_inst32(compiler, MOVT | RD4(dst) |
                    207:                COPY_BITS(imm, 12 + 16, 16, 4) | COPY_BITS(imm, 11 + 16, 26, 1) | COPY_BITS(imm, 8 + 16, 12, 3) | ((imm & 0xff0000) >> 16));
                    208: }
                    209: 
                    210: static SLJIT_INLINE void modify_imm32_const(sljit_uh* inst, sljit_uw new_imm)
                    211: {
1.1.1.4 ! misho     212:        sljit_si dst = inst[1] & 0x0f00;
1.1       misho     213:        SLJIT_ASSERT(((inst[0] & 0xfbf0) == (MOVW >> 16)) && ((inst[2] & 0xfbf0) == (MOVT >> 16)) && dst == (inst[3] & 0x0f00));
                    214:        inst[0] = (MOVW >> 16) | COPY_BITS(new_imm, 12, 0, 4) | COPY_BITS(new_imm, 11, 10, 1);
                    215:        inst[1] = dst | COPY_BITS(new_imm, 8, 12, 3) | (new_imm & 0xff);
                    216:        inst[2] = (MOVT >> 16) | COPY_BITS(new_imm, 12 + 16, 0, 4) | COPY_BITS(new_imm, 11 + 16, 10, 1);
                    217:        inst[3] = dst | COPY_BITS(new_imm, 8 + 16, 12, 3) | ((new_imm & 0xff0000) >> 16);
                    218: }
                    219: 
1.1.1.4 ! misho     220: static SLJIT_INLINE sljit_si detect_jump_type(struct sljit_jump *jump, sljit_uh *code_ptr, sljit_uh *code)
1.1       misho     221: {
1.1.1.4 ! misho     222:        sljit_sw diff;
1.1       misho     223: 
                    224:        if (jump->flags & SLJIT_REWRITABLE_JUMP)
                    225:                return 0;
                    226: 
                    227:        if (jump->flags & JUMP_ADDR) {
                    228:                /* Branch to ARM code is not optimized yet. */
                    229:                if (!(jump->u.target & 0x1))
                    230:                        return 0;
1.1.1.4 ! misho     231:                diff = ((sljit_sw)jump->u.target - (sljit_sw)(code_ptr + 2)) >> 1;
1.1       misho     232:        }
                    233:        else {
                    234:                SLJIT_ASSERT(jump->flags & JUMP_LABEL);
1.1.1.4 ! misho     235:                diff = ((sljit_sw)(code + jump->u.label->size) - (sljit_sw)(code_ptr + 2)) >> 1;
1.1       misho     236:        }
                    237: 
1.1.1.4 ! misho     238:        if (jump->flags & IS_COND) {
1.1       misho     239:                SLJIT_ASSERT(!(jump->flags & IS_BL));
                    240:                if (diff <= 127 && diff >= -128) {
                    241:                        jump->flags |= B_TYPE1;
                    242:                        return 5;
                    243:                }
                    244:                if (diff <= 524287 && diff >= -524288) {
                    245:                        jump->flags |= B_TYPE2;
                    246:                        return 4;
                    247:                }
                    248:                /* +1 comes from the prefix IT instruction. */
                    249:                diff--;
                    250:                if (diff <= 8388607 && diff >= -8388608) {
                    251:                        jump->flags |= B_TYPE3;
                    252:                        return 3;
                    253:                }
                    254:        }
                    255:        else if (jump->flags & IS_BL) {
                    256:                if (diff <= 8388607 && diff >= -8388608) {
                    257:                        jump->flags |= BL_TYPE6;
                    258:                        return 3;
                    259:                }
                    260:        }
                    261:        else {
                    262:                if (diff <= 1023 && diff >= -1024) {
                    263:                        jump->flags |= B_TYPE4;
                    264:                        return 4;
                    265:                }
                    266:                if (diff <= 8388607 && diff >= -8388608) {
                    267:                        jump->flags |= B_TYPE5;
                    268:                        return 3;
                    269:                }
                    270:        }
                    271: 
                    272:        return 0;
                    273: }
                    274: 
1.1.1.4 ! misho     275: static SLJIT_INLINE void inline_set_jump_addr(sljit_uw addr, sljit_uw new_addr, sljit_si flush)
1.1       misho     276: {
                    277:        sljit_uh* inst = (sljit_uh*)addr;
                    278:        modify_imm32_const(inst, new_addr);
                    279:        if (flush) {
                    280:                SLJIT_CACHE_FLUSH(inst, inst + 3);
                    281:        }
                    282: }
                    283: 
                    284: static SLJIT_INLINE void set_jump_instruction(struct sljit_jump *jump)
                    285: {
1.1.1.4 ! misho     286:        sljit_si type = (jump->flags >> 4) & 0xf;
        !           287:        sljit_sw diff;
1.1       misho     288:        sljit_uh *jump_inst;
1.1.1.4 ! misho     289:        sljit_si s, j1, j2;
1.1       misho     290: 
                    291:        if (SLJIT_UNLIKELY(type == 0)) {
                    292:                inline_set_jump_addr(jump->addr, (jump->flags & JUMP_LABEL) ? jump->u.label->addr : jump->u.target, 0);
                    293:                return;
                    294:        }
                    295: 
                    296:        if (jump->flags & JUMP_ADDR) {
                    297:                SLJIT_ASSERT(jump->u.target & 0x1);
1.1.1.4 ! misho     298:                diff = ((sljit_sw)jump->u.target - (sljit_sw)(jump->addr + 4)) >> 1;
1.1       misho     299:        }
                    300:        else
1.1.1.4 ! misho     301:                diff = ((sljit_sw)(jump->u.label->addr) - (sljit_sw)(jump->addr + 4)) >> 1;
1.1       misho     302:        jump_inst = (sljit_uh*)jump->addr;
                    303: 
                    304:        switch (type) {
                    305:        case 1:
                    306:                /* Encoding T1 of 'B' instruction */
1.1.1.4 ! misho     307:                SLJIT_ASSERT(diff <= 127 && diff >= -128 && (jump->flags & IS_COND));
1.1       misho     308:                jump_inst[0] = 0xd000 | (jump->flags & 0xf00) | (diff & 0xff);
                    309:                return;
                    310:        case 2:
                    311:                /* Encoding T3 of 'B' instruction */
1.1.1.4 ! misho     312:                SLJIT_ASSERT(diff <= 524287 && diff >= -524288 && (jump->flags & IS_COND));
1.1       misho     313:                jump_inst[0] = 0xf000 | COPY_BITS(jump->flags, 8, 6, 4) | COPY_BITS(diff, 11, 0, 6) | COPY_BITS(diff, 19, 10, 1);
                    314:                jump_inst[1] = 0x8000 | COPY_BITS(diff, 17, 13, 1) | COPY_BITS(diff, 18, 11, 1) | (diff & 0x7ff);
                    315:                return;
                    316:        case 3:
1.1.1.4 ! misho     317:                SLJIT_ASSERT(jump->flags & IS_COND);
1.1       misho     318:                *jump_inst++ = IT | ((jump->flags >> 4) & 0xf0) | 0x8;
                    319:                diff--;
                    320:                type = 5;
                    321:                break;
                    322:        case 4:
                    323:                /* Encoding T2 of 'B' instruction */
1.1.1.4 ! misho     324:                SLJIT_ASSERT(diff <= 1023 && diff >= -1024 && !(jump->flags & IS_COND));
1.1       misho     325:                jump_inst[0] = 0xe000 | (diff & 0x7ff);
                    326:                return;
                    327:        }
                    328: 
                    329:        SLJIT_ASSERT(diff <= 8388607 && diff >= -8388608);
                    330: 
                    331:        /* Really complex instruction form for branches. */
                    332:        s = (diff >> 23) & 0x1;
                    333:        j1 = (~(diff >> 21) ^ s) & 0x1;
                    334:        j2 = (~(diff >> 22) ^ s) & 0x1;
                    335:        jump_inst[0] = 0xf000 | (s << 10) | COPY_BITS(diff, 11, 0, 10);
                    336:        jump_inst[1] = (j1 << 13) | (j2 << 11) | (diff & 0x7ff);
                    337: 
                    338:        /* The others have a common form. */
                    339:        if (type == 5) /* Encoding T4 of 'B' instruction */
                    340:                jump_inst[1] |= 0x9000;
                    341:        else if (type == 6) /* Encoding T1 of 'BL' instruction */
                    342:                jump_inst[1] |= 0xd000;
                    343:        else
                    344:                SLJIT_ASSERT_STOP();
                    345: }
                    346: 
                    347: SLJIT_API_FUNC_ATTRIBUTE void* sljit_generate_code(struct sljit_compiler *compiler)
                    348: {
                    349:        struct sljit_memory_fragment *buf;
                    350:        sljit_uh *code;
                    351:        sljit_uh *code_ptr;
                    352:        sljit_uh *buf_ptr;
                    353:        sljit_uh *buf_end;
                    354:        sljit_uw half_count;
                    355: 
                    356:        struct sljit_label *label;
                    357:        struct sljit_jump *jump;
                    358:        struct sljit_const *const_;
                    359: 
                    360:        CHECK_ERROR_PTR();
                    361:        check_sljit_generate_code(compiler);
                    362:        reverse_buf(compiler);
                    363: 
                    364:        code = (sljit_uh*)SLJIT_MALLOC_EXEC(compiler->size * sizeof(sljit_uh));
                    365:        PTR_FAIL_WITH_EXEC_IF(code);
                    366:        buf = compiler->buf;
                    367: 
                    368:        code_ptr = code;
                    369:        half_count = 0;
                    370:        label = compiler->labels;
                    371:        jump = compiler->jumps;
                    372:        const_ = compiler->consts;
                    373: 
                    374:        do {
                    375:                buf_ptr = (sljit_uh*)buf->memory;
                    376:                buf_end = buf_ptr + (buf->used_size >> 1);
                    377:                do {
                    378:                        *code_ptr = *buf_ptr++;
                    379:                        /* These structures are ordered by their address. */
                    380:                        SLJIT_ASSERT(!label || label->size >= half_count);
                    381:                        SLJIT_ASSERT(!jump || jump->addr >= half_count);
                    382:                        SLJIT_ASSERT(!const_ || const_->addr >= half_count);
                    383:                        if (label && label->size == half_count) {
                    384:                                label->addr = ((sljit_uw)code_ptr) | 0x1;
                    385:                                label->size = code_ptr - code;
                    386:                                label = label->next;
                    387:                        }
                    388:                        if (jump && jump->addr == half_count) {
1.1.1.4 ! misho     389:                                        jump->addr = (sljit_uw)code_ptr - ((jump->flags & IS_COND) ? 10 : 8);
1.1       misho     390:                                        code_ptr -= detect_jump_type(jump, code_ptr, code);
                    391:                                        jump = jump->next;
                    392:                        }
                    393:                        if (const_ && const_->addr == half_count) {
                    394:                                const_->addr = (sljit_uw)code_ptr;
                    395:                                const_ = const_->next;
                    396:                        }
                    397:                        code_ptr ++;
                    398:                        half_count ++;
                    399:                } while (buf_ptr < buf_end);
                    400: 
                    401:                buf = buf->next;
                    402:        } while (buf);
                    403: 
                    404:        if (label && label->size == half_count) {
                    405:                label->addr = ((sljit_uw)code_ptr) | 0x1;
                    406:                label->size = code_ptr - code;
                    407:                label = label->next;
                    408:        }
                    409: 
                    410:        SLJIT_ASSERT(!label);
                    411:        SLJIT_ASSERT(!jump);
                    412:        SLJIT_ASSERT(!const_);
1.1.1.4 ! misho     413:        SLJIT_ASSERT(code_ptr - code <= (sljit_sw)compiler->size);
1.1       misho     414: 
                    415:        jump = compiler->jumps;
                    416:        while (jump) {
                    417:                set_jump_instruction(jump);
                    418:                jump = jump->next;
                    419:        }
                    420: 
                    421:        compiler->error = SLJIT_ERR_COMPILED;
1.1.1.4 ! misho     422:        compiler->executable_size = (code_ptr - code) * sizeof(sljit_uh);
        !           423:        SLJIT_CACHE_FLUSH(code, code_ptr);
1.1       misho     424:        /* Set thumb mode flag. */
                    425:        return (void*)((sljit_uw)code | 0x1);
                    426: }
                    427: 
                    428: #define INVALID_IMM    0x80000000
                    429: static sljit_uw get_imm(sljit_uw imm)
                    430: {
                    431:        /* Thumb immediate form. */
1.1.1.4 ! misho     432:        sljit_si counter;
1.1       misho     433: 
                    434:        if (imm <= 0xff)
                    435:                return imm;
                    436: 
                    437:        if ((imm & 0xffff) == (imm >> 16)) {
                    438:                /* Some special cases. */
                    439:                if (!(imm & 0xff00))
                    440:                        return (1 << 12) | (imm & 0xff);
                    441:                if (!(imm & 0xff))
                    442:                        return (2 << 12) | ((imm >> 8) & 0xff);
                    443:                if ((imm & 0xff00) == ((imm & 0xff) << 8))
                    444:                        return (3 << 12) | (imm & 0xff);
                    445:        }
                    446: 
                    447:        /* Assembly optimization: count leading zeroes? */
                    448:        counter = 8;
                    449:        if (!(imm & 0xffff0000)) {
                    450:                counter += 16;
                    451:                imm <<= 16;
                    452:        }
                    453:        if (!(imm & 0xff000000)) {
                    454:                counter += 8;
                    455:                imm <<= 8;
                    456:        }
                    457:        if (!(imm & 0xf0000000)) {
                    458:                counter += 4;
                    459:                imm <<= 4;
                    460:        }
                    461:        if (!(imm & 0xc0000000)) {
                    462:                counter += 2;
                    463:                imm <<= 2;
                    464:        }
                    465:        if (!(imm & 0x80000000)) {
                    466:                counter += 1;
                    467:                imm <<= 1;
                    468:        }
                    469:        /* Since imm >= 128, this must be true. */
                    470:        SLJIT_ASSERT(counter <= 31);
                    471: 
                    472:        if (imm & 0x00ffffff)
                    473:                return INVALID_IMM; /* Cannot be encoded. */
                    474: 
                    475:        return ((imm >> 24) & 0x7f) | COPY_BITS(counter, 4, 26, 1) | COPY_BITS(counter, 1, 12, 3) | COPY_BITS(counter, 0, 7, 1);
                    476: }
                    477: 
1.1.1.4 ! misho     478: static sljit_si load_immediate(struct sljit_compiler *compiler, sljit_si dst, sljit_uw imm)
1.1       misho     479: {
                    480:        sljit_uw tmp;
                    481: 
                    482:        if (imm >= 0x10000) {
                    483:                tmp = get_imm(imm);
                    484:                if (tmp != INVALID_IMM)
                    485:                        return push_inst32(compiler, MOV_WI | RD4(dst) | tmp);
                    486:                tmp = get_imm(~imm);
                    487:                if (tmp != INVALID_IMM)
                    488:                        return push_inst32(compiler, MVN_WI | RD4(dst) | tmp);
                    489:        }
                    490: 
                    491:        /* set low 16 bits, set hi 16 bits to 0. */
                    492:        FAIL_IF(push_inst32(compiler, MOVW | RD4(dst) |
                    493:                COPY_BITS(imm, 12, 16, 4) | COPY_BITS(imm, 11, 26, 1) | COPY_BITS(imm, 8, 12, 3) | (imm & 0xff)));
                    494: 
                    495:        /* set hi 16 bit if needed. */
                    496:        if (imm >= 0x10000)
                    497:                return push_inst32(compiler, MOVT | RD4(dst) |
                    498:                        COPY_BITS(imm, 12 + 16, 16, 4) | COPY_BITS(imm, 11 + 16, 26, 1) | COPY_BITS(imm, 8 + 16, 12, 3) | ((imm & 0xff0000) >> 16));
                    499:        return SLJIT_SUCCESS;
                    500: }
                    501: 
                    502: #define ARG1_IMM       0x0010000
                    503: #define ARG2_IMM       0x0020000
                    504: #define KEEP_FLAGS     0x0040000
                    505: #define SET_MULOV      0x0080000
                    506: /* SET_FLAGS must be 0x100000 as it is also the value of S bit (can be used for optimization). */
                    507: #define SET_FLAGS      0x0100000
                    508: #define UNUSED_RETURN  0x0200000
                    509: #define SLOW_DEST      0x0400000
                    510: #define SLOW_SRC1      0x0800000
                    511: #define SLOW_SRC2      0x1000000
                    512: 
1.1.1.4 ! misho     513: static sljit_si emit_op_imm(struct sljit_compiler *compiler, sljit_si flags, sljit_si dst, sljit_uw arg1, sljit_uw arg2)
1.1       misho     514: {
                    515:        /* dst must be register, TMP_REG1
                    516:           arg1 must be register, TMP_REG1, imm
                    517:           arg2 must be register, TMP_REG2, imm */
1.1.1.4 ! misho     518:        sljit_si reg;
1.1.1.3   misho     519:        sljit_uw imm, negated_imm;
1.1       misho     520: 
                    521:        if (SLJIT_UNLIKELY((flags & (ARG1_IMM | ARG2_IMM)) == (ARG1_IMM | ARG2_IMM))) {
                    522:                /* Both are immediates. */
                    523:                flags &= ~ARG1_IMM;
                    524:                FAIL_IF(load_immediate(compiler, TMP_REG1, arg1));
                    525:                arg1 = TMP_REG1;
                    526:        }
                    527: 
                    528:        if (flags & (ARG1_IMM | ARG2_IMM)) {
                    529:                reg = (flags & ARG2_IMM) ? arg1 : arg2;
                    530:                imm = (flags & ARG2_IMM) ? arg2 : arg1;
                    531: 
                    532:                switch (flags & 0xffff) {
                    533:                case SLJIT_MOV:
                    534:                        SLJIT_ASSERT(!(flags & SET_FLAGS) && (flags & ARG2_IMM) && arg1 == TMP_REG1);
                    535:                        return load_immediate(compiler, dst, imm);
                    536:                case SLJIT_NOT:
                    537:                        if (!(flags & SET_FLAGS))
                    538:                                return load_immediate(compiler, dst, ~imm);
                    539:                        /* Since the flags should be set, we just fallback to the register mode.
                    540:                           Although I could do some clever things here, "NOT IMM" does not worth the efforts. */
                    541:                        break;
                    542:                case SLJIT_CLZ:
                    543:                        /* No form with immediate operand. */
                    544:                        break;
                    545:                case SLJIT_ADD:
1.1.1.4 ! misho     546:                        negated_imm = (sljit_uw)-(sljit_sw)imm;
1.1       misho     547:                        if (!(flags & KEEP_FLAGS) && IS_2_LO_REGS(reg, dst)) {
                    548:                                if (imm <= 0x7)
                    549:                                        return push_inst16(compiler, ADDSI3 | IMM3(imm) | RD3(dst) | RN3(reg));
1.1.1.3   misho     550:                                if (negated_imm <= 0x7)
                    551:                                        return push_inst16(compiler, SUBSI3 | IMM3(negated_imm) | RD3(dst) | RN3(reg));
                    552:                                if (reg == dst) {
                    553:                                        if (imm <= 0xff)
                    554:                                                return push_inst16(compiler, ADDSI8 | IMM8(imm) | RDN3(dst));
                    555:                                        if (negated_imm <= 0xff)
                    556:                                                return push_inst16(compiler, SUBSI8 | IMM8(negated_imm) | RDN3(dst));
                    557:                                }
                    558:                        }
                    559:                        if (!(flags & SET_FLAGS)) {
                    560:                                if (imm <= 0xfff)
                    561:                                        return push_inst32(compiler, ADDWI | RD4(dst) | RN4(reg) | IMM12(imm));
                    562:                                if (negated_imm <= 0xfff)
                    563:                                        return push_inst32(compiler, SUBWI | RD4(dst) | RN4(reg) | IMM12(negated_imm));
1.1       misho     564:                        }
                    565:                        imm = get_imm(imm);
                    566:                        if (imm != INVALID_IMM)
                    567:                                return push_inst32(compiler, ADD_WI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    568:                        break;
                    569:                case SLJIT_ADDC:
                    570:                        imm = get_imm(imm);
                    571:                        if (imm != INVALID_IMM)
                    572:                                return push_inst32(compiler, ADCI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    573:                        break;
                    574:                case SLJIT_SUB:
                    575:                        if (flags & ARG2_IMM) {
1.1.1.4 ! misho     576:                                negated_imm = (sljit_uw)-(sljit_sw)imm;
1.1       misho     577:                                if (!(flags & KEEP_FLAGS) && IS_2_LO_REGS(reg, dst)) {
                    578:                                        if (imm <= 0x7)
                    579:                                                return push_inst16(compiler, SUBSI3 | IMM3(imm) | RD3(dst) | RN3(reg));
1.1.1.3   misho     580:                                        if (negated_imm <= 0x7)
                    581:                                                return push_inst16(compiler, ADDSI3 | IMM3(negated_imm) | RD3(dst) | RN3(reg));
                    582:                                        if (reg == dst) {
                    583:                                                if (imm <= 0xff)
1.1       misho     584:                                                        return push_inst16(compiler, SUBSI8 | IMM8(imm) | RDN3(dst));
1.1.1.3   misho     585:                                                if (negated_imm <= 0xff)
                    586:                                                        return push_inst16(compiler, ADDSI8 | IMM8(negated_imm) | RDN3(dst));
1.1       misho     587:                                        }
1.1.1.3   misho     588:                                        if (imm <= 0xff && (flags & UNUSED_RETURN))
                    589:                                                return push_inst16(compiler, CMPI | IMM8(imm) | RDN3(reg));
                    590:                                }
                    591:                                if (!(flags & SET_FLAGS)) {
                    592:                                        if (imm <= 0xfff)
                    593:                                                return push_inst32(compiler, SUBWI | RD4(dst) | RN4(reg) | IMM12(imm));
                    594:                                        if (negated_imm <= 0xfff)
                    595:                                                return push_inst32(compiler, ADDWI | RD4(dst) | RN4(reg) | IMM12(negated_imm));
1.1       misho     596:                                }
                    597:                                imm = get_imm(imm);
                    598:                                if (imm != INVALID_IMM)
                    599:                                        return push_inst32(compiler, SUB_WI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    600:                        }
                    601:                        else {
                    602:                                if (!(flags & KEEP_FLAGS) && imm == 0 && IS_2_LO_REGS(reg, dst))
                    603:                                        return push_inst16(compiler, RSBSI | RD3(dst) | RN3(reg));
                    604:                                imm = get_imm(imm);
                    605:                                if (imm != INVALID_IMM)
                    606:                                        return push_inst32(compiler, RSB_WI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    607:                        }
                    608:                        break;
                    609:                case SLJIT_SUBC:
                    610:                        if (flags & ARG2_IMM) {
                    611:                                imm = get_imm(imm);
                    612:                                if (imm != INVALID_IMM)
                    613:                                        return push_inst32(compiler, SBCI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    614:                        }
                    615:                        break;
                    616:                case SLJIT_MUL:
                    617:                        /* No form with immediate operand. */
                    618:                        break;
                    619:                case SLJIT_AND:
                    620:                        imm = get_imm(imm);
                    621:                        if (imm != INVALID_IMM)
                    622:                                return push_inst32(compiler, ANDI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    623:                        imm = get_imm(~((flags & ARG2_IMM) ? arg2 : arg1));
                    624:                        if (imm != INVALID_IMM)
                    625:                                return push_inst32(compiler, BICI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    626:                        break;
                    627:                case SLJIT_OR:
                    628:                        imm = get_imm(imm);
                    629:                        if (imm != INVALID_IMM)
                    630:                                return push_inst32(compiler, ORRI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    631:                        imm = get_imm(~((flags & ARG2_IMM) ? arg2 : arg1));
                    632:                        if (imm != INVALID_IMM)
                    633:                                return push_inst32(compiler, ORNI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    634:                        break;
                    635:                case SLJIT_XOR:
                    636:                        imm = get_imm(imm);
                    637:                        if (imm != INVALID_IMM)
                    638:                                return push_inst32(compiler, EORI | (flags & SET_FLAGS) | RD4(dst) | RN4(reg) | imm);
                    639:                        break;
                    640:                case SLJIT_SHL:
                    641:                        if (flags & ARG2_IMM) {
                    642:                                imm &= 0x1f;
1.1.1.2   misho     643:                                if (imm == 0) {
                    644:                                        if (!(flags & SET_FLAGS))
                    645:                                                return push_inst16(compiler, MOV | SET_REGS44(dst, reg));
                    646:                                        if (IS_2_LO_REGS(dst, reg))
                    647:                                                return push_inst16(compiler, MOVS | RD3(dst) | RN3(reg));
                    648:                                        return push_inst32(compiler, MOV_W | SET_FLAGS | RD4(dst) | RM4(reg));
                    649:                                }
1.1       misho     650:                                if (!(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, reg))
                    651:                                        return push_inst16(compiler, LSLSI | RD3(dst) | RN3(reg) | (imm << 6));
                    652:                                return push_inst32(compiler, LSL_WI | (flags & SET_FLAGS) | RD4(dst) | RM4(reg) | IMM5(imm));
                    653:                        }
                    654:                        break;
                    655:                case SLJIT_LSHR:
                    656:                        if (flags & ARG2_IMM) {
                    657:                                imm &= 0x1f;
1.1.1.2   misho     658:                                if (imm == 0) {
                    659:                                        if (!(flags & SET_FLAGS))
                    660:                                                return push_inst16(compiler, MOV | SET_REGS44(dst, reg));
                    661:                                        if (IS_2_LO_REGS(dst, reg))
                    662:                                                return push_inst16(compiler, MOVS | RD3(dst) | RN3(reg));
                    663:                                        return push_inst32(compiler, MOV_W | SET_FLAGS | RD4(dst) | RM4(reg));
                    664:                                }
1.1       misho     665:                                if (!(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, reg))
                    666:                                        return push_inst16(compiler, LSRSI | RD3(dst) | RN3(reg) | (imm << 6));
                    667:                                return push_inst32(compiler, LSR_WI | (flags & SET_FLAGS) | RD4(dst) | RM4(reg) | IMM5(imm));
                    668:                        }
                    669:                        break;
                    670:                case SLJIT_ASHR:
                    671:                        if (flags & ARG2_IMM) {
                    672:                                imm &= 0x1f;
1.1.1.2   misho     673:                                if (imm == 0) {
                    674:                                        if (!(flags & SET_FLAGS))
                    675:                                                return push_inst16(compiler, MOV | SET_REGS44(dst, reg));
                    676:                                        if (IS_2_LO_REGS(dst, reg))
                    677:                                                return push_inst16(compiler, MOVS | RD3(dst) | RN3(reg));
                    678:                                        return push_inst32(compiler, MOV_W | SET_FLAGS | RD4(dst) | RM4(reg));
                    679:                                }
1.1       misho     680:                                if (!(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, reg))
                    681:                                        return push_inst16(compiler, ASRSI | RD3(dst) | RN3(reg) | (imm << 6));
                    682:                                return push_inst32(compiler, ASR_WI | (flags & SET_FLAGS) | RD4(dst) | RM4(reg) | IMM5(imm));
                    683:                        }
                    684:                        break;
                    685:                default:
                    686:                        SLJIT_ASSERT_STOP();
                    687:                        break;
                    688:                }
                    689: 
                    690:                if (flags & ARG2_IMM) {
                    691:                        FAIL_IF(load_immediate(compiler, TMP_REG2, arg2));
                    692:                        arg2 = TMP_REG2;
                    693:                }
                    694:                else {
                    695:                        FAIL_IF(load_immediate(compiler, TMP_REG1, arg1));
                    696:                        arg1 = TMP_REG1;
                    697:                }
                    698:        }
                    699: 
                    700:        /* Both arguments are registers. */
                    701:        switch (flags & 0xffff) {
                    702:        case SLJIT_MOV:
                    703:        case SLJIT_MOV_UI:
                    704:        case SLJIT_MOV_SI:
1.1.1.4 ! misho     705:        case SLJIT_MOV_P:
1.1       misho     706:        case SLJIT_MOVU:
                    707:        case SLJIT_MOVU_UI:
                    708:        case SLJIT_MOVU_SI:
1.1.1.4 ! misho     709:        case SLJIT_MOVU_P:
1.1       misho     710:                SLJIT_ASSERT(!(flags & SET_FLAGS) && arg1 == TMP_REG1);
                    711:                return push_inst16(compiler, MOV | SET_REGS44(dst, arg2));
                    712:        case SLJIT_MOV_UB:
                    713:        case SLJIT_MOVU_UB:
                    714:                SLJIT_ASSERT(!(flags & SET_FLAGS) && arg1 == TMP_REG1);
                    715:                if (IS_2_LO_REGS(dst, arg2))
                    716:                        return push_inst16(compiler, UXTB | RD3(dst) | RN3(arg2));
                    717:                return push_inst32(compiler, UXTB_W | RD4(dst) | RM4(arg2));
                    718:        case SLJIT_MOV_SB:
                    719:        case SLJIT_MOVU_SB:
                    720:                SLJIT_ASSERT(!(flags & SET_FLAGS) && arg1 == TMP_REG1);
                    721:                if (IS_2_LO_REGS(dst, arg2))
                    722:                        return push_inst16(compiler, SXTB | RD3(dst) | RN3(arg2));
                    723:                return push_inst32(compiler, SXTB_W | RD4(dst) | RM4(arg2));
                    724:        case SLJIT_MOV_UH:
                    725:        case SLJIT_MOVU_UH:
                    726:                SLJIT_ASSERT(!(flags & SET_FLAGS) && arg1 == TMP_REG1);
                    727:                if (IS_2_LO_REGS(dst, arg2))
                    728:                        return push_inst16(compiler, UXTH | RD3(dst) | RN3(arg2));
                    729:                return push_inst32(compiler, UXTH_W | RD4(dst) | RM4(arg2));
                    730:        case SLJIT_MOV_SH:
                    731:        case SLJIT_MOVU_SH:
                    732:                SLJIT_ASSERT(!(flags & SET_FLAGS) && arg1 == TMP_REG1);
                    733:                if (IS_2_LO_REGS(dst, arg2))
                    734:                        return push_inst16(compiler, SXTH | RD3(dst) | RN3(arg2));
                    735:                return push_inst32(compiler, SXTH_W | RD4(dst) | RM4(arg2));
                    736:        case SLJIT_NOT:
                    737:                SLJIT_ASSERT(arg1 == TMP_REG1);
                    738:                if (!(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    739:                        return push_inst16(compiler, MVNS | RD3(dst) | RN3(arg2));
                    740:                return push_inst32(compiler, MVN_W | (flags & SET_FLAGS) | RD4(dst) | RM4(arg2));
                    741:        case SLJIT_CLZ:
                    742:                SLJIT_ASSERT(arg1 == TMP_REG1);
                    743:                FAIL_IF(push_inst32(compiler, CLZ | RN4(arg2) | RD4(dst) | RM4(arg2)));
                    744:                if (flags & SET_FLAGS) {
                    745:                        if (reg_map[dst] <= 7)
                    746:                                return push_inst16(compiler, CMPI | RDN3(dst));
                    747:                        return push_inst32(compiler, ADD_WI | SET_FLAGS | RN4(dst) | RD4(dst));
                    748:                }
                    749:                return SLJIT_SUCCESS;
                    750:        case SLJIT_ADD:
                    751:                if (!(flags & KEEP_FLAGS) && IS_3_LO_REGS(dst, arg1, arg2))
                    752:                        return push_inst16(compiler, ADDS | RD3(dst) | RN3(arg1) | RM3(arg2));
                    753:                if (dst == arg1 && !(flags & SET_FLAGS))
                    754:                        return push_inst16(compiler, ADD | SET_REGS44(dst, arg2));
                    755:                return push_inst32(compiler, ADD_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    756:        case SLJIT_ADDC:
                    757:                if (dst == arg1 && !(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    758:                        return push_inst16(compiler, ADCS | RD3(dst) | RN3(arg2));
                    759:                return push_inst32(compiler, ADC_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    760:        case SLJIT_SUB:
                    761:                if (!(flags & KEEP_FLAGS) && IS_3_LO_REGS(dst, arg1, arg2))
                    762:                        return push_inst16(compiler, SUBS | RD3(dst) | RN3(arg1) | RM3(arg2));
                    763:                return push_inst32(compiler, SUB_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    764:        case SLJIT_SUBC:
                    765:                if (dst == arg1 && !(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    766:                        return push_inst16(compiler, SBCS | RD3(dst) | RN3(arg2));
                    767:                return push_inst32(compiler, SBC_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    768:        case SLJIT_MUL:
                    769:                if (!(flags & SET_FLAGS))
                    770:                        return push_inst32(compiler, MUL | RD4(dst) | RN4(arg1) | RM4(arg2));
                    771:                SLJIT_ASSERT(reg_map[TMP_REG2] <= 7 && dst != TMP_REG2);
                    772:                FAIL_IF(push_inst32(compiler, SMULL | RT4(dst) | RD4(TMP_REG2) | RN4(arg1) | RM4(arg2)));
                    773:                /* cmp TMP_REG2, dst asr #31. */
                    774:                return push_inst32(compiler, CMP_W | RN4(TMP_REG2) | 0x70e0 | RM4(dst));
                    775:        case SLJIT_AND:
                    776:                if (!(flags & KEEP_FLAGS)) {
                    777:                        if (dst == arg1 && IS_2_LO_REGS(dst, arg2))
                    778:                                return push_inst16(compiler, ANDS | RD3(dst) | RN3(arg2));
                    779:                        if ((flags & UNUSED_RETURN) && IS_2_LO_REGS(arg1, arg2))
                    780:                                return push_inst16(compiler, TST | RD3(arg1) | RN3(arg2));
                    781:                }
                    782:                return push_inst32(compiler, AND_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    783:        case SLJIT_OR:
                    784:                if (dst == arg1 && !(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    785:                        return push_inst16(compiler, ORRS | RD3(dst) | RN3(arg2));
                    786:                return push_inst32(compiler, ORR_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    787:        case SLJIT_XOR:
                    788:                if (dst == arg1 && !(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    789:                        return push_inst16(compiler, EORS | RD3(dst) | RN3(arg2));
                    790:                return push_inst32(compiler, EOR_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    791:        case SLJIT_SHL:
                    792:                if (dst == arg1 && !(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    793:                        return push_inst16(compiler, LSLS | RD3(dst) | RN3(arg2));
                    794:                return push_inst32(compiler, LSL_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    795:        case SLJIT_LSHR:
                    796:                if (dst == arg1 && !(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    797:                        return push_inst16(compiler, LSRS | RD3(dst) | RN3(arg2));
                    798:                return push_inst32(compiler, LSR_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    799:        case SLJIT_ASHR:
                    800:                if (dst == arg1 && !(flags & KEEP_FLAGS) && IS_2_LO_REGS(dst, arg2))
                    801:                        return push_inst16(compiler, ASRS | RD3(dst) | RN3(arg2));
                    802:                return push_inst32(compiler, ASR_W | (flags & SET_FLAGS) | RD4(dst) | RN4(arg1) | RM4(arg2));
                    803:        }
                    804: 
                    805:        SLJIT_ASSERT_STOP();
                    806:        return SLJIT_SUCCESS;
                    807: }
                    808: 
                    809: #define STORE          0x01
                    810: #define SIGNED         0x02
                    811: 
                    812: #define WORD_SIZE      0x00
                    813: #define BYTE_SIZE      0x04
                    814: #define HALF_SIZE      0x08
                    815: 
                    816: #define UPDATE         0x10
                    817: #define ARG_TEST       0x20
                    818: 
                    819: #define IS_WORD_SIZE(flags)            (!(flags & (BYTE_SIZE | HALF_SIZE)))
                    820: #define OFFSET_CHECK(imm, shift)       (!(argw & ~(imm << shift)))
                    821: 
                    822: /*
                    823:   1st letter:
                    824:   w = word
                    825:   b = byte
                    826:   h = half
                    827: 
                    828:   2nd letter:
                    829:   s = signed
                    830:   u = unsigned
                    831: 
                    832:   3rd letter:
                    833:   l = load
                    834:   s = store
                    835: */
                    836: 
                    837: static SLJIT_CONST sljit_uw sljit_mem16[12] = {
                    838: /* w u l */ 0x5800 /* ldr */,
                    839: /* w u s */ 0x5000 /* str */,
                    840: /* w s l */ 0x5800 /* ldr */,
                    841: /* w s s */ 0x5000 /* str */,
                    842: 
                    843: /* b u l */ 0x5c00 /* ldrb */,
                    844: /* b u s */ 0x5400 /* strb */,
                    845: /* b s l */ 0x5600 /* ldrsb */,
                    846: /* b s s */ 0x5400 /* strb */,
                    847: 
                    848: /* h u l */ 0x5a00 /* ldrh */,
                    849: /* h u s */ 0x5200 /* strh */,
                    850: /* h s l */ 0x5e00 /* ldrsh */,
                    851: /* h s s */ 0x5200 /* strh */,
                    852: };
                    853: 
                    854: static SLJIT_CONST sljit_uw sljit_mem16_imm5[12] = {
                    855: /* w u l */ 0x6800 /* ldr imm5 */,
                    856: /* w u s */ 0x6000 /* str imm5 */,
                    857: /* w s l */ 0x6800 /* ldr imm5 */,
                    858: /* w s s */ 0x6000 /* str imm5 */,
                    859: 
                    860: /* b u l */ 0x7800 /* ldrb imm5 */,
                    861: /* b u s */ 0x7000 /* strb imm5 */,
                    862: /* b s l */ 0x0000 /* not allowed */,
                    863: /* b s s */ 0x7000 /* strb imm5 */,
                    864: 
                    865: /* h u l */ 0x8800 /* ldrh imm5 */,
                    866: /* h u s */ 0x8000 /* strh imm5 */,
                    867: /* h s l */ 0x0000 /* not allowed */,
                    868: /* h s s */ 0x8000 /* strh imm5 */,
                    869: };
                    870: 
                    871: #define MEM_IMM8       0xc00
                    872: #define MEM_IMM12      0x800000
                    873: static SLJIT_CONST sljit_uw sljit_mem32[12] = {
                    874: /* w u l */ 0xf8500000 /* ldr.w */,
                    875: /* w u s */ 0xf8400000 /* str.w */,
                    876: /* w s l */ 0xf8500000 /* ldr.w */,
                    877: /* w s s */ 0xf8400000 /* str.w */,
                    878: 
                    879: /* b u l */ 0xf8100000 /* ldrb.w */,
                    880: /* b u s */ 0xf8000000 /* strb.w */,
                    881: /* b s l */ 0xf9100000 /* ldrsb.w */,
                    882: /* b s s */ 0xf8000000 /* strb.w */,
                    883: 
                    884: /* h u l */ 0xf8300000 /* ldrh.w */,
                    885: /* h u s */ 0xf8200000 /* strsh.w */,
                    886: /* h s l */ 0xf9300000 /* ldrsh.w */,
                    887: /* h s s */ 0xf8200000 /* strsh.w */,
                    888: };
                    889: 
                    890: /* Helper function. Dst should be reg + value, using at most 1 instruction, flags does not set. */
1.1.1.4 ! misho     891: static sljit_si emit_set_delta(struct sljit_compiler *compiler, sljit_si dst, sljit_si reg, sljit_sw value)
1.1       misho     892: {
                    893:        if (value >= 0) {
                    894:                if (value <= 0xfff)
                    895:                        return push_inst32(compiler, ADDWI | RD4(dst) | RN4(reg) | IMM12(value));
                    896:                value = get_imm(value);
                    897:                if (value != INVALID_IMM)
                    898:                        return push_inst32(compiler, ADD_WI | RD4(dst) | RN4(reg) | value);
                    899:        }
                    900:        else {
                    901:                value = -value;
                    902:                if (value <= 0xfff)
                    903:                        return push_inst32(compiler, SUBWI | RD4(dst) | RN4(reg) | IMM12(value));
                    904:                value = get_imm(value);
                    905:                if (value != INVALID_IMM)
                    906:                        return push_inst32(compiler, SUB_WI | RD4(dst) | RN4(reg) | value);
                    907:        }
                    908:        return SLJIT_ERR_UNSUPPORTED;
                    909: }
                    910: 
                    911: /* Can perform an operation using at most 1 instruction. */
1.1.1.4 ! misho     912: static sljit_si getput_arg_fast(struct sljit_compiler *compiler, sljit_si flags, sljit_si reg, sljit_si arg, sljit_sw argw)
1.1       misho     913: {
1.1.1.4 ! misho     914:        sljit_si tmp;
1.1       misho     915: 
                    916:        SLJIT_ASSERT(arg & SLJIT_MEM);
                    917: 
                    918:        if (SLJIT_UNLIKELY(flags & UPDATE)) {
                    919:                if ((arg & 0xf) && !(arg & 0xf0) && argw <= 0xff && argw >= -0xff) {
                    920:                        flags &= ~UPDATE;
                    921:                        arg &= 0xf;
                    922:                        if (SLJIT_UNLIKELY(flags & ARG_TEST))
                    923:                                return 1;
                    924: 
                    925:                        if (argw >= 0)
                    926:                                argw |= 0x200;
                    927:                        else {
                    928:                                argw = -argw;
                    929:                        }
                    930:                        SLJIT_ASSERT(argw >= 0 && (argw & 0xff) <= 0xff);
                    931:                        FAIL_IF(push_inst32(compiler, sljit_mem32[flags] | MEM_IMM8 | RT4(reg) | RN4(arg) | 0x100 | argw));
                    932:                        return -1;
                    933:                }
                    934:                return (flags & ARG_TEST) ? SLJIT_SUCCESS : 0;
                    935:        }
                    936: 
                    937:        if (SLJIT_UNLIKELY(arg & 0xf0)) {
                    938:                argw &= 0x3;
                    939:                tmp = (arg >> 4) & 0xf;
                    940:                arg &= 0xf;
                    941:                if (SLJIT_UNLIKELY(flags & ARG_TEST))
                    942:                        return 1;
                    943: 
                    944:                if (!argw && IS_3_LO_REGS(reg, arg, tmp))
                    945:                        FAIL_IF(push_inst16(compiler, sljit_mem16[flags] | RD3(reg) | RN3(arg) | RM3(tmp)));
                    946:                else
                    947:                        FAIL_IF(push_inst32(compiler, sljit_mem32[flags] | RT4(reg) | RN4(arg) | RM4(tmp) | (argw << 4)));
                    948:                return -1;
                    949:        }
                    950: 
                    951:        if (!(arg & 0xf) || argw > 0xfff || argw < -0xff)
                    952:                return (flags & ARG_TEST) ? SLJIT_SUCCESS : 0;
                    953: 
                    954:        if (SLJIT_UNLIKELY(flags & ARG_TEST))
                    955:                return 1;
                    956: 
                    957:        arg &= 0xf;
                    958:        if (IS_2_LO_REGS(reg, arg) && sljit_mem16_imm5[flags]) {
                    959:                tmp = 3;
                    960:                if (IS_WORD_SIZE(flags)) {
                    961:                        if (OFFSET_CHECK(0x1f, 2))
                    962:                                tmp = 2;
                    963:                }
                    964:                else if (flags & BYTE_SIZE)
                    965:                {
                    966:                        if (OFFSET_CHECK(0x1f, 0))
                    967:                                tmp = 0;
                    968:                }
                    969:                else {
                    970:                        SLJIT_ASSERT(flags & HALF_SIZE);
                    971:                        if (OFFSET_CHECK(0x1f, 1))
                    972:                                tmp = 1;
                    973:                }
                    974: 
                    975:                if (tmp != 3) {
                    976:                        FAIL_IF(push_inst16(compiler, sljit_mem16_imm5[flags] | RD3(reg) | RN3(arg) | (argw << (6 - tmp))));
                    977:                        return -1;
                    978:                }
                    979:        }
                    980: 
                    981:        /* SP based immediate. */
                    982:        if (SLJIT_UNLIKELY(arg == SLJIT_LOCALS_REG) && OFFSET_CHECK(0xff, 2) && IS_WORD_SIZE(flags) && reg_map[reg] <= 7) {
                    983:                FAIL_IF(push_inst16(compiler, STR_SP | ((flags & STORE) ? 0 : 0x800) | RDN3(reg) | (argw >> 2)));
                    984:                return -1;
                    985:        }
                    986: 
                    987:        if (argw >= 0)
                    988:                FAIL_IF(push_inst32(compiler, sljit_mem32[flags] | MEM_IMM12 | RT4(reg) | RN4(arg) | argw));
                    989:        else
                    990:                FAIL_IF(push_inst32(compiler, sljit_mem32[flags] | MEM_IMM8 | RT4(reg) | RN4(arg) | -argw));
                    991:        return -1;
                    992: }
                    993: 
                    994: /* see getput_arg below.
                    995:    Note: can_cache is called only for binary operators. Those
                    996:    operators always uses word arguments without write back. */
1.1.1.4 ! misho     997: static sljit_si can_cache(sljit_si arg, sljit_sw argw, sljit_si next_arg, sljit_sw next_argw)
1.1       misho     998: {
                    999:        /* Simple operation except for updates. */
                   1000:        if ((arg & 0xf0) || !(next_arg & SLJIT_MEM))
                   1001:                return 0;
                   1002: 
                   1003:        if (!(arg & 0xf)) {
                   1004:                if ((sljit_uw)(argw - next_argw) <= 0xfff || (sljit_uw)(next_argw - argw) <= 0xfff)
                   1005:                        return 1;
                   1006:                return 0;
                   1007:        }
                   1008: 
                   1009:        if (argw == next_argw)
                   1010:                return 1;
                   1011: 
                   1012:        if (arg == next_arg && ((sljit_uw)(argw - next_argw) <= 0xfff || (sljit_uw)(next_argw - argw) <= 0xfff))
                   1013:                return 1;
                   1014: 
                   1015:        return 0;
                   1016: }
                   1017: 
                   1018: /* Emit the necessary instructions. See can_cache above. */
1.1.1.4 ! misho    1019: static sljit_si getput_arg(struct sljit_compiler *compiler, sljit_si flags, sljit_si reg, sljit_si arg, sljit_sw argw, sljit_si next_arg, sljit_sw next_argw)
1.1       misho    1020: {
1.1.1.4 ! misho    1021:        sljit_si tmp_r;
        !          1022:        sljit_sw tmp;
1.1       misho    1023: 
                   1024:        SLJIT_ASSERT(arg & SLJIT_MEM);
                   1025:        if (!(next_arg & SLJIT_MEM)) {
                   1026:                next_arg = 0;
                   1027:                next_argw = 0;
                   1028:        }
                   1029: 
                   1030:        tmp_r = (flags & STORE) ? TMP_REG3 : reg;
                   1031: 
                   1032:        if (SLJIT_UNLIKELY(flags & UPDATE)) {
                   1033:                flags &= ~UPDATE;
                   1034:                /* Update only applies if a base register exists. */
                   1035:                if (arg & 0xf) {
                   1036:                        /* There is no caching here. */
                   1037:                        tmp = (arg & 0xf0) >> 4;
                   1038:                        arg &= 0xf;
                   1039: 
                   1040:                        if (!tmp) {
                   1041:                                if (!(argw & ~0xfff)) {
                   1042:                                        FAIL_IF(push_inst32(compiler, sljit_mem32[flags] | MEM_IMM12 | RT4(reg) | RN4(arg) | argw));
                   1043:                                        return push_inst32(compiler, ADDWI | RD4(arg) | RN4(arg) | IMM12(argw));
                   1044:                                }
                   1045: 
                   1046:                                if (compiler->cache_arg == SLJIT_MEM) {
                   1047:                                        if (argw == compiler->cache_argw) {
                   1048:                                                tmp = TMP_REG3;
                   1049:                                                argw = 0;
                   1050:                                        }
                   1051:                                        else if (emit_set_delta(compiler, TMP_REG3, TMP_REG3, argw - compiler->cache_argw) != SLJIT_ERR_UNSUPPORTED) {
                   1052:                                                FAIL_IF(compiler->error);
                   1053:                                                compiler->cache_argw = argw;
                   1054:                                                tmp = TMP_REG3;
                   1055:                                                argw = 0;
                   1056:                                        }
                   1057:                                }
                   1058: 
                   1059:                                if (argw) {
                   1060:                                        FAIL_IF(load_immediate(compiler, TMP_REG3, argw));
                   1061:                                        compiler->cache_arg = SLJIT_MEM;
                   1062:                                        compiler->cache_argw = argw;
                   1063:                                        tmp = TMP_REG3;
                   1064:                                        argw = 0;
                   1065:                                }
                   1066:                        }
                   1067: 
                   1068:                        argw &= 0x3;
                   1069:                        if (!argw && IS_3_LO_REGS(reg, arg, tmp)) {
                   1070:                                FAIL_IF(push_inst16(compiler, sljit_mem16[flags] | RD3(reg) | RN3(arg) | RM3(tmp)));
                   1071:                                return push_inst16(compiler, ADD | SET_REGS44(arg, tmp));
                   1072:                        }
                   1073:                        FAIL_IF(push_inst32(compiler, sljit_mem32[flags] | RT4(reg) | RN4(arg) | RM4(tmp) | (argw << 4)));
                   1074:                        return push_inst32(compiler, ADD_W | RD4(arg) | RN4(arg) | RM4(tmp) | (argw << 6));
                   1075:                }
                   1076:        }
                   1077: 
                   1078:        SLJIT_ASSERT(!(arg & 0xf0));
                   1079: 
                   1080:        if (compiler->cache_arg == arg) {
                   1081:                if (!((argw - compiler->cache_argw) & ~0xfff))
                   1082:                        return push_inst32(compiler, sljit_mem32[flags] | MEM_IMM12 | RT4(reg) | RN4(TMP_REG3) | (argw - compiler->cache_argw));
                   1083:                if (!((compiler->cache_argw - argw) & ~0xff))
                   1084:                        return push_inst32(compiler, sljit_mem32[flags] | MEM_IMM8 | RT4(reg) | RN4(TMP_REG3) | (compiler->cache_argw - argw));
                   1085:                if (emit_set_delta(compiler, TMP_REG3, TMP_REG3, argw - compiler->cache_argw) != SLJIT_ERR_UNSUPPORTED) {
                   1086:                        FAIL_IF(compiler->error);
                   1087:                        return push_inst32(compiler, sljit_mem32[flags] | MEM_IMM12 | RT4(reg) | RN4(TMP_REG3) | 0);
                   1088:                }
                   1089:        }
                   1090: 
                   1091:        next_arg = (arg & 0xf) && (arg == next_arg);
                   1092:        arg &= 0xf;
                   1093:        if (arg && compiler->cache_arg == SLJIT_MEM && compiler->cache_argw == argw)
                   1094:                return push_inst32(compiler, sljit_mem32[flags] | RT4(reg) | RN4(arg) | RM4(TMP_REG3));
                   1095: 
                   1096:        compiler->cache_argw = argw;
                   1097:        if (next_arg && emit_set_delta(compiler, TMP_REG3, arg, argw) != SLJIT_ERR_UNSUPPORTED) {
                   1098:                FAIL_IF(compiler->error);
                   1099:                compiler->cache_arg = SLJIT_MEM | arg;
                   1100:                arg = 0;
                   1101:        }
                   1102:        else {
                   1103:                FAIL_IF(load_immediate(compiler, TMP_REG3, argw));
                   1104:                compiler->cache_arg = SLJIT_MEM;
                   1105: 
                   1106:                if (next_arg) {
                   1107:                        FAIL_IF(push_inst16(compiler, ADD | SET_REGS44(TMP_REG3, arg)));
                   1108:                        compiler->cache_arg = SLJIT_MEM | arg;
                   1109:                        arg = 0;
                   1110:                }
                   1111:        }
                   1112: 
                   1113:        if (arg)
                   1114:                return push_inst32(compiler, sljit_mem32[flags] | RT4(reg) | RN4(arg) | RM4(TMP_REG3));
                   1115:        return push_inst32(compiler, sljit_mem32[flags] | MEM_IMM12 | RT4(reg) | RN4(TMP_REG3) | 0);
                   1116: }
                   1117: 
1.1.1.4 ! misho    1118: static SLJIT_INLINE sljit_si emit_op_mem(struct sljit_compiler *compiler, sljit_si flags, sljit_si reg, sljit_si arg, sljit_sw argw)
1.1       misho    1119: {
                   1120:        if (getput_arg_fast(compiler, flags, reg, arg, argw))
                   1121:                return compiler->error;
                   1122:        compiler->cache_arg = 0;
                   1123:        compiler->cache_argw = 0;
                   1124:        return getput_arg(compiler, flags, reg, arg, argw, 0, 0);
                   1125: }
                   1126: 
1.1.1.4 ! misho    1127: static SLJIT_INLINE sljit_si emit_op_mem2(struct sljit_compiler *compiler, sljit_si flags, sljit_si reg, sljit_si arg1, sljit_sw arg1w, sljit_si arg2, sljit_sw arg2w)
        !          1128: {
        !          1129:        if (getput_arg_fast(compiler, flags, reg, arg1, arg1w))
        !          1130:                return compiler->error;
        !          1131:        return getput_arg(compiler, flags, reg, arg1, arg1w, arg2, arg2w);
        !          1132: }
        !          1133: 
        !          1134: /* --------------------------------------------------------------------- */
        !          1135: /*  Entry, exit                                                          */
        !          1136: /* --------------------------------------------------------------------- */
        !          1137: 
        !          1138: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_enter(struct sljit_compiler *compiler, sljit_si args, sljit_si scratches, sljit_si saveds, sljit_si local_size)
1.1       misho    1139: {
1.1.1.4 ! misho    1140:        sljit_si size;
1.1       misho    1141:        sljit_ins push;
                   1142: 
                   1143:        CHECK_ERROR();
1.1.1.4 ! misho    1144:        check_sljit_emit_enter(compiler, args, scratches, saveds, local_size);
1.1       misho    1145: 
1.1.1.4 ! misho    1146:        compiler->scratches = scratches;
1.1.1.2   misho    1147:        compiler->saveds = saveds;
1.1.1.3   misho    1148: #if (defined SLJIT_DEBUG && SLJIT_DEBUG)
                   1149:        compiler->logical_local_size = local_size;
                   1150: #endif
1.1       misho    1151: 
                   1152:        push = (1 << 4);
1.1.1.2   misho    1153:        if (saveds >= 5)
1.1       misho    1154:                push |= 1 << 11;
1.1.1.2   misho    1155:        if (saveds >= 4)
1.1       misho    1156:                push |= 1 << 10;
1.1.1.2   misho    1157:        if (saveds >= 3)
1.1       misho    1158:                push |= 1 << 8;
1.1.1.2   misho    1159:        if (saveds >= 2)
1.1       misho    1160:                push |= 1 << 7;
1.1.1.2   misho    1161:        if (saveds >= 1)
1.1       misho    1162:                push |= 1 << 6;
1.1.1.4 ! misho    1163:         if (scratches >= 5)
1.1       misho    1164:                push |= 1 << 5;
1.1.1.2   misho    1165:        FAIL_IF(saveds >= 3
1.1       misho    1166:                ? push_inst32(compiler, PUSH_W | (1 << 14) | push)
                   1167:                : push_inst16(compiler, PUSH | push));
                   1168: 
                   1169:        /* Stack must be aligned to 8 bytes: */
1.1.1.2   misho    1170:        size = (3 + saveds) * sizeof(sljit_uw);
1.1       misho    1171:        local_size += size;
                   1172:        local_size = (local_size + 7) & ~7;
                   1173:        local_size -= size;
                   1174:        compiler->local_size = local_size;
                   1175:        if (local_size > 0) {
                   1176:                if (local_size <= (127 << 2))
                   1177:                        FAIL_IF(push_inst16(compiler, SUB_SP | (local_size >> 2)));
                   1178:                else
                   1179:                        FAIL_IF(emit_op_imm(compiler, SLJIT_SUB | ARG2_IMM, SLJIT_LOCALS_REG, SLJIT_LOCALS_REG, local_size));
                   1180:        }
                   1181: 
                   1182:        if (args >= 1)
1.1.1.4 ! misho    1183:                FAIL_IF(push_inst16(compiler, MOV | SET_REGS44(SLJIT_SAVED_REG1, SLJIT_SCRATCH_REG1)));
1.1       misho    1184:        if (args >= 2)
1.1.1.4 ! misho    1185:                FAIL_IF(push_inst16(compiler, MOV | SET_REGS44(SLJIT_SAVED_REG2, SLJIT_SCRATCH_REG2)));
1.1       misho    1186:        if (args >= 3)
1.1.1.4 ! misho    1187:                FAIL_IF(push_inst16(compiler, MOV | SET_REGS44(SLJIT_SAVED_REG3, SLJIT_SCRATCH_REG3)));
1.1       misho    1188: 
                   1189:        return SLJIT_SUCCESS;
                   1190: }
                   1191: 
1.1.1.4 ! misho    1192: SLJIT_API_FUNC_ATTRIBUTE void sljit_set_context(struct sljit_compiler *compiler, sljit_si args, sljit_si scratches, sljit_si saveds, sljit_si local_size)
1.1       misho    1193: {
1.1.1.4 ! misho    1194:        sljit_si size;
1.1       misho    1195: 
                   1196:        CHECK_ERROR_VOID();
1.1.1.4 ! misho    1197:        check_sljit_set_context(compiler, args, scratches, saveds, local_size);
1.1       misho    1198: 
1.1.1.4 ! misho    1199:        compiler->scratches = scratches;
1.1.1.2   misho    1200:        compiler->saveds = saveds;
1.1.1.3   misho    1201: #if (defined SLJIT_DEBUG && SLJIT_DEBUG)
                   1202:        compiler->logical_local_size = local_size;
                   1203: #endif
1.1       misho    1204: 
1.1.1.2   misho    1205:        size = (3 + saveds) * sizeof(sljit_uw);
1.1       misho    1206:        local_size += size;
                   1207:        local_size = (local_size + 7) & ~7;
                   1208:        local_size -= size;
                   1209:        compiler->local_size = local_size;
                   1210: }
                   1211: 
1.1.1.4 ! misho    1212: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_return(struct sljit_compiler *compiler, sljit_si op, sljit_si src, sljit_sw srcw)
1.1       misho    1213: {
                   1214:        sljit_ins pop;
                   1215: 
                   1216:        CHECK_ERROR();
1.1.1.2   misho    1217:        check_sljit_emit_return(compiler, op, src, srcw);
1.1       misho    1218: 
1.1.1.2   misho    1219:        FAIL_IF(emit_mov_before_return(compiler, op, src, srcw));
1.1       misho    1220: 
                   1221:        if (compiler->local_size > 0) {
                   1222:                if (compiler->local_size <= (127 << 2))
                   1223:                        FAIL_IF(push_inst16(compiler, ADD_SP | (compiler->local_size >> 2)));
                   1224:                else
                   1225:                        FAIL_IF(emit_op_imm(compiler, SLJIT_ADD | ARG2_IMM, SLJIT_LOCALS_REG, SLJIT_LOCALS_REG, compiler->local_size));
                   1226:        }
                   1227: 
                   1228:        pop = (1 << 4);
1.1.1.2   misho    1229:        if (compiler->saveds >= 5)
1.1       misho    1230:                pop |= 1 << 11;
1.1.1.2   misho    1231:        if (compiler->saveds >= 4)
1.1       misho    1232:                pop |= 1 << 10;
1.1.1.2   misho    1233:        if (compiler->saveds >= 3)
1.1       misho    1234:                pop |= 1 << 8;
1.1.1.2   misho    1235:        if (compiler->saveds >= 2)
1.1       misho    1236:                pop |= 1 << 7;
1.1.1.2   misho    1237:        if (compiler->saveds >= 1)
1.1       misho    1238:                pop |= 1 << 6;
1.1.1.4 ! misho    1239:         if (compiler->scratches >= 5)
1.1       misho    1240:                pop |= 1 << 5;
1.1.1.2   misho    1241:        return compiler->saveds >= 3
1.1       misho    1242:                ? push_inst32(compiler, POP_W | (1 << 15) | pop)
                   1243:                : push_inst16(compiler, POP | pop);
                   1244: }
                   1245: 
                   1246: /* --------------------------------------------------------------------- */
                   1247: /*  Operators                                                            */
                   1248: /* --------------------------------------------------------------------- */
                   1249: 
1.1.1.2   misho    1250: #ifdef __cplusplus
                   1251: extern "C" {
                   1252: #endif
                   1253: 
                   1254: #if defined(__GNUC__)
1.1.1.4 ! misho    1255: extern unsigned int __aeabi_uidivmod(unsigned int numerator, int unsigned denominator);
        !          1256: extern int __aeabi_idivmod(int numerator, int denominator);
1.1.1.2   misho    1257: #else
                   1258: #error "Software divmod functions are needed"
                   1259: #endif
                   1260: 
                   1261: #ifdef __cplusplus
                   1262: }
                   1263: #endif
                   1264: 
1.1.1.4 ! misho    1265: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_op0(struct sljit_compiler *compiler, sljit_si op)
1.1       misho    1266: {
                   1267:        CHECK_ERROR();
                   1268:        check_sljit_emit_op0(compiler, op);
                   1269: 
                   1270:        op = GET_OPCODE(op);
                   1271:        switch (op) {
                   1272:        case SLJIT_BREAKPOINT:
                   1273:                push_inst16(compiler, BKPT);
                   1274:                break;
                   1275:        case SLJIT_NOP:
                   1276:                push_inst16(compiler, NOP);
                   1277:                break;
1.1.1.2   misho    1278:        case SLJIT_UMUL:
                   1279:        case SLJIT_SMUL:
                   1280:                return push_inst32(compiler, (op == SLJIT_UMUL ? UMULL : SMULL)
1.1.1.4 ! misho    1281:                        | (reg_map[SLJIT_SCRATCH_REG2] << 8)
        !          1282:                        | (reg_map[SLJIT_SCRATCH_REG1] << 12)
        !          1283:                        | (reg_map[SLJIT_SCRATCH_REG1] << 16)
        !          1284:                        | reg_map[SLJIT_SCRATCH_REG2]);
1.1.1.2   misho    1285:        case SLJIT_UDIV:
                   1286:        case SLJIT_SDIV:
1.1.1.4 ! misho    1287:                if (compiler->scratches >= 4) {
1.1.1.2   misho    1288:                        FAIL_IF(push_inst32(compiler, 0xf84d2d04 /* str r2, [sp, #-4]! */));
                   1289:                        FAIL_IF(push_inst32(compiler, 0xf84dcd04 /* str ip, [sp, #-4]! */));
1.1.1.4 ! misho    1290:                } else if (compiler->scratches >= 3)
1.1.1.2   misho    1291:                        FAIL_IF(push_inst32(compiler, 0xf84d2d08 /* str r2, [sp, #-8]! */));
                   1292: #if defined(__GNUC__)
                   1293:                FAIL_IF(sljit_emit_ijump(compiler, SLJIT_FAST_CALL, SLJIT_IMM,
                   1294:                        (op == SLJIT_UDIV ? SLJIT_FUNC_OFFSET(__aeabi_uidivmod) : SLJIT_FUNC_OFFSET(__aeabi_idivmod))));
                   1295: #else
                   1296: #error "Software divmod functions are needed"
                   1297: #endif
1.1.1.4 ! misho    1298:                if (compiler->scratches >= 4) {
1.1.1.2   misho    1299:                        FAIL_IF(push_inst32(compiler, 0xf85dcb04 /* ldr ip, [sp], #4 */));
                   1300:                        return push_inst32(compiler, 0xf85d2b04 /* ldr r2, [sp], #4 */);
1.1.1.4 ! misho    1301:                } else if (compiler->scratches >= 3)
1.1.1.2   misho    1302:                        return push_inst32(compiler, 0xf85d2b08 /* ldr r2, [sp], #8 */);
                   1303:                return SLJIT_SUCCESS;
1.1       misho    1304:        }
                   1305: 
                   1306:        return SLJIT_SUCCESS;
                   1307: }
                   1308: 
1.1.1.4 ! misho    1309: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_op1(struct sljit_compiler *compiler, sljit_si op,
        !          1310:        sljit_si dst, sljit_sw dstw,
        !          1311:        sljit_si src, sljit_sw srcw)
1.1       misho    1312: {
1.1.1.4 ! misho    1313:        sljit_si dst_r, flags;
        !          1314:        sljit_si op_flags = GET_ALL_FLAGS(op);
1.1       misho    1315: 
                   1316:        CHECK_ERROR();
                   1317:        check_sljit_emit_op1(compiler, op, dst, dstw, src, srcw);
1.1.1.3   misho    1318:        ADJUST_LOCAL_OFFSET(dst, dstw);
                   1319:        ADJUST_LOCAL_OFFSET(src, srcw);
1.1       misho    1320: 
                   1321:        compiler->cache_arg = 0;
                   1322:        compiler->cache_argw = 0;
                   1323: 
1.1.1.4 ! misho    1324:        dst_r = (dst >= SLJIT_SCRATCH_REG1 && dst <= TMP_REG3) ? dst : TMP_REG1;
1.1       misho    1325: 
1.1.1.4 ! misho    1326:        op = GET_OPCODE(op);
        !          1327:        if (op >= SLJIT_MOV && op <= SLJIT_MOVU_P) {
        !          1328:                switch (op) {
1.1       misho    1329:                case SLJIT_MOV:
                   1330:                case SLJIT_MOV_UI:
                   1331:                case SLJIT_MOV_SI:
1.1.1.4 ! misho    1332:                case SLJIT_MOV_P:
1.1       misho    1333:                        flags = WORD_SIZE;
                   1334:                        break;
                   1335:                case SLJIT_MOV_UB:
                   1336:                        flags = BYTE_SIZE;
                   1337:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1338:                                srcw = (sljit_ub)srcw;
1.1       misho    1339:                        break;
                   1340:                case SLJIT_MOV_SB:
                   1341:                        flags = BYTE_SIZE | SIGNED;
                   1342:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1343:                                srcw = (sljit_sb)srcw;
1.1       misho    1344:                        break;
                   1345:                case SLJIT_MOV_UH:
                   1346:                        flags = HALF_SIZE;
                   1347:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1348:                                srcw = (sljit_uh)srcw;
1.1       misho    1349:                        break;
                   1350:                case SLJIT_MOV_SH:
                   1351:                        flags = HALF_SIZE | SIGNED;
                   1352:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1353:                                srcw = (sljit_sh)srcw;
1.1       misho    1354:                        break;
                   1355:                case SLJIT_MOVU:
                   1356:                case SLJIT_MOVU_UI:
                   1357:                case SLJIT_MOVU_SI:
1.1.1.4 ! misho    1358:                case SLJIT_MOVU_P:
1.1       misho    1359:                        flags = WORD_SIZE | UPDATE;
                   1360:                        break;
                   1361:                case SLJIT_MOVU_UB:
                   1362:                        flags = BYTE_SIZE | UPDATE;
                   1363:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1364:                                srcw = (sljit_ub)srcw;
1.1       misho    1365:                        break;
                   1366:                case SLJIT_MOVU_SB:
                   1367:                        flags = BYTE_SIZE | SIGNED | UPDATE;
                   1368:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1369:                                srcw = (sljit_sb)srcw;
1.1       misho    1370:                        break;
                   1371:                case SLJIT_MOVU_UH:
                   1372:                        flags = HALF_SIZE | UPDATE;
                   1373:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1374:                                srcw = (sljit_uh)srcw;
1.1       misho    1375:                        break;
                   1376:                case SLJIT_MOVU_SH:
                   1377:                        flags = HALF_SIZE | SIGNED | UPDATE;
                   1378:                        if (src & SLJIT_IMM)
1.1.1.4 ! misho    1379:                                srcw = (sljit_sh)srcw;
1.1       misho    1380:                        break;
                   1381:                default:
                   1382:                        SLJIT_ASSERT_STOP();
                   1383:                        flags = 0;
                   1384:                        break;
                   1385:                }
                   1386: 
                   1387:                if (src & SLJIT_IMM)
                   1388:                        FAIL_IF(emit_op_imm(compiler, SLJIT_MOV | ARG2_IMM, dst_r, TMP_REG1, srcw));
                   1389:                else if (src & SLJIT_MEM) {
                   1390:                        if (getput_arg_fast(compiler, flags, dst_r, src, srcw))
                   1391:                                FAIL_IF(compiler->error);
                   1392:                        else
                   1393:                                FAIL_IF(getput_arg(compiler, flags, dst_r, src, srcw, dst, dstw));
                   1394:                } else {
                   1395:                        if (dst_r != TMP_REG1)
1.1.1.4 ! misho    1396:                                return emit_op_imm(compiler, op, dst_r, TMP_REG1, src);
1.1       misho    1397:                        dst_r = src;
                   1398:                }
                   1399: 
                   1400:                if (dst & SLJIT_MEM) {
                   1401:                        if (getput_arg_fast(compiler, flags | STORE, dst_r, dst, dstw))
                   1402:                                return compiler->error;
                   1403:                        else
                   1404:                                return getput_arg(compiler, flags | STORE, dst_r, dst, dstw, 0, 0);
                   1405:                }
                   1406:                return SLJIT_SUCCESS;
                   1407:        }
                   1408: 
1.1.1.4 ! misho    1409:        if (op == SLJIT_NEG) {
1.1       misho    1410: #if (defined SLJIT_VERBOSE && SLJIT_VERBOSE) || (defined SLJIT_DEBUG && SLJIT_DEBUG)
                   1411:                compiler->skip_checks = 1;
                   1412: #endif
1.1.1.4 ! misho    1413:                return sljit_emit_op2(compiler, SLJIT_SUB | op_flags, dst, dstw, SLJIT_IMM, 0, src, srcw);
1.1       misho    1414:        }
                   1415: 
1.1.1.4 ! misho    1416:        flags = (GET_FLAGS(op_flags) ? SET_FLAGS : 0) | ((op_flags & SLJIT_KEEP_FLAGS) ? KEEP_FLAGS : 0);
1.1       misho    1417:        if (src & SLJIT_MEM) {
                   1418:                if (getput_arg_fast(compiler, WORD_SIZE, TMP_REG2, src, srcw))
                   1419:                        FAIL_IF(compiler->error);
                   1420:                else
                   1421:                        FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG2, src, srcw, dst, dstw));
                   1422:                src = TMP_REG2;
                   1423:        }
                   1424: 
                   1425:        if (src & SLJIT_IMM)
                   1426:                flags |= ARG2_IMM;
                   1427:        else
                   1428:                srcw = src;
                   1429: 
1.1.1.4 ! misho    1430:        emit_op_imm(compiler, flags | op, dst_r, TMP_REG1, srcw);
1.1       misho    1431: 
                   1432:        if (dst & SLJIT_MEM) {
                   1433:                if (getput_arg_fast(compiler, flags | STORE, dst_r, dst, dstw))
                   1434:                        return compiler->error;
                   1435:                else
                   1436:                        return getput_arg(compiler, flags | STORE, dst_r, dst, dstw, 0, 0);
                   1437:        }
                   1438:        return SLJIT_SUCCESS;
                   1439: }
                   1440: 
1.1.1.4 ! misho    1441: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_op2(struct sljit_compiler *compiler, sljit_si op,
        !          1442:        sljit_si dst, sljit_sw dstw,
        !          1443:        sljit_si src1, sljit_sw src1w,
        !          1444:        sljit_si src2, sljit_sw src2w)
1.1       misho    1445: {
1.1.1.4 ! misho    1446:        sljit_si dst_r, flags;
1.1       misho    1447: 
                   1448:        CHECK_ERROR();
                   1449:        check_sljit_emit_op2(compiler, op, dst, dstw, src1, src1w, src2, src2w);
1.1.1.3   misho    1450:        ADJUST_LOCAL_OFFSET(dst, dstw);
                   1451:        ADJUST_LOCAL_OFFSET(src1, src1w);
                   1452:        ADJUST_LOCAL_OFFSET(src2, src2w);
1.1       misho    1453: 
                   1454:        compiler->cache_arg = 0;
                   1455:        compiler->cache_argw = 0;
                   1456: 
1.1.1.4 ! misho    1457:        dst_r = (dst >= SLJIT_SCRATCH_REG1 && dst <= TMP_REG3) ? dst : TMP_REG1;
1.1       misho    1458:        flags = (GET_FLAGS(op) ? SET_FLAGS : 0) | ((op & SLJIT_KEEP_FLAGS) ? KEEP_FLAGS : 0);
                   1459: 
                   1460:        if ((dst & SLJIT_MEM) && !getput_arg_fast(compiler, WORD_SIZE | STORE | ARG_TEST, TMP_REG1, dst, dstw))
                   1461:                flags |= SLOW_DEST;
                   1462: 
                   1463:        if (src1 & SLJIT_MEM) {
                   1464:                if (getput_arg_fast(compiler, WORD_SIZE, TMP_REG1, src1, src1w))
                   1465:                        FAIL_IF(compiler->error);
                   1466:                else
                   1467:                        flags |= SLOW_SRC1;
                   1468:        }
                   1469:        if (src2 & SLJIT_MEM) {
                   1470:                if (getput_arg_fast(compiler, WORD_SIZE, TMP_REG2, src2, src2w))
                   1471:                        FAIL_IF(compiler->error);
                   1472:                else
                   1473:                        flags |= SLOW_SRC2;
                   1474:        }
                   1475: 
                   1476:        if ((flags & (SLOW_SRC1 | SLOW_SRC2)) == (SLOW_SRC1 | SLOW_SRC2)) {
                   1477:                if (!can_cache(src1, src1w, src2, src2w) && can_cache(src1, src1w, dst, dstw)) {
                   1478:                        FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG2, src2, src2w, src1, src1w));
                   1479:                        FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG1, src1, src1w, dst, dstw));
                   1480:                }
                   1481:                else {
                   1482:                        FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG1, src1, src1w, src2, src2w));
                   1483:                        FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG2, src2, src2w, dst, dstw));
                   1484:                }
                   1485:        }
                   1486:        else if (flags & SLOW_SRC1)
                   1487:                FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG1, src1, src1w, dst, dstw));
                   1488:        else if (flags & SLOW_SRC2)
                   1489:                FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG2, src2, src2w, dst, dstw));
                   1490: 
                   1491:        if (src1 & SLJIT_MEM)
                   1492:                src1 = TMP_REG1;
                   1493:        if (src2 & SLJIT_MEM)
                   1494:                src2 = TMP_REG2;
                   1495: 
                   1496:        if (src1 & SLJIT_IMM)
                   1497:                flags |= ARG1_IMM;
                   1498:        else
                   1499:                src1w = src1;
                   1500:        if (src2 & SLJIT_IMM)
                   1501:                flags |= ARG2_IMM;
                   1502:        else
                   1503:                src2w = src2;
                   1504: 
                   1505:        if (dst == SLJIT_UNUSED)
                   1506:                flags |= UNUSED_RETURN;
                   1507: 
                   1508:        if (GET_OPCODE(op) == SLJIT_MUL && (op & SLJIT_SET_O))
                   1509:                flags |= SET_MULOV;
                   1510: 
                   1511:        emit_op_imm(compiler, flags | GET_OPCODE(op), dst_r, src1w, src2w);
                   1512: 
                   1513:        if (dst & SLJIT_MEM) {
                   1514:                if (!(flags & SLOW_DEST)) {
                   1515:                        getput_arg_fast(compiler, WORD_SIZE | STORE, dst_r, dst, dstw);
                   1516:                        return compiler->error;
                   1517:                }
                   1518:                return getput_arg(compiler, WORD_SIZE | STORE, TMP_REG1, dst, dstw, 0, 0);
                   1519:        }
                   1520:        return SLJIT_SUCCESS;
                   1521: }
                   1522: 
1.1.1.4 ! misho    1523: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_get_register_index(sljit_si reg)
1.1.1.2   misho    1524: {
                   1525:        check_sljit_get_register_index(reg);
                   1526:        return reg_map[reg];
                   1527: }
                   1528: 
1.1.1.4 ! misho    1529: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_get_float_register_index(sljit_si reg)
        !          1530: {
        !          1531:        check_sljit_get_float_register_index(reg);
        !          1532:        return reg;
        !          1533: }
        !          1534: 
        !          1535: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_op_custom(struct sljit_compiler *compiler,
        !          1536:        void *instruction, sljit_si size)
1.1.1.2   misho    1537: {
                   1538:        CHECK_ERROR();
                   1539:        check_sljit_emit_op_custom(compiler, instruction, size);
                   1540:        SLJIT_ASSERT(size == 2 || size == 4);
                   1541: 
                   1542:        if (size == 2)
                   1543:                return push_inst16(compiler, *(sljit_uh*)instruction);
                   1544:        return push_inst32(compiler, *(sljit_ins*)instruction);
                   1545: }
                   1546: 
1.1       misho    1547: /* --------------------------------------------------------------------- */
                   1548: /*  Floating point operators                                             */
                   1549: /* --------------------------------------------------------------------- */
                   1550: 
1.1.1.4 ! misho    1551: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_is_fpu_available(void)
1.1       misho    1552: {
                   1553:        return 1;
                   1554: }
                   1555: 
1.1.1.4 ! misho    1556: #define FPU_LOAD (1 << 20)
        !          1557: 
        !          1558: static sljit_si emit_fop_mem(struct sljit_compiler *compiler, sljit_si flags, sljit_si reg, sljit_si arg, sljit_sw argw)
1.1       misho    1559: {
1.1.1.4 ! misho    1560:        sljit_sw tmp;
        !          1561:        sljit_uw imm;
        !          1562:        sljit_sw inst = VSTR_F32 | (flags & (SLJIT_SINGLE_OP | FPU_LOAD));
1.1       misho    1563: 
                   1564:        SLJIT_ASSERT(arg & SLJIT_MEM);
                   1565: 
                   1566:        /* Fast loads and stores. */
                   1567:        if (SLJIT_UNLIKELY(arg & 0xf0)) {
                   1568:                FAIL_IF(push_inst32(compiler, ADD_W | RD4(TMP_REG2) | RN4(arg & 0xf) | RM4((arg & 0xf0) >> 4) | ((argw & 0x3) << 6)));
                   1569:                arg = SLJIT_MEM | TMP_REG2;
                   1570:                argw = 0;
                   1571:        }
                   1572: 
1.1.1.4 ! misho    1573:        if ((arg & 0xf) && (argw & 0x3) == 0) {
1.1       misho    1574:                if (!(argw & ~0x3fc))
                   1575:                        return push_inst32(compiler, inst | 0x800000 | RN4(arg & 0xf) | DD4(reg) | (argw >> 2));
                   1576:                if (!(-argw & ~0x3fc))
                   1577:                        return push_inst32(compiler, inst | RN4(arg & 0xf) | DD4(reg) | (-argw >> 2));
                   1578:        }
                   1579: 
                   1580:        SLJIT_ASSERT(!(arg & 0xf0));
                   1581:        if (compiler->cache_arg == arg) {
                   1582:                tmp = argw - compiler->cache_argw;
                   1583:                if (!(tmp & ~0x3fc))
                   1584:                        return push_inst32(compiler, inst | 0x800000 | RN4(TMP_REG3) | DD4(reg) | (tmp >> 2));
                   1585:                if (!(-tmp & ~0x3fc))
                   1586:                        return push_inst32(compiler, inst | RN4(TMP_REG3) | DD4(reg) | (-tmp >> 2));
                   1587:                if (emit_set_delta(compiler, TMP_REG3, TMP_REG3, tmp) != SLJIT_ERR_UNSUPPORTED) {
                   1588:                        FAIL_IF(compiler->error);
                   1589:                        compiler->cache_argw = argw;
                   1590:                        return push_inst32(compiler, inst | 0x800000 | RN4(TMP_REG3) | DD4(reg));
                   1591:                }
                   1592:        }
                   1593: 
1.1.1.4 ! misho    1594:        if (arg & 0xf) {
        !          1595:                if (emit_set_delta(compiler, TMP_REG1, arg & 0xf, argw) != SLJIT_ERR_UNSUPPORTED) {
        !          1596:                        FAIL_IF(compiler->error);
        !          1597:                        return push_inst32(compiler, inst | 0x800000 | RN4(TMP_REG1) | DD4(reg));
        !          1598:                }
        !          1599:                imm = get_imm(argw & ~0x3fc);
        !          1600:                if (imm != INVALID_IMM) {
        !          1601:                        FAIL_IF(push_inst32(compiler, ADD_WI | RD4(TMP_REG1) | RN4(arg & 0xf) | imm));
        !          1602:                        return push_inst32(compiler, inst | 0x800000 | RN4(TMP_REG1) | DD4(reg) | ((argw & 0x3fc) >> 2));
        !          1603:                }
        !          1604:                imm = get_imm(-argw & ~0x3fc);
        !          1605:                if (imm != INVALID_IMM) {
        !          1606:                        argw = -argw;
        !          1607:                        FAIL_IF(push_inst32(compiler, SUB_WI | RD4(TMP_REG1) | RN4(arg & 0xf) | imm));
        !          1608:                        return push_inst32(compiler, inst | RN4(TMP_REG1) | DD4(reg) | ((argw & 0x3fc) >> 2));
        !          1609:                }
        !          1610:        }
        !          1611: 
1.1       misho    1612:        compiler->cache_arg = arg;
                   1613:        compiler->cache_argw = argw;
                   1614: 
                   1615:        if (SLJIT_UNLIKELY(!(arg & 0xf)))
                   1616:                FAIL_IF(load_immediate(compiler, TMP_REG3, argw));
                   1617:        else {
                   1618:                FAIL_IF(load_immediate(compiler, TMP_REG3, argw));
                   1619:                if (arg & 0xf)
                   1620:                        FAIL_IF(push_inst16(compiler, ADD | SET_REGS44(TMP_REG3, (arg & 0xf))));
                   1621:        }
                   1622:        return push_inst32(compiler, inst | 0x800000 | RN4(TMP_REG3) | DD4(reg));
                   1623: }
                   1624: 
1.1.1.4 ! misho    1625: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_fop1(struct sljit_compiler *compiler, sljit_si op,
        !          1626:        sljit_si dst, sljit_sw dstw,
        !          1627:        sljit_si src, sljit_sw srcw)
1.1       misho    1628: {
1.1.1.4 ! misho    1629:        sljit_si dst_r;
1.1       misho    1630: 
                   1631:        CHECK_ERROR();
                   1632:        check_sljit_emit_fop1(compiler, op, dst, dstw, src, srcw);
1.1.1.4 ! misho    1633:        SLJIT_COMPILE_ASSERT((SLJIT_SINGLE_OP == 0x100), float_transfer_bit_error);
1.1       misho    1634: 
                   1635:        compiler->cache_arg = 0;
                   1636:        compiler->cache_argw = 0;
1.1.1.4 ! misho    1637:        op ^= SLJIT_SINGLE_OP;
1.1       misho    1638: 
1.1.1.4 ! misho    1639:        if (GET_OPCODE(op) == SLJIT_CMPD) {
1.1       misho    1640:                if (dst & SLJIT_MEM) {
1.1.1.4 ! misho    1641:                        emit_fop_mem(compiler, (op & SLJIT_SINGLE_OP) | FPU_LOAD, TMP_FREG1, dst, dstw);
1.1       misho    1642:                        dst = TMP_FREG1;
                   1643:                }
                   1644:                if (src & SLJIT_MEM) {
1.1.1.4 ! misho    1645:                        emit_fop_mem(compiler, (op & SLJIT_SINGLE_OP) | FPU_LOAD, TMP_FREG2, src, srcw);
1.1       misho    1646:                        src = TMP_FREG2;
                   1647:                }
1.1.1.4 ! misho    1648:                FAIL_IF(push_inst32(compiler, VCMP_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst) | DM4(src)));
1.1       misho    1649:                return push_inst32(compiler, VMRS);
                   1650:        }
                   1651: 
1.1.1.4 ! misho    1652:        dst_r = (dst > SLJIT_FLOAT_REG6) ? TMP_FREG1 : dst;
1.1       misho    1653:        if (src & SLJIT_MEM) {
1.1.1.4 ! misho    1654:                emit_fop_mem(compiler, (op & SLJIT_SINGLE_OP) | FPU_LOAD, dst_r, src, srcw);
1.1       misho    1655:                src = dst_r;
                   1656:        }
                   1657: 
                   1658:        switch (GET_OPCODE(op)) {
1.1.1.4 ! misho    1659:        case SLJIT_MOVD:
1.1       misho    1660:                if (src != dst_r)
1.1.1.4 ! misho    1661:                        FAIL_IF(push_inst32(compiler, VMOV_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst_r) | DM4(src)));
1.1       misho    1662:                break;
1.1.1.4 ! misho    1663:        case SLJIT_NEGD:
        !          1664:                FAIL_IF(push_inst32(compiler, VNEG_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst_r) | DM4(src)));
1.1       misho    1665:                break;
1.1.1.4 ! misho    1666:        case SLJIT_ABSD:
        !          1667:                FAIL_IF(push_inst32(compiler, VABS_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst_r) | DM4(src)));
1.1       misho    1668:                break;
                   1669:        }
                   1670: 
                   1671:        if (dst & SLJIT_MEM)
1.1.1.4 ! misho    1672:                return emit_fop_mem(compiler, (op & SLJIT_SINGLE_OP), TMP_FREG1, dst, dstw);
1.1       misho    1673:        return SLJIT_SUCCESS;
                   1674: }
                   1675: 
1.1.1.4 ! misho    1676: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_fop2(struct sljit_compiler *compiler, sljit_si op,
        !          1677:        sljit_si dst, sljit_sw dstw,
        !          1678:        sljit_si src1, sljit_sw src1w,
        !          1679:        sljit_si src2, sljit_sw src2w)
1.1       misho    1680: {
1.1.1.4 ! misho    1681:        sljit_si dst_r;
1.1       misho    1682: 
                   1683:        CHECK_ERROR();
                   1684:        check_sljit_emit_fop2(compiler, op, dst, dstw, src1, src1w, src2, src2w);
                   1685: 
                   1686:        compiler->cache_arg = 0;
                   1687:        compiler->cache_argw = 0;
1.1.1.4 ! misho    1688:        op ^= SLJIT_SINGLE_OP;
1.1       misho    1689: 
1.1.1.4 ! misho    1690:        dst_r = (dst > SLJIT_FLOAT_REG6) ? TMP_FREG1 : dst;
1.1       misho    1691:        if (src1 & SLJIT_MEM) {
1.1.1.4 ! misho    1692:                emit_fop_mem(compiler, (op & SLJIT_SINGLE_OP) | FPU_LOAD, TMP_FREG1, src1, src1w);
1.1       misho    1693:                src1 = TMP_FREG1;
                   1694:        }
                   1695:        if (src2 & SLJIT_MEM) {
1.1.1.4 ! misho    1696:                emit_fop_mem(compiler, (op & SLJIT_SINGLE_OP) | FPU_LOAD, TMP_FREG2, src2, src2w);
1.1       misho    1697:                src2 = TMP_FREG2;
                   1698:        }
                   1699: 
                   1700:        switch (GET_OPCODE(op)) {
1.1.1.4 ! misho    1701:        case SLJIT_ADDD:
        !          1702:                FAIL_IF(push_inst32(compiler, VADD_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst_r) | DN4(src1) | DM4(src2)));
1.1       misho    1703:                break;
1.1.1.4 ! misho    1704:        case SLJIT_SUBD:
        !          1705:                FAIL_IF(push_inst32(compiler, VSUB_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst_r) | DN4(src1) | DM4(src2)));
1.1       misho    1706:                break;
1.1.1.4 ! misho    1707:        case SLJIT_MULD:
        !          1708:                FAIL_IF(push_inst32(compiler, VMUL_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst_r) | DN4(src1) | DM4(src2)));
1.1       misho    1709:                break;
1.1.1.4 ! misho    1710:        case SLJIT_DIVD:
        !          1711:                FAIL_IF(push_inst32(compiler, VDIV_F32 | (op & SLJIT_SINGLE_OP) | DD4(dst_r) | DN4(src1) | DM4(src2)));
1.1       misho    1712:                break;
                   1713:        }
                   1714: 
                   1715:        if (dst & SLJIT_MEM)
1.1.1.4 ! misho    1716:                return emit_fop_mem(compiler, (op & SLJIT_SINGLE_OP), TMP_FREG1, dst, dstw);
1.1       misho    1717:        return SLJIT_SUCCESS;
                   1718: }
                   1719: 
1.1.1.4 ! misho    1720: #undef FPU_LOAD
        !          1721: 
1.1       misho    1722: /* --------------------------------------------------------------------- */
                   1723: /*  Other instructions                                                   */
                   1724: /* --------------------------------------------------------------------- */
                   1725: 
1.1.1.4 ! misho    1726: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_fast_enter(struct sljit_compiler *compiler, sljit_si dst, sljit_sw dstw)
1.1       misho    1727: {
                   1728:        CHECK_ERROR();
1.1.1.3   misho    1729:        check_sljit_emit_fast_enter(compiler, dst, dstw);
                   1730:        ADJUST_LOCAL_OFFSET(dst, dstw);
1.1       misho    1731: 
1.1.1.4 ! misho    1732:        /* For UNUSED dst. Uncommon, but possible. */
        !          1733:        if (dst == SLJIT_UNUSED)
        !          1734:                return SLJIT_SUCCESS;
        !          1735: 
        !          1736:        if (dst <= TMP_REG3)
1.1       misho    1737:                return push_inst16(compiler, MOV | SET_REGS44(dst, TMP_REG3));
                   1738: 
1.1.1.4 ! misho    1739:        /* Memory. */
        !          1740:        if (getput_arg_fast(compiler, WORD_SIZE | STORE, TMP_REG3, dst, dstw))
        !          1741:                return compiler->error;
        !          1742:        /* TMP_REG3 is used for caching. */
        !          1743:        FAIL_IF(push_inst16(compiler, MOV | SET_REGS44(TMP_REG2, TMP_REG3)));
        !          1744:        compiler->cache_arg = 0;
        !          1745:        compiler->cache_argw = 0;
        !          1746:        return getput_arg(compiler, WORD_SIZE | STORE, TMP_REG2, dst, dstw, 0, 0);
1.1       misho    1747: }
                   1748: 
1.1.1.4 ! misho    1749: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_fast_return(struct sljit_compiler *compiler, sljit_si src, sljit_sw srcw)
1.1       misho    1750: {
                   1751:        CHECK_ERROR();
                   1752:        check_sljit_emit_fast_return(compiler, src, srcw);
1.1.1.3   misho    1753:        ADJUST_LOCAL_OFFSET(src, srcw);
1.1       misho    1754: 
1.1.1.4 ! misho    1755:        if (src <= TMP_REG3)
1.1       misho    1756:                FAIL_IF(push_inst16(compiler, MOV | SET_REGS44(TMP_REG3, src)));
                   1757:        else if (src & SLJIT_MEM) {
                   1758:                if (getput_arg_fast(compiler, WORD_SIZE, TMP_REG3, src, srcw))
                   1759:                        FAIL_IF(compiler->error);
                   1760:                else {
                   1761:                        compiler->cache_arg = 0;
                   1762:                        compiler->cache_argw = 0;
                   1763:                        FAIL_IF(getput_arg(compiler, WORD_SIZE, TMP_REG2, src, srcw, 0, 0));
                   1764:                        FAIL_IF(push_inst16(compiler, MOV | SET_REGS44(TMP_REG3, TMP_REG2)));
                   1765:                }
                   1766:        }
                   1767:        else if (src & SLJIT_IMM)
                   1768:                FAIL_IF(load_immediate(compiler, TMP_REG3, srcw));
                   1769:        return push_inst16(compiler, BLX | RN3(TMP_REG3));
                   1770: }
                   1771: 
                   1772: /* --------------------------------------------------------------------- */
                   1773: /*  Conditional instructions                                             */
                   1774: /* --------------------------------------------------------------------- */
                   1775: 
1.1.1.4 ! misho    1776: static sljit_uw get_cc(sljit_si type)
1.1       misho    1777: {
                   1778:        switch (type) {
                   1779:        case SLJIT_C_EQUAL:
                   1780:        case SLJIT_C_MUL_NOT_OVERFLOW:
                   1781:        case SLJIT_C_FLOAT_EQUAL:
                   1782:                return 0x0;
                   1783: 
                   1784:        case SLJIT_C_NOT_EQUAL:
                   1785:        case SLJIT_C_MUL_OVERFLOW:
                   1786:        case SLJIT_C_FLOAT_NOT_EQUAL:
                   1787:                return 0x1;
                   1788: 
                   1789:        case SLJIT_C_LESS:
                   1790:        case SLJIT_C_FLOAT_LESS:
                   1791:                return 0x3;
                   1792: 
                   1793:        case SLJIT_C_GREATER_EQUAL:
                   1794:        case SLJIT_C_FLOAT_GREATER_EQUAL:
                   1795:                return 0x2;
                   1796: 
                   1797:        case SLJIT_C_GREATER:
                   1798:        case SLJIT_C_FLOAT_GREATER:
                   1799:                return 0x8;
                   1800: 
                   1801:        case SLJIT_C_LESS_EQUAL:
                   1802:        case SLJIT_C_FLOAT_LESS_EQUAL:
                   1803:                return 0x9;
                   1804: 
                   1805:        case SLJIT_C_SIG_LESS:
                   1806:                return 0xb;
                   1807: 
                   1808:        case SLJIT_C_SIG_GREATER_EQUAL:
                   1809:                return 0xa;
                   1810: 
                   1811:        case SLJIT_C_SIG_GREATER:
                   1812:                return 0xc;
                   1813: 
                   1814:        case SLJIT_C_SIG_LESS_EQUAL:
                   1815:                return 0xd;
                   1816: 
                   1817:        case SLJIT_C_OVERFLOW:
1.1.1.4 ! misho    1818:        case SLJIT_C_FLOAT_UNORDERED:
1.1       misho    1819:                return 0x6;
                   1820: 
                   1821:        case SLJIT_C_NOT_OVERFLOW:
1.1.1.4 ! misho    1822:        case SLJIT_C_FLOAT_ORDERED:
1.1       misho    1823:                return 0x7;
                   1824: 
                   1825:        default: /* SLJIT_JUMP */
                   1826:                return 0xe;
                   1827:        }
                   1828: }
                   1829: 
                   1830: SLJIT_API_FUNC_ATTRIBUTE struct sljit_label* sljit_emit_label(struct sljit_compiler *compiler)
                   1831: {
                   1832:        struct sljit_label *label;
                   1833: 
                   1834:        CHECK_ERROR_PTR();
                   1835:        check_sljit_emit_label(compiler);
                   1836: 
                   1837:        if (compiler->last_label && compiler->last_label->size == compiler->size)
                   1838:                return compiler->last_label;
                   1839: 
                   1840:        label = (struct sljit_label*)ensure_abuf(compiler, sizeof(struct sljit_label));
                   1841:        PTR_FAIL_IF(!label);
                   1842:        set_label(label, compiler);
                   1843:        return label;
                   1844: }
                   1845: 
1.1.1.4 ! misho    1846: SLJIT_API_FUNC_ATTRIBUTE struct sljit_jump* sljit_emit_jump(struct sljit_compiler *compiler, sljit_si type)
1.1       misho    1847: {
                   1848:        struct sljit_jump *jump;
1.1.1.4 ! misho    1849:        sljit_si cc;
1.1       misho    1850: 
                   1851:        CHECK_ERROR_PTR();
                   1852:        check_sljit_emit_jump(compiler, type);
                   1853: 
                   1854:        jump = (struct sljit_jump*)ensure_abuf(compiler, sizeof(struct sljit_jump));
                   1855:        PTR_FAIL_IF(!jump);
                   1856:        set_jump(jump, compiler, type & SLJIT_REWRITABLE_JUMP);
                   1857:        type &= 0xff;
                   1858: 
                   1859:        /* In ARM, we don't need to touch the arguments. */
                   1860:        PTR_FAIL_IF(emit_imm32_const(compiler, TMP_REG1, 0));
                   1861:        if (type < SLJIT_JUMP) {
1.1.1.4 ! misho    1862:                jump->flags |= IS_COND;
1.1       misho    1863:                cc = get_cc(type);
                   1864:                jump->flags |= cc << 8;
                   1865:                PTR_FAIL_IF(push_inst16(compiler, IT | (cc << 4) | 0x8));
                   1866:        }
                   1867: 
                   1868:        jump->addr = compiler->size;
                   1869:        if (type <= SLJIT_JUMP)
                   1870:                PTR_FAIL_IF(push_inst16(compiler, BX | RN3(TMP_REG1)));
                   1871:        else {
                   1872:                jump->flags |= IS_BL;
                   1873:                PTR_FAIL_IF(push_inst16(compiler, BLX | RN3(TMP_REG1)));
                   1874:        }
                   1875: 
                   1876:        return jump;
                   1877: }
                   1878: 
1.1.1.4 ! misho    1879: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_ijump(struct sljit_compiler *compiler, sljit_si type, sljit_si src, sljit_sw srcw)
1.1       misho    1880: {
                   1881:        struct sljit_jump *jump;
                   1882: 
                   1883:        CHECK_ERROR();
                   1884:        check_sljit_emit_ijump(compiler, type, src, srcw);
1.1.1.3   misho    1885:        ADJUST_LOCAL_OFFSET(src, srcw);
1.1       misho    1886: 
                   1887:        /* In ARM, we don't need to touch the arguments. */
                   1888:        if (src & SLJIT_IMM) {
                   1889:                jump = (struct sljit_jump*)ensure_abuf(compiler, sizeof(struct sljit_jump));
                   1890:                FAIL_IF(!jump);
                   1891:                set_jump(jump, compiler, JUMP_ADDR | ((type >= SLJIT_FAST_CALL) ? IS_BL : 0));
                   1892:                jump->u.target = srcw;
                   1893: 
                   1894:                FAIL_IF(emit_imm32_const(compiler, TMP_REG1, 0));
                   1895:                jump->addr = compiler->size;
                   1896:                FAIL_IF(push_inst16(compiler, (type <= SLJIT_JUMP ? BX : BLX) | RN3(TMP_REG1)));
                   1897:        }
                   1898:        else {
1.1.1.4 ! misho    1899:                if (src <= TMP_REG3)
1.1       misho    1900:                        return push_inst16(compiler, (type <= SLJIT_JUMP ? BX : BLX) | RN3(src));
                   1901: 
                   1902:                FAIL_IF(emit_op_mem(compiler, WORD_SIZE, type <= SLJIT_JUMP ? TMP_PC : TMP_REG1, src, srcw));
                   1903:                if (type >= SLJIT_FAST_CALL)
                   1904:                        return push_inst16(compiler, BLX | RN3(TMP_REG1));
                   1905:        }
                   1906:        return SLJIT_SUCCESS;
                   1907: }
                   1908: 
1.1.1.4 ! misho    1909: SLJIT_API_FUNC_ATTRIBUTE sljit_si sljit_emit_op_flags(struct sljit_compiler *compiler, sljit_si op,
        !          1910:        sljit_si dst, sljit_sw dstw,
        !          1911:        sljit_si src, sljit_sw srcw,
        !          1912:        sljit_si type)
1.1       misho    1913: {
1.1.1.4 ! misho    1914:        sljit_si dst_r, flags = GET_ALL_FLAGS(op);
        !          1915:        sljit_ins ins;
1.1       misho    1916:        sljit_uw cc;
                   1917: 
                   1918:        CHECK_ERROR();
1.1.1.4 ! misho    1919:        check_sljit_emit_op_flags(compiler, op, dst, dstw, src, srcw, type);
1.1.1.3   misho    1920:        ADJUST_LOCAL_OFFSET(dst, dstw);
1.1.1.4 ! misho    1921:        ADJUST_LOCAL_OFFSET(src, srcw);
1.1       misho    1922: 
                   1923:        if (dst == SLJIT_UNUSED)
                   1924:                return SLJIT_SUCCESS;
                   1925: 
1.1.1.4 ! misho    1926:        op = GET_OPCODE(op);
1.1       misho    1927:        cc = get_cc(type);
1.1.1.4 ! misho    1928:        dst_r = (dst <= TMP_REG3) ? dst : TMP_REG2;
        !          1929: 
        !          1930:        if (op < SLJIT_ADD) {
        !          1931:                FAIL_IF(push_inst16(compiler, IT | (cc << 4) | (((cc & 0x1) ^ 0x1) << 3) | 0x4));
        !          1932:                if (reg_map[dst_r] > 7) {
        !          1933:                        FAIL_IF(push_inst32(compiler, MOV_WI | RD4(dst_r) | 1));
        !          1934:                        FAIL_IF(push_inst32(compiler, MOV_WI | RD4(dst_r) | 0));
        !          1935:                } else {
        !          1936:                        FAIL_IF(push_inst16(compiler, MOVSI | RDN3(dst_r) | 1));
        !          1937:                        FAIL_IF(push_inst16(compiler, MOVSI | RDN3(dst_r) | 0));
        !          1938:                }
        !          1939:                return dst_r == TMP_REG2 ? emit_op_mem(compiler, WORD_SIZE | STORE, TMP_REG2, dst, dstw) : SLJIT_SUCCESS;
        !          1940:        }
        !          1941: 
        !          1942:        ins = (op == SLJIT_AND ? ANDI : (op == SLJIT_OR ? ORRI : EORI));
        !          1943:        if ((op == SLJIT_OR || op == SLJIT_XOR) && dst <= TMP_REG3 && dst == src) {
        !          1944:                /* Does not change the other bits. */
1.1       misho    1945:                FAIL_IF(push_inst16(compiler, IT | (cc << 4) | 0x8));
1.1.1.4 ! misho    1946:                FAIL_IF(push_inst32(compiler, ins | RN4(src) | RD4(dst) | 1));
        !          1947:                if (flags & SLJIT_SET_E) {
        !          1948:                        /* The condition must always be set, even if the ORRI/EORI is not executed above. */
1.1       misho    1949:                        if (reg_map[dst] <= 7)
1.1.1.4 ! misho    1950:                                return push_inst16(compiler, MOVS | RD3(TMP_REG1) | RN3(dst));
        !          1951:                        return push_inst32(compiler, MOV_W | SET_FLAGS | RD4(TMP_REG1) | RM4(dst));
1.1       misho    1952:                }
                   1953:                return SLJIT_SUCCESS;
                   1954:        }
                   1955: 
1.1.1.4 ! misho    1956:        compiler->cache_arg = 0;
        !          1957:        compiler->cache_argw = 0;
        !          1958:        if (src & SLJIT_MEM) {
        !          1959:                FAIL_IF(emit_op_mem2(compiler, WORD_SIZE, TMP_REG1, src, srcw, dst, dstw));
        !          1960:                src = TMP_REG1;
        !          1961:                srcw = 0;
        !          1962:        } else if (src & SLJIT_IMM) {
        !          1963:                FAIL_IF(load_immediate(compiler, TMP_REG1, srcw));
        !          1964:                src = TMP_REG1;
        !          1965:                srcw = 0;
        !          1966:        }
1.1       misho    1967: 
                   1968:        FAIL_IF(push_inst16(compiler, IT | (cc << 4) | (((cc & 0x1) ^ 0x1) << 3) | 0x4));
1.1.1.4 ! misho    1969:        FAIL_IF(push_inst32(compiler, ins | RN4(src) | RD4(dst_r) | 1));
        !          1970:        FAIL_IF(push_inst32(compiler, ins | RN4(src) | RD4(dst_r) | 0));
        !          1971:        if (dst_r == TMP_REG2)
        !          1972:                FAIL_IF(emit_op_mem2(compiler, WORD_SIZE | STORE, TMP_REG2, dst, dstw, 0, 0));
        !          1973: 
        !          1974:        if (flags & SLJIT_SET_E) {
        !          1975:                /* The condition must always be set, even if the ORR/EORI is not executed above. */
        !          1976:                if (reg_map[dst_r] <= 7)
        !          1977:                        return push_inst16(compiler, MOVS | RD3(TMP_REG1) | RN3(dst_r));
        !          1978:                return push_inst32(compiler, MOV_W | SET_FLAGS | RD4(TMP_REG1) | RM4(dst_r));
1.1       misho    1979:        }
                   1980:        return SLJIT_SUCCESS;
                   1981: }
                   1982: 
1.1.1.4 ! misho    1983: SLJIT_API_FUNC_ATTRIBUTE struct sljit_const* sljit_emit_const(struct sljit_compiler *compiler, sljit_si dst, sljit_sw dstw, sljit_sw init_value)
1.1       misho    1984: {
                   1985:        struct sljit_const *const_;
1.1.1.4 ! misho    1986:        sljit_si dst_r;
1.1       misho    1987: 
                   1988:        CHECK_ERROR_PTR();
                   1989:        check_sljit_emit_const(compiler, dst, dstw, init_value);
1.1.1.3   misho    1990:        ADJUST_LOCAL_OFFSET(dst, dstw);
1.1       misho    1991: 
                   1992:        const_ = (struct sljit_const*)ensure_abuf(compiler, sizeof(struct sljit_const));
                   1993:        PTR_FAIL_IF(!const_);
                   1994:        set_const(const_, compiler);
                   1995: 
1.1.1.4 ! misho    1996:        dst_r = (dst <= TMP_REG3) ? dst : TMP_REG1;
1.1       misho    1997:        PTR_FAIL_IF(emit_imm32_const(compiler, dst_r, init_value));
                   1998: 
                   1999:        if (dst & SLJIT_MEM)
                   2000:                PTR_FAIL_IF(emit_op_mem(compiler, WORD_SIZE | STORE, dst_r, dst, dstw));
                   2001:        return const_;
                   2002: }
                   2003: 
                   2004: SLJIT_API_FUNC_ATTRIBUTE void sljit_set_jump_addr(sljit_uw addr, sljit_uw new_addr)
                   2005: {
                   2006:        inline_set_jump_addr(addr, new_addr, 1);
                   2007: }
                   2008: 
1.1.1.4 ! misho    2009: SLJIT_API_FUNC_ATTRIBUTE void sljit_set_const(sljit_uw addr, sljit_sw new_constant)
1.1       misho    2010: {
                   2011:        sljit_uh* inst = (sljit_uh*)addr;
                   2012:        modify_imm32_const(inst, new_constant);
                   2013:        SLJIT_CACHE_FLUSH(inst, inst + 3);
                   2014: }

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>