Home | History | Annotate | Download | only in assembler
      1 /*
      2  * Copyright (C) 2009 University of Szeged
      3  * All rights reserved.
      4  *
      5  * Redistribution and use in source and binary forms, with or without
      6  * modification, are permitted provided that the following conditions
      7  * are met:
      8  * 1. Redistributions of source code must retain the above copyright
      9  *    notice, this list of conditions and the following disclaimer.
     10  * 2. Redistributions in binary form must reproduce the above copyright
     11  *    notice, this list of conditions and the following disclaimer in the
     12  *    documentation and/or other materials provided with the distribution.
     13  *
     14  * THIS SOFTWARE IS PROVIDED BY UNIVERSITY OF SZEGED ``AS IS'' AND ANY
     15  * EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
     16  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
     17  * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL UNIVERSITY OF SZEGED OR
     18  * CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
     19  * EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
     20  * PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
     21  * PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY
     22  * OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
     23  * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
     24  * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
     25  */
     26 
     27 #ifndef ARMAssembler_h
     28 #define ARMAssembler_h
     29 
     30 #include <wtf/Platform.h>
     31 
     32 #if ENABLE(ASSEMBLER) && CPU(ARM_TRADITIONAL)
     33 
     34 #include "AssemblerBufferWithConstantPool.h"
     35 #include <wtf/Assertions.h>
     36 namespace JSC {
     37 
     38     typedef uint32_t ARMWord;
     39 
     40     namespace ARMRegisters {
     41         typedef enum {
     42             r0 = 0,
     43             r1,
     44             r2,
     45             r3,
     46             S0 = r3,
     47             r4,
     48             r5,
     49             r6,
     50             r7,
     51             r8,
     52             S1 = r8,
     53             r9,
     54             r10,
     55             r11,
     56             r12,
     57             r13,
     58             sp = r13,
     59             r14,
     60             lr = r14,
     61             r15,
     62             pc = r15
     63         } RegisterID;
     64 
     65         typedef enum {
     66             d0,
     67             d1,
     68             d2,
     69             d3,
     70             SD0 = d3
     71         } FPRegisterID;
     72 
     73     } // namespace ARMRegisters
     74 
     75     class ARMAssembler {
     76     public:
     77         typedef ARMRegisters::RegisterID RegisterID;
     78         typedef ARMRegisters::FPRegisterID FPRegisterID;
     79         typedef AssemblerBufferWithConstantPool<2048, 4, 4, ARMAssembler> ARMBuffer;
     80         typedef SegmentedVector<int, 64> Jumps;
     81 
     82         ARMAssembler() { }
     83 
     84         // ARM conditional constants
     85         typedef enum {
     86             EQ = 0x00000000, // Zero
     87             NE = 0x10000000, // Non-zero
     88             CS = 0x20000000,
     89             CC = 0x30000000,
     90             MI = 0x40000000,
     91             PL = 0x50000000,
     92             VS = 0x60000000,
     93             VC = 0x70000000,
     94             HI = 0x80000000,
     95             LS = 0x90000000,
     96             GE = 0xa0000000,
     97             LT = 0xb0000000,
     98             GT = 0xc0000000,
     99             LE = 0xd0000000,
    100             AL = 0xe0000000
    101         } Condition;
    102 
    103         // ARM instruction constants
    104         enum {
    105             AND = (0x0 << 21),
    106             EOR = (0x1 << 21),
    107             SUB = (0x2 << 21),
    108             RSB = (0x3 << 21),
    109             ADD = (0x4 << 21),
    110             ADC = (0x5 << 21),
    111             SBC = (0x6 << 21),
    112             RSC = (0x7 << 21),
    113             TST = (0x8 << 21),
    114             TEQ = (0x9 << 21),
    115             CMP = (0xa << 21),
    116             CMN = (0xb << 21),
    117             ORR = (0xc << 21),
    118             MOV = (0xd << 21),
    119             BIC = (0xe << 21),
    120             MVN = (0xf << 21),
    121             MUL = 0x00000090,
    122             MULL = 0x00c00090,
    123             FADDD = 0x0e300b00,
    124             FDIVD = 0x0e800b00,
    125             FSUBD = 0x0e300b40,
    126             FMULD = 0x0e200b00,
    127             FCMPD = 0x0eb40b40,
    128             DTR = 0x05000000,
    129             LDRH = 0x00100090,
    130             STRH = 0x00000090,
    131             STMDB = 0x09200000,
    132             LDMIA = 0x08b00000,
    133             FDTR = 0x0d000b00,
    134             B = 0x0a000000,
    135             BL = 0x0b000000,
    136             FMSR = 0x0e000a10,
    137             FMRS = 0x0e100a10,
    138             FSITOD = 0x0eb80bc0,
    139             FTOSID = 0x0ebd0b40,
    140             FMSTAT = 0x0ef1fa10,
    141 #if WTF_ARM_ARCH_AT_LEAST(5)
    142             CLZ = 0x016f0f10,
    143             BKPT = 0xe120070,
    144 #endif
    145 #if WTF_ARM_ARCH_AT_LEAST(7)
    146             MOVW = 0x03000000,
    147             MOVT = 0x03400000,
    148 #endif
    149         };
    150 
    151         enum {
    152             OP2_IMM = (1 << 25),
    153             OP2_IMMh = (1 << 22),
    154             OP2_INV_IMM = (1 << 26),
    155             SET_CC = (1 << 20),
    156             OP2_OFSREG = (1 << 25),
    157             DT_UP = (1 << 23),
    158             DT_WB = (1 << 21),
    159             // This flag is inlcuded in LDR and STR
    160             DT_PRE = (1 << 24),
    161             HDT_UH = (1 << 5),
    162             DT_LOAD = (1 << 20),
    163         };
    164 
    165         // Masks of ARM instructions
    166         enum {
    167             BRANCH_MASK = 0x00ffffff,
    168             NONARM = 0xf0000000,
    169             SDT_MASK = 0x0c000000,
    170             SDT_OFFSET_MASK = 0xfff,
    171         };
    172 
    173         enum {
    174             BOFFSET_MIN = -0x00800000,
    175             BOFFSET_MAX = 0x007fffff,
    176             SDT = 0x04000000,
    177         };
    178 
    179         enum {
    180             padForAlign8  = 0x00,
    181             padForAlign16 = 0x0000,
    182             padForAlign32 = 0xee120070,
    183         };
    184 
    185         static const ARMWord INVALID_IMM = 0xf0000000;
    186         static const int DefaultPrefetching = 2;
    187 
    188         class JmpSrc {
    189             friend class ARMAssembler;
    190         public:
    191             JmpSrc()
    192                 : m_offset(-1)
    193             {
    194             }
    195 
    196         private:
    197             JmpSrc(int offset)
    198                 : m_offset(offset)
    199             {
    200             }
    201 
    202             int m_offset;
    203         };
    204 
    205         class JmpDst {
    206             friend class ARMAssembler;
    207         public:
    208             JmpDst()
    209                 : m_offset(-1)
    210                 , m_used(false)
    211             {
    212             }
    213 
    214             bool isUsed() const { return m_used; }
    215             void used() { m_used = true; }
    216         private:
    217             JmpDst(int offset)
    218                 : m_offset(offset)
    219                 , m_used(false)
    220             {
    221                 ASSERT(m_offset == offset);
    222             }
    223 
    224             int m_offset : 31;
    225             int m_used : 1;
    226         };
    227 
    228         // Instruction formating
    229 
    230         void emitInst(ARMWord op, int rd, int rn, ARMWord op2)
    231         {
    232             ASSERT ( ((op2 & ~OP2_IMM) <= 0xfff) || (((op2 & ~OP2_IMMh) <= 0xfff)) );
    233             m_buffer.putInt(op | RN(rn) | RD(rd) | op2);
    234         }
    235 
    236         void and_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    237         {
    238             emitInst(static_cast<ARMWord>(cc) | AND, rd, rn, op2);
    239         }
    240 
    241         void ands_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    242         {
    243             emitInst(static_cast<ARMWord>(cc) | AND | SET_CC, rd, rn, op2);
    244         }
    245 
    246         void eor_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    247         {
    248             emitInst(static_cast<ARMWord>(cc) | EOR, rd, rn, op2);
    249         }
    250 
    251         void eors_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    252         {
    253             emitInst(static_cast<ARMWord>(cc) | EOR | SET_CC, rd, rn, op2);
    254         }
    255 
    256         void sub_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    257         {
    258             emitInst(static_cast<ARMWord>(cc) | SUB, rd, rn, op2);
    259         }
    260 
    261         void subs_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    262         {
    263             emitInst(static_cast<ARMWord>(cc) | SUB | SET_CC, rd, rn, op2);
    264         }
    265 
    266         void rsb_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    267         {
    268             emitInst(static_cast<ARMWord>(cc) | RSB, rd, rn, op2);
    269         }
    270 
    271         void rsbs_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    272         {
    273             emitInst(static_cast<ARMWord>(cc) | RSB | SET_CC, rd, rn, op2);
    274         }
    275 
    276         void add_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    277         {
    278             emitInst(static_cast<ARMWord>(cc) | ADD, rd, rn, op2);
    279         }
    280 
    281         void adds_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    282         {
    283             emitInst(static_cast<ARMWord>(cc) | ADD | SET_CC, rd, rn, op2);
    284         }
    285 
    286         void adc_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    287         {
    288             emitInst(static_cast<ARMWord>(cc) | ADC, rd, rn, op2);
    289         }
    290 
    291         void adcs_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    292         {
    293             emitInst(static_cast<ARMWord>(cc) | ADC | SET_CC, rd, rn, op2);
    294         }
    295 
    296         void sbc_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    297         {
    298             emitInst(static_cast<ARMWord>(cc) | SBC, rd, rn, op2);
    299         }
    300 
    301         void sbcs_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    302         {
    303             emitInst(static_cast<ARMWord>(cc) | SBC | SET_CC, rd, rn, op2);
    304         }
    305 
    306         void rsc_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    307         {
    308             emitInst(static_cast<ARMWord>(cc) | RSC, rd, rn, op2);
    309         }
    310 
    311         void rscs_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    312         {
    313             emitInst(static_cast<ARMWord>(cc) | RSC | SET_CC, rd, rn, op2);
    314         }
    315 
    316         void tst_r(int rn, ARMWord op2, Condition cc = AL)
    317         {
    318             emitInst(static_cast<ARMWord>(cc) | TST | SET_CC, 0, rn, op2);
    319         }
    320 
    321         void teq_r(int rn, ARMWord op2, Condition cc = AL)
    322         {
    323             emitInst(static_cast<ARMWord>(cc) | TEQ | SET_CC, 0, rn, op2);
    324         }
    325 
    326         void cmp_r(int rn, ARMWord op2, Condition cc = AL)
    327         {
    328             emitInst(static_cast<ARMWord>(cc) | CMP | SET_CC, 0, rn, op2);
    329         }
    330 
    331         void orr_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    332         {
    333             emitInst(static_cast<ARMWord>(cc) | ORR, rd, rn, op2);
    334         }
    335 
    336         void orrs_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    337         {
    338             emitInst(static_cast<ARMWord>(cc) | ORR | SET_CC, rd, rn, op2);
    339         }
    340 
    341         void mov_r(int rd, ARMWord op2, Condition cc = AL)
    342         {
    343             emitInst(static_cast<ARMWord>(cc) | MOV, rd, ARMRegisters::r0, op2);
    344         }
    345 
    346 #if WTF_ARM_ARCH_AT_LEAST(7)
    347         void movw_r(int rd, ARMWord op2, Condition cc = AL)
    348         {
    349             ASSERT((op2 | 0xf0fff) == 0xf0fff);
    350             m_buffer.putInt(static_cast<ARMWord>(cc) | MOVW | RD(rd) | op2);
    351         }
    352 
    353         void movt_r(int rd, ARMWord op2, Condition cc = AL)
    354         {
    355             ASSERT((op2 | 0xf0fff) == 0xf0fff);
    356             m_buffer.putInt(static_cast<ARMWord>(cc) | MOVT | RD(rd) | op2);
    357         }
    358 #endif
    359 
    360         void movs_r(int rd, ARMWord op2, Condition cc = AL)
    361         {
    362             emitInst(static_cast<ARMWord>(cc) | MOV | SET_CC, rd, ARMRegisters::r0, op2);
    363         }
    364 
    365         void bic_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    366         {
    367             emitInst(static_cast<ARMWord>(cc) | BIC, rd, rn, op2);
    368         }
    369 
    370         void bics_r(int rd, int rn, ARMWord op2, Condition cc = AL)
    371         {
    372             emitInst(static_cast<ARMWord>(cc) | BIC | SET_CC, rd, rn, op2);
    373         }
    374 
    375         void mvn_r(int rd, ARMWord op2, Condition cc = AL)
    376         {
    377             emitInst(static_cast<ARMWord>(cc) | MVN, rd, ARMRegisters::r0, op2);
    378         }
    379 
    380         void mvns_r(int rd, ARMWord op2, Condition cc = AL)
    381         {
    382             emitInst(static_cast<ARMWord>(cc) | MVN | SET_CC, rd, ARMRegisters::r0, op2);
    383         }
    384 
    385         void mul_r(int rd, int rn, int rm, Condition cc = AL)
    386         {
    387             m_buffer.putInt(static_cast<ARMWord>(cc) | MUL | RN(rd) | RS(rn) | RM(rm));
    388         }
    389 
    390         void muls_r(int rd, int rn, int rm, Condition cc = AL)
    391         {
    392             m_buffer.putInt(static_cast<ARMWord>(cc) | MUL | SET_CC | RN(rd) | RS(rn) | RM(rm));
    393         }
    394 
    395         void mull_r(int rdhi, int rdlo, int rn, int rm, Condition cc = AL)
    396         {
    397             m_buffer.putInt(static_cast<ARMWord>(cc) | MULL | RN(rdhi) | RD(rdlo) | RS(rn) | RM(rm));
    398         }
    399 
    400         void faddd_r(int dd, int dn, int dm, Condition cc = AL)
    401         {
    402             emitInst(static_cast<ARMWord>(cc) | FADDD, dd, dn, dm);
    403         }
    404 
    405         void fdivd_r(int dd, int dn, int dm, Condition cc = AL)
    406         {
    407             emitInst(static_cast<ARMWord>(cc) | FDIVD, dd, dn, dm);
    408         }
    409 
    410         void fsubd_r(int dd, int dn, int dm, Condition cc = AL)
    411         {
    412             emitInst(static_cast<ARMWord>(cc) | FSUBD, dd, dn, dm);
    413         }
    414 
    415         void fmuld_r(int dd, int dn, int dm, Condition cc = AL)
    416         {
    417             emitInst(static_cast<ARMWord>(cc) | FMULD, dd, dn, dm);
    418         }
    419 
    420         void fcmpd_r(int dd, int dm, Condition cc = AL)
    421         {
    422             emitInst(static_cast<ARMWord>(cc) | FCMPD, dd, 0, dm);
    423         }
    424 
    425         void ldr_imm(int rd, ARMWord imm, Condition cc = AL)
    426         {
    427             m_buffer.putIntWithConstantInt(static_cast<ARMWord>(cc) | DTR | DT_LOAD | DT_UP | RN(ARMRegisters::pc) | RD(rd), imm, true);
    428         }
    429 
    430         void ldr_un_imm(int rd, ARMWord imm, Condition cc = AL)
    431         {
    432             m_buffer.putIntWithConstantInt(static_cast<ARMWord>(cc) | DTR | DT_LOAD | DT_UP | RN(ARMRegisters::pc) | RD(rd), imm);
    433         }
    434 
    435         void dtr_u(bool isLoad, int rd, int rb, ARMWord op2, Condition cc = AL)
    436         {
    437             emitInst(static_cast<ARMWord>(cc) | DTR | (isLoad ? DT_LOAD : 0) | DT_UP, rd, rb, op2);
    438         }
    439 
    440         void dtr_ur(bool isLoad, int rd, int rb, int rm, Condition cc = AL)
    441         {
    442             emitInst(static_cast<ARMWord>(cc) | DTR | (isLoad ? DT_LOAD : 0) | DT_UP | OP2_OFSREG, rd, rb, rm);
    443         }
    444 
    445         void dtr_d(bool isLoad, int rd, int rb, ARMWord op2, Condition cc = AL)
    446         {
    447             emitInst(static_cast<ARMWord>(cc) | DTR | (isLoad ? DT_LOAD : 0), rd, rb, op2);
    448         }
    449 
    450         void dtr_dr(bool isLoad, int rd, int rb, int rm, Condition cc = AL)
    451         {
    452             emitInst(static_cast<ARMWord>(cc) | DTR | (isLoad ? DT_LOAD : 0) | OP2_OFSREG, rd, rb, rm);
    453         }
    454 
    455         void ldrh_r(int rd, int rn, int rm, Condition cc = AL)
    456         {
    457             emitInst(static_cast<ARMWord>(cc) | LDRH | HDT_UH | DT_UP | DT_PRE, rd, rn, rm);
    458         }
    459 
    460         void ldrh_d(int rd, int rb, ARMWord op2, Condition cc = AL)
    461         {
    462             emitInst(static_cast<ARMWord>(cc) | LDRH | HDT_UH | DT_PRE, rd, rb, op2);
    463         }
    464 
    465         void ldrh_u(int rd, int rb, ARMWord op2, Condition cc = AL)
    466         {
    467             emitInst(static_cast<ARMWord>(cc) | LDRH | HDT_UH | DT_UP | DT_PRE, rd, rb, op2);
    468         }
    469 
    470         void strh_r(int rn, int rm, int rd, Condition cc = AL)
    471         {
    472             emitInst(static_cast<ARMWord>(cc) | STRH | HDT_UH | DT_UP | DT_PRE, rd, rn, rm);
    473         }
    474 
    475         void fdtr_u(bool isLoad, int rd, int rb, ARMWord op2, Condition cc = AL)
    476         {
    477             ASSERT(op2 <= 0xff);
    478             emitInst(static_cast<ARMWord>(cc) | FDTR | DT_UP | (isLoad ? DT_LOAD : 0), rd, rb, op2);
    479         }
    480 
    481         void fdtr_d(bool isLoad, int rd, int rb, ARMWord op2, Condition cc = AL)
    482         {
    483             ASSERT(op2 <= 0xff);
    484             emitInst(static_cast<ARMWord>(cc) | FDTR | (isLoad ? DT_LOAD : 0), rd, rb, op2);
    485         }
    486 
    487         void push_r(int reg, Condition cc = AL)
    488         {
    489             ASSERT(ARMWord(reg) <= 0xf);
    490             m_buffer.putInt(cc | DTR | DT_WB | RN(ARMRegisters::sp) | RD(reg) | 0x4);
    491         }
    492 
    493         void pop_r(int reg, Condition cc = AL)
    494         {
    495             ASSERT(ARMWord(reg) <= 0xf);
    496             m_buffer.putInt(cc | (DTR ^ DT_PRE) | DT_LOAD | DT_UP | RN(ARMRegisters::sp) | RD(reg) | 0x4);
    497         }
    498 
    499         inline void poke_r(int reg, Condition cc = AL)
    500         {
    501             dtr_d(false, ARMRegisters::sp, 0, reg, cc);
    502         }
    503 
    504         inline void peek_r(int reg, Condition cc = AL)
    505         {
    506             dtr_u(true, reg, ARMRegisters::sp, 0, cc);
    507         }
    508 
    509         void fmsr_r(int dd, int rn, Condition cc = AL)
    510         {
    511             emitInst(static_cast<ARMWord>(cc) | FMSR, rn, dd, 0);
    512         }
    513 
    514         void fmrs_r(int rd, int dn, Condition cc = AL)
    515         {
    516             emitInst(static_cast<ARMWord>(cc) | FMRS, rd, dn, 0);
    517         }
    518 
    519         void fsitod_r(int dd, int dm, Condition cc = AL)
    520         {
    521             emitInst(static_cast<ARMWord>(cc) | FSITOD, dd, 0, dm);
    522         }
    523 
    524         void ftosid_r(int fd, int dm, Condition cc = AL)
    525         {
    526             emitInst(static_cast<ARMWord>(cc) | FTOSID, fd, 0, dm);
    527         }
    528 
    529         void fmstat(Condition cc = AL)
    530         {
    531             m_buffer.putInt(static_cast<ARMWord>(cc) | FMSTAT);
    532         }
    533 
    534 #if WTF_ARM_ARCH_AT_LEAST(5)
    535         void clz_r(int rd, int rm, Condition cc = AL)
    536         {
    537             m_buffer.putInt(static_cast<ARMWord>(cc) | CLZ | RD(rd) | RM(rm));
    538         }
    539 #endif
    540 
    541         void bkpt(ARMWord value)
    542         {
    543 #if WTF_ARM_ARCH_AT_LEAST(5)
    544             m_buffer.putInt(BKPT | ((value & 0xff0) << 4) | (value & 0xf));
    545 #else
    546             // Cannot access to Zero memory address
    547             dtr_dr(true, ARMRegisters::S0, ARMRegisters::S0, ARMRegisters::S0);
    548 #endif
    549         }
    550 
    551         static ARMWord lsl(int reg, ARMWord value)
    552         {
    553             ASSERT(reg <= ARMRegisters::pc);
    554             ASSERT(value <= 0x1f);
    555             return reg | (value << 7) | 0x00;
    556         }
    557 
    558         static ARMWord lsr(int reg, ARMWord value)
    559         {
    560             ASSERT(reg <= ARMRegisters::pc);
    561             ASSERT(value <= 0x1f);
    562             return reg | (value << 7) | 0x20;
    563         }
    564 
    565         static ARMWord asr(int reg, ARMWord value)
    566         {
    567             ASSERT(reg <= ARMRegisters::pc);
    568             ASSERT(value <= 0x1f);
    569             return reg | (value << 7) | 0x40;
    570         }
    571 
    572         static ARMWord lsl_r(int reg, int shiftReg)
    573         {
    574             ASSERT(reg <= ARMRegisters::pc);
    575             ASSERT(shiftReg <= ARMRegisters::pc);
    576             return reg | (shiftReg << 8) | 0x10;
    577         }
    578 
    579         static ARMWord lsr_r(int reg, int shiftReg)
    580         {
    581             ASSERT(reg <= ARMRegisters::pc);
    582             ASSERT(shiftReg <= ARMRegisters::pc);
    583             return reg | (shiftReg << 8) | 0x30;
    584         }
    585 
    586         static ARMWord asr_r(int reg, int shiftReg)
    587         {
    588             ASSERT(reg <= ARMRegisters::pc);
    589             ASSERT(shiftReg <= ARMRegisters::pc);
    590             return reg | (shiftReg << 8) | 0x50;
    591         }
    592 
    593         // General helpers
    594 
    595         int size()
    596         {
    597             return m_buffer.size();
    598         }
    599 
    600         void ensureSpace(int insnSpace, int constSpace)
    601         {
    602             m_buffer.ensureSpace(insnSpace, constSpace);
    603         }
    604 
    605         int sizeOfConstantPool()
    606         {
    607             return m_buffer.sizeOfConstantPool();
    608         }
    609 
    610         JmpDst label()
    611         {
    612             return JmpDst(m_buffer.size());
    613         }
    614 
    615         JmpDst align(int alignment)
    616         {
    617             while (!m_buffer.isAligned(alignment))
    618                 mov_r(ARMRegisters::r0, ARMRegisters::r0);
    619 
    620             return label();
    621         }
    622 
    623         JmpSrc jmp(Condition cc = AL, int useConstantPool = 0)
    624         {
    625             ensureSpace(sizeof(ARMWord), sizeof(ARMWord));
    626             int s = m_buffer.uncheckedSize();
    627             ldr_un_imm(ARMRegisters::pc, 0xffffffff, cc);
    628             m_jumps.append(s | (useConstantPool & 0x1));
    629             return JmpSrc(s);
    630         }
    631 
    632         void* executableCopy(ExecutablePool* allocator);
    633 
    634         // Patching helpers
    635 
    636         static ARMWord* getLdrImmAddress(ARMWord* insn)
    637         {
    638             // Must be an ldr ..., [pc +/- imm]
    639             ASSERT((*insn & 0x0f7f0000) == 0x051f0000);
    640 
    641             ARMWord addr = reinterpret_cast<ARMWord>(insn) + DefaultPrefetching * sizeof(ARMWord);
    642             if (*insn & DT_UP)
    643                 return reinterpret_cast<ARMWord*>(addr + (*insn & SDT_OFFSET_MASK));
    644             return reinterpret_cast<ARMWord*>(addr - (*insn & SDT_OFFSET_MASK));
    645         }
    646 
    647         static ARMWord* getLdrImmAddressOnPool(ARMWord* insn, uint32_t* constPool)
    648         {
    649             // Must be an ldr ..., [pc +/- imm]
    650             ASSERT((*insn & 0x0f7f0000) == 0x051f0000);
    651 
    652             if (*insn & 0x1)
    653                 return reinterpret_cast<ARMWord*>(constPool + ((*insn & SDT_OFFSET_MASK) >> 1));
    654             return getLdrImmAddress(insn);
    655         }
    656 
    657         static void patchPointerInternal(intptr_t from, void* to)
    658         {
    659             ARMWord* insn = reinterpret_cast<ARMWord*>(from);
    660             ARMWord* addr = getLdrImmAddress(insn);
    661             *addr = reinterpret_cast<ARMWord>(to);
    662         }
    663 
    664         static ARMWord patchConstantPoolLoad(ARMWord load, ARMWord value)
    665         {
    666             value = (value << 1) + 1;
    667             ASSERT(!(value & ~0xfff));
    668             return (load & ~0xfff) | value;
    669         }
    670 
    671         static void patchConstantPoolLoad(void* loadAddr, void* constPoolAddr);
    672 
    673         // Patch pointers
    674 
    675         static void linkPointer(void* code, JmpDst from, void* to)
    676         {
    677             patchPointerInternal(reinterpret_cast<intptr_t>(code) + from.m_offset, to);
    678         }
    679 
    680         static void repatchInt32(void* from, int32_t to)
    681         {
    682             patchPointerInternal(reinterpret_cast<intptr_t>(from), reinterpret_cast<void*>(to));
    683         }
    684 
    685         static void repatchPointer(void* from, void* to)
    686         {
    687             patchPointerInternal(reinterpret_cast<intptr_t>(from), to);
    688         }
    689 
    690         static void repatchLoadPtrToLEA(void* from)
    691         {
    692             // On arm, this is a patch from LDR to ADD. It is restricted conversion,
    693             // from special case to special case, altough enough for its purpose
    694             ARMWord* insn = reinterpret_cast<ARMWord*>(from);
    695             ASSERT((*insn & 0x0ff00f00) == 0x05900000);
    696 
    697             *insn = (*insn & 0xf00ff0ff) | 0x02800000;
    698             ExecutableAllocator::cacheFlush(insn, sizeof(ARMWord));
    699         }
    700 
    701         // Linkers
    702 
    703         void linkJump(JmpSrc from, JmpDst to)
    704         {
    705             ARMWord* insn = reinterpret_cast<ARMWord*>(m_buffer.data()) + (from.m_offset / sizeof(ARMWord));
    706             ARMWord* addr = getLdrImmAddressOnPool(insn, m_buffer.poolAddress());
    707             *addr = static_cast<ARMWord>(to.m_offset);
    708         }
    709 
    710         static void linkJump(void* code, JmpSrc from, void* to)
    711         {
    712             patchPointerInternal(reinterpret_cast<intptr_t>(code) + from.m_offset, to);
    713         }
    714 
    715         static void relinkJump(void* from, void* to)
    716         {
    717             patchPointerInternal(reinterpret_cast<intptr_t>(from) - sizeof(ARMWord), to);
    718         }
    719 
    720         static void linkCall(void* code, JmpSrc from, void* to)
    721         {
    722             patchPointerInternal(reinterpret_cast<intptr_t>(code) + from.m_offset, to);
    723         }
    724 
    725         static void relinkCall(void* from, void* to)
    726         {
    727             patchPointerInternal(reinterpret_cast<intptr_t>(from) - sizeof(ARMWord), to);
    728         }
    729 
    730         // Address operations
    731 
    732         static void* getRelocatedAddress(void* code, JmpSrc jump)
    733         {
    734             return reinterpret_cast<void*>(reinterpret_cast<ARMWord*>(code) + jump.m_offset / sizeof(ARMWord) + 1);
    735         }
    736 
    737         static void* getRelocatedAddress(void* code, JmpDst label)
    738         {
    739             return reinterpret_cast<void*>(reinterpret_cast<ARMWord*>(code) + label.m_offset / sizeof(ARMWord));
    740         }
    741 
    742         // Address differences
    743 
    744         static int getDifferenceBetweenLabels(JmpDst from, JmpSrc to)
    745         {
    746             return (to.m_offset + sizeof(ARMWord)) - from.m_offset;
    747         }
    748 
    749         static int getDifferenceBetweenLabels(JmpDst from, JmpDst to)
    750         {
    751             return to.m_offset - from.m_offset;
    752         }
    753 
    754         static unsigned getCallReturnOffset(JmpSrc call)
    755         {
    756             return call.m_offset + sizeof(ARMWord);
    757         }
    758 
    759         // Handle immediates
    760 
    761         static ARMWord getOp2Byte(ARMWord imm)
    762         {
    763             ASSERT(imm <= 0xff);
    764             return OP2_IMMh | (imm & 0x0f) | ((imm & 0xf0) << 4) ;
    765         }
    766 
    767         static ARMWord getOp2(ARMWord imm);
    768 
    769 #if WTF_ARM_ARCH_AT_LEAST(7)
    770         static ARMWord getImm16Op2(ARMWord imm)
    771         {
    772             if (imm <= 0xffff)
    773                 return (imm & 0xf000) << 4 | (imm & 0xfff);
    774             return INVALID_IMM;
    775         }
    776 #endif
    777         ARMWord getImm(ARMWord imm, int tmpReg, bool invert = false);
    778         void moveImm(ARMWord imm, int dest);
    779         ARMWord encodeComplexImm(ARMWord imm, int dest);
    780 
    781         // Memory load/store helpers
    782 
    783         void dataTransfer32(bool isLoad, RegisterID srcDst, RegisterID base, int32_t offset);
    784         void baseIndexTransfer32(bool isLoad, RegisterID srcDst, RegisterID base, RegisterID index, int scale, int32_t offset);
    785         void doubleTransfer(bool isLoad, FPRegisterID srcDst, RegisterID base, int32_t offset);
    786 
    787         // Constant pool hnadlers
    788 
    789         static ARMWord placeConstantPoolBarrier(int offset)
    790         {
    791             offset = (offset - sizeof(ARMWord)) >> 2;
    792             ASSERT((offset <= BOFFSET_MAX && offset >= BOFFSET_MIN));
    793             return AL | B | (offset & BRANCH_MASK);
    794         }
    795 
    796     private:
    797         ARMWord RM(int reg)
    798         {
    799             ASSERT(reg <= ARMRegisters::pc);
    800             return reg;
    801         }
    802 
    803         ARMWord RS(int reg)
    804         {
    805             ASSERT(reg <= ARMRegisters::pc);
    806             return reg << 8;
    807         }
    808 
    809         ARMWord RD(int reg)
    810         {
    811             ASSERT(reg <= ARMRegisters::pc);
    812             return reg << 12;
    813         }
    814 
    815         ARMWord RN(int reg)
    816         {
    817             ASSERT(reg <= ARMRegisters::pc);
    818             return reg << 16;
    819         }
    820 
    821         static ARMWord getConditionalField(ARMWord i)
    822         {
    823             return i & 0xf0000000;
    824         }
    825 
    826         int genInt(int reg, ARMWord imm, bool positive);
    827 
    828         ARMBuffer m_buffer;
    829         Jumps m_jumps;
    830     };
    831 
    832 } // namespace JSC
    833 
    834 #endif // ENABLE(ASSEMBLER) && CPU(ARM_TRADITIONAL)
    835 
    836 #endif // ARMAssembler_h
    837