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

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

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