Home | History | Annotate | Download | only in x86
      1 /*
      2  * x86 expression handling
      3  *
      4  *  Copyright (C) 2001-2007  Peter Johnson
      5  *
      6  * Redistribution and use in source and binary forms, with or without
      7  * modification, are permitted provided that the following conditions
      8  * are met:
      9  * 1. Redistributions of source code must retain the above copyright
     10  *    notice, this list of conditions and the following disclaimer.
     11  * 2. Redistributions in binary form must reproduce the above copyright
     12  *    notice, this list of conditions and the following disclaimer in the
     13  *    documentation and/or other materials provided with the distribution.
     14  *
     15  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND OTHER CONTRIBUTORS ``AS IS''
     16  * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
     17  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
     18  * ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR OTHER CONTRIBUTORS BE
     19  * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
     20  * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
     21  * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
     22  * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
     23  * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
     24  * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
     25  * POSSIBILITY OF SUCH DAMAGE.
     26  */
     27 #include <util.h>
     28 
     29 #include <libyasm.h>
     30 
     31 #include "x86arch.h"
     32 
     33 
     34 typedef struct x86_checkea_reg3264_data {
     35     int *regs;          /* total multiplier for each reg */
     36     unsigned char vsib_mode;
     37     unsigned char bits;
     38     unsigned char addrsize;
     39 } x86_checkea_reg3264_data;
     40 
     41 /* Only works if ei->type == EXPR_REG (doesn't check).
     42  * Overwrites ei with intnum of 0 (to eliminate regs from the final expr).
     43  */
     44 static /*@null@*/ /*@dependent@*/ int *
     45 x86_expr_checkea_get_reg3264(yasm_expr__item *ei, int *regnum,
     46                              /*returned*/ void *d)
     47 {
     48     x86_checkea_reg3264_data *data = d;
     49 
     50     switch ((x86_expritem_reg_size)(ei->data.reg & ~0xFUL)) {
     51         case X86_REG32:
     52             if (data->addrsize != 32)
     53                 return 0;
     54             *regnum = (unsigned int)(ei->data.reg & 0xF);
     55             break;
     56         case X86_REG64:
     57             if (data->addrsize != 64)
     58                 return 0;
     59             *regnum = (unsigned int)(ei->data.reg & 0xF);
     60             break;
     61         case X86_XMMREG:
     62             if (data->vsib_mode != 1)
     63                 return 0;
     64             if (data->bits != 64 && (ei->data.reg & 0x8) == 0x8)
     65                 return 0;
     66             *regnum = 17+(unsigned int)(ei->data.reg & 0xF);
     67             break;
     68         case X86_YMMREG:
     69             if (data->vsib_mode != 2)
     70                 return 0;
     71             if (data->bits != 64 && (ei->data.reg & 0x8) == 0x8)
     72                 return 0;
     73             *regnum = 17+(unsigned int)(ei->data.reg & 0xF);
     74             break;
     75         case X86_RIP:
     76             if (data->bits != 64)
     77                 return 0;
     78             *regnum = 16;
     79             break;
     80         default:
     81             return 0;
     82     }
     83 
     84     /* overwrite with 0 to eliminate register from displacement expr */
     85     ei->type = YASM_EXPR_INT;
     86     ei->data.intn = yasm_intnum_create_uint(0);
     87 
     88     /* we're okay */
     89     return &data->regs[*regnum];
     90 }
     91 
     92 typedef struct x86_checkea_reg16_data {
     93     int bx, si, di, bp;         /* total multiplier for each reg */
     94 } x86_checkea_reg16_data;
     95 
     96 /* Only works if ei->type == EXPR_REG (doesn't check).
     97  * Overwrites ei with intnum of 0 (to eliminate regs from the final expr).
     98  */
     99 static /*@null@*/ int *
    100 x86_expr_checkea_get_reg16(yasm_expr__item *ei, int *regnum, void *d)
    101 {
    102     x86_checkea_reg16_data *data = d;
    103     /* in order: ax,cx,dx,bx,sp,bp,si,di */
    104     /*@-nullassign@*/
    105     static int *reg16[8] = {0,0,0,0,0,0,0,0};
    106     /*@=nullassign@*/
    107 
    108     reg16[3] = &data->bx;
    109     reg16[5] = &data->bp;
    110     reg16[6] = &data->si;
    111     reg16[7] = &data->di;
    112 
    113     /* don't allow 32-bit registers */
    114     if ((ei->data.reg & ~0xFUL) != X86_REG16)
    115         return 0;
    116 
    117     /* & 7 for sanity check */
    118     *regnum = (unsigned int)(ei->data.reg & 0x7);
    119 
    120     /* only allow BX, SI, DI, BP */
    121     if (!reg16[*regnum])
    122         return 0;
    123 
    124     /* overwrite with 0 to eliminate register from displacement expr */
    125     ei->type = YASM_EXPR_INT;
    126     ei->data.intn = yasm_intnum_create_uint(0);
    127 
    128     /* we're okay */
    129     return reg16[*regnum];
    130 }
    131 
    132 /* Distribute over registers to help bring them to the topmost level of e.
    133  * Also check for illegal operations against registers.
    134  * Returns 0 if something was illegal, 1 if legal and nothing in e changed,
    135  * and 2 if legal and e needs to be simplified.
    136  *
    137  * Only half joking: Someday make this/checkea able to accept crazy things
    138  *  like: (bx+di)*(bx+di)-bx*bx-2*bx*di-di*di+di?  Probably not: NASM never
    139  *  accepted such things, and it's doubtful such an expn is valid anyway
    140  *  (even though the above one is).  But even macros would be hard-pressed
    141  *  to generate something like this.
    142  *
    143  * e must already have been simplified for this function to work properly
    144  * (as it doesn't think things like SUB are valid).
    145  *
    146  * IMPLEMENTATION NOTE: About the only thing this function really needs to
    147  * "distribute" is: (non-float-expn or intnum) * (sum expn of registers).
    148  *
    149  * TODO: Clean up this code, make it easier to understand.
    150  */
    151 static int
    152 x86_expr_checkea_distcheck_reg(yasm_expr **ep, unsigned int bits)
    153 {
    154     yasm_expr *e = *ep;
    155     int i;
    156     int havereg = -1, havereg_expr = -1;
    157     int retval = 1;     /* default to legal, no changes */
    158 
    159     for (i=0; i<e->numterms; i++) {
    160         switch (e->terms[i].type) {
    161             case YASM_EXPR_REG:
    162                 /* Check op to make sure it's valid to use w/register. */
    163                 switch (e->op) {
    164                     case YASM_EXPR_MUL:
    165                         /* Check for reg*reg */
    166                         if (havereg != -1)
    167                             return 0;
    168                         break;
    169                     case YASM_EXPR_ADD:
    170                     case YASM_EXPR_IDENT:
    171                         break;
    172                     default:
    173                         return 0;
    174                 }
    175                 havereg = i;
    176                 break;
    177             case YASM_EXPR_FLOAT:
    178                 /* Floats not allowed. */
    179                 return 0;
    180             case YASM_EXPR_EXPR:
    181                 if (yasm_expr__contains(e->terms[i].data.expn,
    182                                         YASM_EXPR_REG)) {
    183                     int ret2;
    184 
    185                     /* Check op to make sure it's valid to use w/register. */
    186                     if (e->op != YASM_EXPR_ADD && e->op != YASM_EXPR_MUL)
    187                         return 0;
    188                     /* Check for reg*reg */
    189                     if (e->op == YASM_EXPR_MUL && havereg != -1)
    190                         return 0;
    191                     havereg = i;
    192                     havereg_expr = i;
    193                     /* Recurse to check lower levels */
    194                     ret2 =
    195                         x86_expr_checkea_distcheck_reg(&e->terms[i].data.expn,
    196                                                        bits);
    197                     if (ret2 == 0)
    198                         return 0;
    199                     if (ret2 == 2)
    200                         retval = 2;
    201                 } else if (yasm_expr__contains(e->terms[i].data.expn,
    202                                                YASM_EXPR_FLOAT))
    203                     return 0;   /* Disallow floats */
    204                 break;
    205             default:
    206                 break;
    207         }
    208     }
    209 
    210     /* just exit if no registers were used */
    211     if (havereg == -1)
    212         return retval;
    213 
    214     /* Distribute */
    215     if (e->op == YASM_EXPR_MUL && havereg_expr != -1) {
    216         yasm_expr *ne;
    217 
    218         retval = 2;     /* we're going to change it */
    219 
    220         /* The reg expn *must* be EXPR_ADD at this point.  Sanity check. */
    221         if (e->terms[havereg_expr].type != YASM_EXPR_EXPR ||
    222             e->terms[havereg_expr].data.expn->op != YASM_EXPR_ADD)
    223             yasm_internal_error(N_("Register expression not ADD or EXPN"));
    224 
    225         /* Iterate over each term in reg expn */
    226         for (i=0; i<e->terms[havereg_expr].data.expn->numterms; i++) {
    227             /* Copy everything EXCEPT havereg_expr term into new expression */
    228             ne = yasm_expr__copy_except(e, havereg_expr);
    229             assert(ne != NULL);
    230             /* Copy reg expr term into uncopied (empty) term in new expn */
    231             ne->terms[havereg_expr] =
    232                 e->terms[havereg_expr].data.expn->terms[i]; /* struct copy */
    233             /* Overwrite old reg expr term with new expn */
    234             e->terms[havereg_expr].data.expn->terms[i].type = YASM_EXPR_EXPR;
    235             e->terms[havereg_expr].data.expn->terms[i].data.expn = ne;
    236         }
    237 
    238         /* Replace e with expanded reg expn */
    239         ne = e->terms[havereg_expr].data.expn;
    240         e->terms[havereg_expr].type = YASM_EXPR_NONE;   /* don't delete it! */
    241         yasm_expr_destroy(e);                       /* but everything else */
    242         e = ne;
    243         /*@-onlytrans@*/
    244         *ep = ne;
    245         /*@=onlytrans@*/
    246     }
    247 
    248     return retval;
    249 }
    250 
    251 /* Simplify and determine if expression is superficially valid:
    252  * Valid expr should be [(int-equiv expn)]+[reg*(int-equiv expn)+...]
    253  * where the [...] parts are optional.
    254  *
    255  * Don't simplify out constant identities if we're looking for an indexreg: we
    256  * may need the multiplier for determining what the indexreg is!
    257  *
    258  * Returns 1 if invalid register usage, 2 if unable to determine all values,
    259  * and 0 if all values successfully determined and saved in data.
    260  */
    261 static int
    262 x86_expr_checkea_getregusage(yasm_expr **ep, /*@null@*/ int *indexreg,
    263     int *pcrel, unsigned int bits, void *data,
    264     int *(*get_reg)(yasm_expr__item *ei, int *regnum, void *d))
    265 {
    266     int i;
    267     int *reg;
    268     int regnum;
    269     int indexval = 0;
    270     int indexmult = 0;
    271     yasm_expr *e, *wrt;
    272 
    273     /*@-unqualifiedtrans@*/
    274     *ep = yasm_expr__level_tree(*ep, 1, 1, indexreg == 0, 0, NULL, NULL);
    275 
    276     /* Check for WRT rip first */
    277     wrt = yasm_expr_extract_wrt(ep);
    278     if (wrt && wrt->op == YASM_EXPR_IDENT &&
    279         wrt->terms[0].type == YASM_EXPR_REG) {
    280         if (bits != 64) {   /* only valid in 64-bit mode */
    281             yasm_expr_destroy(wrt);
    282             return 1;
    283         }
    284         reg = get_reg(&wrt->terms[0], &regnum, data);
    285         if (!reg || regnum != 16) { /* only accept rip */
    286             yasm_expr_destroy(wrt);
    287             return 1;
    288         }
    289         (*reg)++;
    290 
    291         /* Delete WRT.  Set pcrel to 1 to indicate to x86
    292          * bytecode code to do PC-relative displacement transform.
    293          */
    294         *pcrel = 1;
    295         yasm_expr_destroy(wrt);
    296     } else if (wrt) {
    297         yasm_expr_destroy(wrt);
    298         return 1;
    299     }
    300 
    301     /*@=unqualifiedtrans@*/
    302     assert(*ep != NULL);
    303     e = *ep;
    304     switch (x86_expr_checkea_distcheck_reg(ep, bits)) {
    305         case 0:
    306             return 1;
    307         case 2:
    308             /* Need to simplify again */
    309             *ep = yasm_expr__level_tree(*ep, 1, 1, indexreg == 0, 0, NULL,
    310                                         NULL);
    311             e = *ep;
    312             break;
    313         default:
    314             break;
    315     }
    316 
    317     switch (e->op) {
    318         case YASM_EXPR_ADD:
    319             /* Prescan for non-int multipliers against a reg.
    320              * This is invalid due to the optimizer structure.
    321              */
    322             for (i=0; i<e->numterms; i++)
    323                 if (e->terms[i].type == YASM_EXPR_EXPR) {
    324                     yasm_expr__order_terms(e->terms[i].data.expn);
    325                     if (e->terms[i].data.expn->terms[0].type ==
    326                         YASM_EXPR_REG) {
    327                         if (e->terms[i].data.expn->numterms > 2)
    328                             return 1;
    329                         if (e->terms[i].data.expn->terms[1].type !=
    330                             YASM_EXPR_INT)
    331                             return 1;
    332                     }
    333                 }
    334 
    335             /*@fallthrough@*/
    336         case YASM_EXPR_IDENT:
    337             /* Check each term for register (and possible multiplier). */
    338             for (i=0; i<e->numterms; i++) {
    339                 if (e->terms[i].type == YASM_EXPR_REG) {
    340                     reg = get_reg(&e->terms[i], &regnum, data);
    341                     if (!reg)
    342                         return 1;
    343                     (*reg)++;
    344                     /* Let last, largest multipler win indexreg */
    345                     if (indexreg && *reg > 0 && indexval <= *reg &&
    346                         !indexmult) {
    347                         *indexreg = regnum;
    348                         indexval = *reg;
    349                     }
    350                 } else if (e->terms[i].type == YASM_EXPR_EXPR) {
    351                     /* Already ordered from ADD above, just grab the value.
    352                      * Sanity check for EXPR_INT.
    353                      */
    354                     if (e->terms[i].data.expn->terms[0].type ==
    355                         YASM_EXPR_REG) {
    356                         long delta;
    357                         if (e->terms[i].data.expn->terms[1].type !=
    358                             YASM_EXPR_INT)
    359                             yasm_internal_error(
    360                                 N_("Non-integer value in reg expn"));
    361                         reg = get_reg(&e->terms[i].data.expn->terms[0],
    362                                       &regnum, data);
    363                         if (!reg)
    364                             return 1;
    365                         delta = yasm_intnum_get_int(
    366                             e->terms[i].data.expn->terms[1].data.intn);
    367                         (*reg) += delta;
    368                         /* Let last, largest multipler win indexreg */
    369                         if (indexreg && delta > 0 && indexval <= *reg) {
    370                             *indexreg = regnum;
    371                             indexval = *reg;
    372                             indexmult = 1;
    373                         } else if (indexreg && *indexreg == regnum &&
    374                                    delta < 0 && *reg <= 1) {
    375                             *indexreg = -1;
    376                             indexval = 0;
    377                             indexmult = 0;
    378                         }
    379                     }
    380                 }
    381             }
    382             break;
    383         case YASM_EXPR_MUL:
    384             /* Here, too, check for non-int multipliers against a reg. */
    385             yasm_expr__order_terms(e);
    386             if (e->terms[0].type == YASM_EXPR_REG) {
    387                 long delta;
    388                 if (e->numterms > 2)
    389                     return 1;
    390                 if (e->terms[1].type != YASM_EXPR_INT)
    391                     return 1;
    392                 reg = get_reg(&e->terms[0], &regnum, data);
    393                 if (!reg)
    394                     return 1;
    395                 delta = yasm_intnum_get_int(e->terms[1].data.intn);
    396                 (*reg) += delta;
    397                 if (indexreg)
    398                 {
    399                     if (delta < 0 && *reg <= 1)
    400                     {
    401                         *indexreg = -1;
    402                         indexval = 0;
    403                         indexmult = 0;
    404                     }
    405                     else
    406                         *indexreg = regnum;
    407                 }
    408             }
    409             break;
    410         case YASM_EXPR_SEGOFF:
    411             /* No registers are allowed on either side. */
    412             if (yasm_expr__contains(e, YASM_EXPR_REG))
    413                 return 1;
    414             break;
    415         default:
    416             /* Should never get here! */
    417             yasm_internal_error(N_("unexpected expr op"));
    418     }
    419 
    420     /* Simplify expr, which is now really just the displacement. This
    421      * should get rid of the 0's we put in for registers in the callback.
    422      */
    423     *ep = yasm_expr_simplify(*ep, 0);
    424     /* e = *ep; */
    425 
    426     return 0;
    427 }
    428 
    429 /* Calculate the displacement length, if possible.
    430  * Takes several extra inputs so it can be used by both 32-bit and 16-bit
    431  * expressions:
    432  *  wordsize=16 for 16-bit, =32 for 32-bit.
    433  *  noreg=1 if the *ModRM byte* has no registers used.
    434  *  dispreq=1 if a displacement value is *required* (even if =0).
    435  * Returns 0 if successfully calculated, 1 if not.
    436  */
    437 /*@-nullstate@*/
    438 static int
    439 x86_checkea_calc_displen(x86_effaddr *x86_ea, unsigned int wordsize, int noreg,
    440                          int dispreq)
    441 {
    442     /*@null@*/ /*@only@*/ yasm_intnum *num;
    443 
    444     x86_ea->valid_modrm = 0;    /* default to not yet valid */
    445 
    446     switch (x86_ea->ea.disp.size) {
    447         case 0:
    448             break;
    449         /* If not 0, the displacement length was forced; set the Mod bits
    450          * appropriately and we're done with the ModRM byte.
    451          */
    452         case 8:
    453             /* Byte is only a valid override if there are registers in the
    454              * EA.  With no registers, we must have a 16/32 value.
    455              */
    456             if (noreg) {
    457                 yasm_warn_set(YASM_WARN_IMPLICIT_SIZE_OVERRIDE,
    458                               N_("invalid displacement size; fixed"));
    459                 x86_ea->ea.disp.size = wordsize;
    460             } else
    461                 x86_ea->modrm |= 0100;
    462             x86_ea->valid_modrm = 1;
    463             return 0;
    464         case 16:
    465         case 32:
    466             /* Don't allow changing displacement different from BITS setting
    467              * directly; require an address-size override to change it.
    468              */
    469             if (wordsize != x86_ea->ea.disp.size) {
    470                 yasm_error_set(YASM_ERROR_VALUE,
    471                     N_("invalid effective address (displacement size)"));
    472                 return 1;
    473             }
    474             if (!noreg)
    475                 x86_ea->modrm |= 0200;
    476             x86_ea->valid_modrm = 1;
    477             return 0;
    478         default:
    479             /* we shouldn't ever get any other size! */
    480             yasm_internal_error(N_("strange EA displacement size"));
    481     }
    482 
    483     /* The displacement length hasn't been forced (or the forcing wasn't
    484      * valid), try to determine what it is.
    485      */
    486     if (noreg) {
    487         /* No register in ModRM expression, so it must be disp16/32,
    488          * and as the Mod bits are set to 0 by the caller, we're done
    489          * with the ModRM byte.
    490          */
    491         x86_ea->ea.disp.size = wordsize;
    492         x86_ea->valid_modrm = 1;
    493         return 0;
    494     }
    495 
    496     if (dispreq) {
    497         /* for BP/EBP, there *must* be a displacement value, but we
    498          * may not know the size (8 or 16/32) for sure right now.
    499          */
    500         x86_ea->ea.need_nonzero_len = 1;
    501     }
    502 
    503     if (x86_ea->ea.disp.rel) {
    504         /* Relative displacement; basically all object formats need non-byte
    505          * for relocation here, so just do that. (TODO: handle this
    506          * differently?)
    507          */
    508         x86_ea->ea.disp.size = wordsize;
    509         x86_ea->modrm |= 0200;
    510         x86_ea->valid_modrm = 1;
    511         return 0;
    512     }
    513 
    514     /* At this point there's 3 possibilities for the displacement:
    515      *  - None (if =0)
    516      *  - signed 8 bit (if in -128 to 127 range)
    517      *  - 16/32 bit (word size)
    518      * For now, check intnum value right now; if it's not 0,
    519      * assume 8 bit and set up for allowing 16 bit later.
    520      * FIXME: The complex expression equaling zero is probably a rare case,
    521      * so we ignore it for now.
    522      */
    523     num = yasm_value_get_intnum(&x86_ea->ea.disp, NULL, 0);
    524     if (!num) {
    525         /* Still has unknown values. */
    526         x86_ea->ea.need_nonzero_len = 1;
    527         x86_ea->modrm |= 0100;
    528         x86_ea->valid_modrm = 1;
    529         return 0;
    530     }
    531 
    532     /* Figure out what size displacement we will have. */
    533     if (yasm_intnum_is_zero(num) && !x86_ea->ea.need_nonzero_len) {
    534         /* If we know that the displacement is 0 right now,
    535          * go ahead and delete the expr and make it so no
    536          * displacement value is included in the output.
    537          * The Mod bits of ModRM are set to 0 above, and
    538          * we're done with the ModRM byte!
    539          */
    540         yasm_value_delete(&x86_ea->ea.disp);
    541         x86_ea->ea.need_disp = 0;
    542     } else if (yasm_intnum_in_range(num, -128, 127)) {
    543         /* It fits into a signed byte */
    544         x86_ea->ea.disp.size = 8;
    545         x86_ea->modrm |= 0100;
    546     } else {
    547         /* It's a 16/32-bit displacement */
    548         x86_ea->ea.disp.size = wordsize;
    549         x86_ea->modrm |= 0200;
    550     }
    551     x86_ea->valid_modrm = 1;    /* We're done with ModRM */
    552 
    553     yasm_intnum_destroy(num);
    554     return 0;
    555 }
    556 /*@=nullstate@*/
    557 
    558 static int
    559 x86_expr_checkea_getregsize_callback(yasm_expr__item *ei, void *d)
    560 {
    561     unsigned char *addrsize = (unsigned char *)d;
    562 
    563     if (ei->type == YASM_EXPR_REG) {
    564         switch ((x86_expritem_reg_size)(ei->data.reg & ~0xFUL)) {
    565             case X86_REG16:
    566                 *addrsize = 16;
    567                 break;
    568             case X86_REG32:
    569                 *addrsize = 32;
    570                 break;
    571             case X86_REG64:
    572             case X86_RIP:
    573                 *addrsize = 64;
    574                 break;
    575             default:
    576                 return 0;
    577         }
    578         return 1;
    579     } else
    580         return 0;
    581 }
    582 
    583 int
    584 yasm_x86__expr_checkea(x86_effaddr *x86_ea, unsigned char *addrsize,
    585                        unsigned int bits, int address16_op, unsigned char *rex,
    586                        yasm_bytecode *bc)
    587 {
    588     int retval;
    589 
    590     if (*addrsize == 0) {
    591         /* we need to figure out the address size from what we know about:
    592          * - the displacement length
    593          * - what registers are used in the expression
    594          * - the bits setting
    595          */
    596         switch (x86_ea->ea.disp.size) {
    597             case 16:
    598                 /* must be 16-bit */
    599                 *addrsize = 16;
    600                 break;
    601             case 64:
    602                 /* We have to support this for the MemOffs case, but it's
    603                  * otherwise illegal.  It's also illegal in non-64-bit mode.
    604                  */
    605                 if (x86_ea->need_modrm || x86_ea->need_sib) {
    606                     yasm_error_set(YASM_ERROR_VALUE,
    607                         N_("invalid effective address (displacement size)"));
    608                     return 1;
    609                 }
    610                 *addrsize = 64;
    611                 break;
    612             case 32:
    613                 /* Must be 32-bit in 16-bit or 32-bit modes.  In 64-bit mode,
    614                  * we don't know unless we look at the registers, except in the
    615                  * MemOffs case (see the end of this function).
    616                  */
    617                 if (bits != 64 || (!x86_ea->need_modrm && !x86_ea->need_sib)) {
    618                     *addrsize = 32;
    619                     break;
    620                 }
    621                 /*@fallthrough@*/
    622             default:
    623                 /* If SIB is required, but we're in 16-bit mode, set to 32. */
    624                 if (bits == 16 && x86_ea->need_sib == 1) {
    625                     *addrsize = 32;
    626                     break;
    627                 }
    628                 /* check for use of 16 or 32-bit registers; if none are used
    629                  * default to bits setting.
    630                  */
    631                 if (!x86_ea->ea.disp.abs ||
    632                     !yasm_expr__traverse_leaves_in(x86_ea->ea.disp.abs,
    633                         addrsize, x86_expr_checkea_getregsize_callback))
    634                     *addrsize = bits;
    635                 /* TODO: Add optional warning here if switched address size
    636                  * from bits setting just by register use.. eg [ax] in
    637                  * 32-bit mode would generate a warning.
    638                  */
    639         }
    640     }
    641 
    642     if ((*addrsize == 32 || *addrsize == 64) &&
    643         ((x86_ea->need_modrm && !x86_ea->valid_modrm) ||
    644          (x86_ea->need_sib && !x86_ea->valid_sib))) {
    645         int i;
    646         unsigned char low3;
    647         typedef enum {
    648             REG3264_NONE = -1,
    649             REG3264_EAX = 0,
    650             REG3264_ECX,
    651             REG3264_EDX,
    652             REG3264_EBX,
    653             REG3264_ESP,
    654             REG3264_EBP,
    655             REG3264_ESI,
    656             REG3264_EDI,
    657             REG64_R8,
    658             REG64_R9,
    659             REG64_R10,
    660             REG64_R11,
    661             REG64_R12,
    662             REG64_R13,
    663             REG64_R14,
    664             REG64_R15,
    665             REG64_RIP,
    666             SIMDREGS
    667         } reg3264type;
    668         int reg3264mult[33] =
    669             {0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
    670              0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0};
    671         x86_checkea_reg3264_data reg3264_data;
    672         int basereg = REG3264_NONE;     /* "base" register (for SIB) */
    673         int indexreg = REG3264_NONE;    /* "index" register (for SIB) */
    674         int regcount = 17;              /* normally don't check SIMD regs */
    675 
    676         if (x86_ea->vsib_mode != 0)
    677             regcount = 33;
    678 
    679         /* We can only do 64-bit addresses in 64-bit mode. */
    680         if (*addrsize == 64 && bits != 64) {
    681             yasm_error_set(YASM_ERROR_TYPE,
    682                 N_("invalid effective address (64-bit in non-64-bit mode)"));
    683             return 1;
    684         }
    685 
    686         if (x86_ea->ea.pc_rel && bits != 64) {
    687             yasm_warn_set(YASM_WARN_GENERAL,
    688                 N_("RIP-relative directive ignored in non-64-bit mode"));
    689             x86_ea->ea.pc_rel = 0;
    690         }
    691 
    692         reg3264_data.regs = reg3264mult;
    693         reg3264_data.vsib_mode = x86_ea->vsib_mode;
    694         reg3264_data.bits = bits;
    695         reg3264_data.addrsize = *addrsize;
    696         if (x86_ea->ea.disp.abs) {
    697             int pcrel = 0;
    698             switch (x86_expr_checkea_getregusage
    699                     (&x86_ea->ea.disp.abs, &indexreg, &pcrel, bits,
    700                      &reg3264_data, x86_expr_checkea_get_reg3264)) {
    701                 case 1:
    702                     yasm_error_set(YASM_ERROR_VALUE,
    703                                    N_("invalid effective address"));
    704                     return 1;
    705                 case 2:
    706                     if (pcrel)
    707                         yasm_value_set_curpos_rel(&x86_ea->ea.disp, bc, 1);
    708                     return 2;
    709                 default:
    710                     if (pcrel)
    711                         yasm_value_set_curpos_rel(&x86_ea->ea.disp, bc, 1);
    712                     break;
    713             }
    714         }
    715 
    716         /* If indexreg mult is 0, discard it.
    717          * This is possible because of the way indexreg is found in
    718          * expr_checkea_getregusage().
    719          */
    720         if (indexreg != REG3264_NONE && reg3264mult[indexreg] == 0)
    721             indexreg = REG3264_NONE;
    722 
    723         /* Find a basereg (*1, but not indexreg), if there is one.
    724          * Also, if an indexreg hasn't been assigned, try to find one.
    725          * Meanwhile, check to make sure there's no negative register mults.
    726          */
    727         for (i=0; i<regcount; i++) {
    728             if (reg3264mult[i] < 0) {
    729                 yasm_error_set(YASM_ERROR_VALUE,
    730                                N_("invalid effective address"));
    731                 return 1;
    732             }
    733             if (i != indexreg && reg3264mult[i] == 1 &&
    734                 basereg == REG3264_NONE)
    735                 basereg = i;
    736             else if (indexreg == REG3264_NONE && reg3264mult[i] > 0)
    737                 indexreg = i;
    738         }
    739 
    740         if (x86_ea->vsib_mode != 0) {
    741             /* For VSIB, the SIMD register needs to go into the indexreg.
    742              * Also check basereg (must be a GPR if present) and indexreg
    743              * (must be a SIMD register).
    744              */
    745             if (basereg >= SIMDREGS &&
    746                 (indexreg == REG3264_NONE || reg3264mult[indexreg] == 1)) {
    747                 int temp = basereg;
    748                 basereg = indexreg;
    749                 indexreg = temp;
    750             }
    751             if (basereg >= REG64_RIP || indexreg < SIMDREGS) {
    752                 yasm_error_set(YASM_ERROR_VALUE,
    753                                N_("invalid effective address"));
    754                 return 1;
    755             }
    756         } else if (indexreg != REG3264_NONE && basereg == REG3264_NONE)
    757             /* Handle certain special cases of indexreg mults when basereg is
    758              * empty.
    759              */
    760             switch (reg3264mult[indexreg]) {
    761                 case 1:
    762                     /* Only optimize this way if nosplit wasn't specified */
    763                     if (!x86_ea->ea.nosplit) {
    764                         basereg = indexreg;
    765                         indexreg = -1;
    766                     }
    767                     break;
    768                 case 2:
    769                     /* Only split if nosplit wasn't specified */
    770                     if (!x86_ea->ea.nosplit) {
    771                         basereg = indexreg;
    772                         reg3264mult[indexreg] = 1;
    773                     }
    774                     break;
    775                 case 3:
    776                 case 5:
    777                 case 9:
    778                     basereg = indexreg;
    779                     reg3264mult[indexreg]--;
    780                     break;
    781             }
    782 
    783         /* Make sure there's no other registers than the basereg and indexreg
    784          * we just found.
    785          */
    786         for (i=0; i<regcount; i++)
    787             if (i != basereg && i != indexreg && reg3264mult[i] != 0) {
    788                 yasm_error_set(YASM_ERROR_VALUE,
    789                                N_("invalid effective address"));
    790                 return 1;
    791             }
    792 
    793         /* Check the index multiplier value for validity if present. */
    794         if (indexreg != REG3264_NONE && reg3264mult[indexreg] != 1 &&
    795             reg3264mult[indexreg] != 2 && reg3264mult[indexreg] != 4 &&
    796             reg3264mult[indexreg] != 8) {
    797             yasm_error_set(YASM_ERROR_VALUE, N_("invalid effective address"));
    798             return 1;
    799         }
    800 
    801         /* ESP is not a legal indexreg. */
    802         if (indexreg == REG3264_ESP) {
    803             /* If mult>1 or basereg is ESP also, there's no way to make it
    804              * legal.
    805              */
    806             if (reg3264mult[REG3264_ESP] > 1 || basereg == REG3264_ESP) {
    807                 yasm_error_set(YASM_ERROR_VALUE,
    808                                N_("invalid effective address"));
    809                 return 1;
    810             }
    811             /* If mult==1 and basereg is not ESP, swap indexreg w/basereg. */
    812             indexreg = basereg;
    813             basereg = REG3264_ESP;
    814         }
    815 
    816         /* RIP is only legal if it's the ONLY register used. */
    817         if (indexreg == REG64_RIP ||
    818             (basereg == REG64_RIP && indexreg != REG3264_NONE)) {
    819             yasm_error_set(YASM_ERROR_VALUE, N_("invalid effective address"));
    820             return 1;
    821         }
    822 
    823         /* At this point, we know the base and index registers and that the
    824          * memory expression is (essentially) valid.  Now build the ModRM and
    825          * (optional) SIB bytes.
    826          */
    827 
    828         /* If we're supposed to be RIP-relative and there's no register
    829          * usage, change to RIP-relative.
    830          */
    831         if (basereg == REG3264_NONE && indexreg == REG3264_NONE &&
    832             x86_ea->ea.pc_rel) {
    833             basereg = REG64_RIP;
    834             yasm_value_set_curpos_rel(&x86_ea->ea.disp, bc, 1);
    835         }
    836 
    837         /* First determine R/M (Mod is later determined from disp size) */
    838         x86_ea->need_modrm = 1; /* we always need ModRM */
    839         if (basereg == REG3264_NONE && indexreg == REG3264_NONE) {
    840             /* Just a disp32: in 64-bit mode the RM encoding is used for RIP
    841              * offset addressing, so we need to use the SIB form instead.
    842              */
    843             if (bits == 64) {
    844                 x86_ea->modrm |= 4;
    845                 x86_ea->need_sib = 1;
    846             } else {
    847                 x86_ea->modrm |= 5;
    848                 x86_ea->sib = 0;
    849                 x86_ea->valid_sib = 0;
    850                 x86_ea->need_sib = 0;
    851             }
    852         } else if (basereg == REG64_RIP) {
    853             x86_ea->modrm |= 5;
    854             x86_ea->sib = 0;
    855             x86_ea->valid_sib = 0;
    856             x86_ea->need_sib = 0;
    857             /* RIP always requires a 32-bit displacement */
    858             x86_ea->valid_modrm = 1;
    859             x86_ea->ea.disp.size = 32;
    860             return 0;
    861         } else if (indexreg == REG3264_NONE) {
    862             /* basereg only */
    863             /* Don't need to go to the full effort of determining what type
    864              * of register basereg is, as x86_set_rex_from_reg doesn't pay
    865              * much attention.
    866              */
    867             if (yasm_x86__set_rex_from_reg(rex, &low3,
    868                                            (unsigned int)(X86_REG64 | basereg),
    869                                            bits, X86_REX_B))
    870                 return 1;
    871             x86_ea->modrm |= low3;
    872             /* we don't need an SIB *unless* basereg is ESP or R12 */
    873             if (basereg == REG3264_ESP || basereg == REG64_R12)
    874                 x86_ea->need_sib = 1;
    875             else {
    876                 x86_ea->sib = 0;
    877                 x86_ea->valid_sib = 0;
    878                 x86_ea->need_sib = 0;
    879             }
    880         } else {
    881             /* index or both base and index */
    882             x86_ea->modrm |= 4;
    883             x86_ea->need_sib = 1;
    884         }
    885 
    886         /* Determine SIB if needed */
    887         if (x86_ea->need_sib == 1) {
    888             x86_ea->sib = 0;    /* start with 0 */
    889 
    890             /* Special case: no basereg */
    891             if (basereg == REG3264_NONE)
    892                 x86_ea->sib |= 5;
    893             else {
    894                 if (yasm_x86__set_rex_from_reg(rex, &low3, (unsigned int)
    895                                                (X86_REG64 | basereg), bits,
    896                                                X86_REX_B))
    897                     return 1;
    898                 x86_ea->sib |= low3;
    899             }
    900 
    901             /* Put in indexreg, checking for none case */
    902             if (indexreg == REG3264_NONE)
    903                 x86_ea->sib |= 040;
    904                 /* Any scale field is valid, just leave at 0. */
    905             else {
    906                 if (indexreg >= SIMDREGS) {
    907                     if (yasm_x86__set_rex_from_reg(rex, &low3,
    908                             (unsigned int)(X86_XMMREG | (indexreg-SIMDREGS)),
    909                             bits, X86_REX_X))
    910                         return 1;
    911                 } else {
    912                     if (yasm_x86__set_rex_from_reg(rex, &low3,
    913                             (unsigned int)(X86_REG64 | indexreg),
    914                             bits, X86_REX_X))
    915                         return 1;
    916                 }
    917                 x86_ea->sib |= low3 << 3;
    918                 /* Set scale field, 1 case -> 0, so don't bother. */
    919                 switch (reg3264mult[indexreg]) {
    920                     case 2:
    921                         x86_ea->sib |= 0100;
    922                         break;
    923                     case 4:
    924                         x86_ea->sib |= 0200;
    925                         break;
    926                     case 8:
    927                         x86_ea->sib |= 0300;
    928                         break;
    929                 }
    930             }
    931 
    932             x86_ea->valid_sib = 1;      /* Done with SIB */
    933         }
    934 
    935         /* Calculate displacement length (if possible) */
    936         retval = x86_checkea_calc_displen
    937             (x86_ea, 32, basereg == REG3264_NONE,
    938              basereg == REG3264_EBP || basereg == REG64_R13);
    939         return retval;
    940     } else if (*addrsize == 16 && x86_ea->need_modrm && !x86_ea->valid_modrm) {
    941         static const unsigned char modrm16[16] = {
    942             0006 /* disp16  */, 0007 /* [BX]    */, 0004 /* [SI]    */,
    943             0000 /* [BX+SI] */, 0005 /* [DI]    */, 0001 /* [BX+DI] */,
    944             0377 /* invalid */, 0377 /* invalid */, 0006 /* [BP]+d  */,
    945             0377 /* invalid */, 0002 /* [BP+SI] */, 0377 /* invalid */,
    946             0003 /* [BP+DI] */, 0377 /* invalid */, 0377 /* invalid */,
    947             0377 /* invalid */
    948         };
    949         x86_checkea_reg16_data reg16mult = {0, 0, 0, 0};
    950         enum {
    951             HAVE_NONE = 0,
    952             HAVE_BX = 1<<0,
    953             HAVE_SI = 1<<1,
    954             HAVE_DI = 1<<2,
    955             HAVE_BP = 1<<3
    956         } havereg = HAVE_NONE;
    957 
    958         /* 64-bit mode does not allow 16-bit addresses */
    959         if (bits == 64 && !address16_op) {
    960             yasm_error_set(YASM_ERROR_TYPE,
    961                 N_("16-bit addresses not supported in 64-bit mode"));
    962             return 1;
    963         }
    964 
    965         /* 16-bit cannot have SIB */
    966         x86_ea->sib = 0;
    967         x86_ea->valid_sib = 0;
    968         x86_ea->need_sib = 0;
    969 
    970         if (x86_ea->ea.disp.abs) {
    971             int pcrel = 0;
    972             switch (x86_expr_checkea_getregusage
    973                     (&x86_ea->ea.disp.abs, (int *)NULL, &pcrel, bits,
    974                      &reg16mult, x86_expr_checkea_get_reg16)) {
    975                 case 1:
    976                     yasm_error_set(YASM_ERROR_VALUE,
    977                                    N_("invalid effective address"));
    978                     return 1;
    979                 case 2:
    980                     if (pcrel)
    981                         yasm_value_set_curpos_rel(&x86_ea->ea.disp, bc, 1);
    982                     return 2;
    983                 default:
    984                     if (pcrel)
    985                         yasm_value_set_curpos_rel(&x86_ea->ea.disp, bc, 1);
    986                     break;
    987             }
    988         }
    989 
    990         /* reg multipliers not 0 or 1 are illegal. */
    991         if (reg16mult.bx & ~1 || reg16mult.si & ~1 || reg16mult.di & ~1 ||
    992             reg16mult.bp & ~1) {
    993             yasm_error_set(YASM_ERROR_VALUE, N_("invalid effective address"));
    994             return 1;
    995         }
    996 
    997         /* Set havereg appropriately */
    998         if (reg16mult.bx > 0)
    999             havereg |= HAVE_BX;
   1000         if (reg16mult.si > 0)
   1001             havereg |= HAVE_SI;
   1002         if (reg16mult.di > 0)
   1003             havereg |= HAVE_DI;
   1004         if (reg16mult.bp > 0)
   1005             havereg |= HAVE_BP;
   1006 
   1007         /* Check the modrm value for invalid combinations. */
   1008         if (modrm16[havereg] & 0070) {
   1009             yasm_error_set(YASM_ERROR_VALUE, N_("invalid effective address"));
   1010             return 1;
   1011         }
   1012 
   1013         /* Set ModRM byte for registers */
   1014         x86_ea->modrm |= modrm16[havereg];
   1015 
   1016         /* Calculate displacement length (if possible) */
   1017         retval = x86_checkea_calc_displen
   1018             (x86_ea, 16, havereg == HAVE_NONE, havereg == HAVE_BP);
   1019         return retval;
   1020     } else if (!x86_ea->need_modrm && !x86_ea->need_sib) {
   1021         /* Special case for MOV MemOffs opcode: displacement but no modrm. */
   1022         switch (*addrsize) {
   1023             case 64:
   1024                 if (bits != 64) {
   1025                     yasm_error_set(YASM_ERROR_TYPE,
   1026                         N_("invalid effective address (64-bit in non-64-bit mode)"));
   1027                     return 1;
   1028                 }
   1029                 x86_ea->ea.disp.size = 64;
   1030                 break;
   1031             case 32:
   1032                 x86_ea->ea.disp.size = 32;
   1033                 break;
   1034             case 16:
   1035                 /* 64-bit mode does not allow 16-bit addresses */
   1036                 if (bits == 64 && !address16_op) {
   1037                     yasm_error_set(YASM_ERROR_TYPE,
   1038                         N_("16-bit addresses not supported in 64-bit mode"));
   1039                     return 1;
   1040                 }
   1041                 x86_ea->ea.disp.size = 16;
   1042                 break;
   1043         }
   1044     }
   1045     return 0;
   1046 }
   1047 
   1048 int
   1049 yasm_x86__floatnum_tobytes(yasm_arch *arch, const yasm_floatnum *flt,
   1050                            unsigned char *buf, size_t destsize, size_t valsize,
   1051                            size_t shift, int warn)
   1052 {
   1053     if (!yasm_floatnum_check_size(flt, valsize)) {
   1054         yasm_error_set(YASM_ERROR_FLOATING_POINT,
   1055                        N_("invalid floating point constant size"));
   1056         return 1;
   1057     }
   1058 
   1059     yasm_floatnum_get_sized(flt, buf, destsize, valsize, shift, 0, warn);
   1060     return 0;
   1061 }
   1062