| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864 | {    Copyright (c) 1998-2002 by Florian Klaempfl    Generate x86 assembler for in/case nodes    This program is free software; you can redistribute it and/or modify    it under the terms of the GNU General Public License as published by    the Free Software Foundation; either version 2 of the License, or    (at your option) any later version.    This program is distributed in the hope that it will be useful,    but WITHOUT ANY WARRANTY; without even the implied warranty of    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the    GNU General Public License for more details.    You should have received a copy of the GNU General Public License    along with this program; if not, write to the Free Software    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. ****************************************************************************}unit nx86set;{$i fpcdefs.inc}interface    uses      globtype,      node,nset,pass_1,ncgset;    type       tx86innode = class(tinnode)         procedure pass_generate_code;override;         function pass_1 : tnode;override;       end;      tx86casenode = class(tcgcasenode)         function  has_jumptable : boolean;override;         procedure genjumptable(hp : pcaselabel;min_,max_ : aint);override;         procedure genlinearlist(hp : pcaselabel);override;      end;implementation    uses      systems,constexp,      verbose,globals,      symconst,symdef,defutil,      aasmbase,aasmtai,aasmdata,aasmcpu,      cgbase,pass_2,tgobj,      ncon,      cpubase,      cga,cgobj,hlcgobj,cgutils,ncgutil,      cgx86,      procinfo;{*****************************************************************************                                  TX86CASENODE*****************************************************************************}    function tx86casenode.has_jumptable : boolean;      begin        has_jumptable:=true;      end;    procedure tx86casenode.genjumptable(hp : pcaselabel;min_,max_ : aint);      var        table : tasmlabel;        last : TConstExprInt;        indexreg : tregister;        href : treference;        jtlist: tasmlist;        opcgsize: tcgsize;        jumpreg: tregister;        labeltyp: taiconst_type;        procedure genitem(list:TAsmList;t : pcaselabel);          var            i : aint;          begin            if assigned(t^.less) then              genitem(list,t^.less);            { fill possible hole }            i:=last.svalue+1;            while i<=t^._low.svalue-1 do              begin                list.concat(Tai_const.Create_type_sym(labeltyp,elselabel));                inc(i);              end;            i:=t^._low.svalue;            while i<=t^._high.svalue do              begin                list.concat(Tai_const.Create_type_sym(labeltyp,blocklabel(t^.blockid)));                inc(i);              end;            last:=t^._high;            if assigned(t^.greater) then              genitem(list,t^.greater);          end;      begin        last:=min_;        { This generates near pointers on i8086 }        labeltyp:=aitconst_ptr;        opcgsize:=def_cgsize(opsize);        if not(jumptable_no_range) then          begin             { a <= x <= b <-> unsigned(x-a) <= (b-a) }             cg.a_op_const_reg(current_asmdata.CurrAsmList,OP_SUB,opcgsize,aint(min_),hregister);             { case expr greater than max_ => goto elselabel }             cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,opcgsize,OC_A,aint(max_)-aint(min_),hregister,elselabel);             min_:=0;          end;        current_asmdata.getglobaldatalabel(table);        { make it a 32bit register }        indexreg:=cg.makeregsize(current_asmdata.CurrAsmList,hregister,OS_INT);        cg.a_load_reg_reg(current_asmdata.CurrAsmList,opcgsize,OS_INT,hregister,indexreg);        { create reference }        reference_reset_symbol(href,table,0,sizeof(pint));        href.offset:=(-aint(min_))*sizeof(aint);        href.index:=indexreg;{$ifdef i8086}        cg.a_op_const_reg(current_asmdata.CurrAsmList,OP_SHL,OS_INT,1,indexreg);{$else i8086}        href.scalefactor:=sizeof(aint);{$endif i8086}        if (not (target_info.system in [system_i386_darwin,system_i386_iphonesim])) and           (cs_create_pic in current_settings.moduleswitches) then          begin            labeltyp:=aitconst_gotoff_symbol;            jumpreg:=cg.getintregister(current_asmdata.CurrAsmList,OS_ADDR);            cg.a_load_ref_reg(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,href,jumpreg);            cg.a_op_reg_reg(current_asmdata.CurrAsmList,OP_ADD,OS_ADDR,current_procinfo.got,jumpreg);            emit_reg(A_JMP,S_NO,jumpreg);          end        else          emit_ref(A_JMP,S_NO,href);        { generate jump table }        if (target_info.system in [system_i386_darwin,system_i386_iphonesim]) then          jtlist:=current_asmdata.asmlists[al_const]        else          jtlist:=current_procinfo.aktlocaldata;        new_section(jtlist,sec_rodata,current_procinfo.procdef.mangledname,sizeof(aint));        jtlist.concat(Tai_label.Create(table));        genitem(jtlist,hp);      end;    procedure tx86casenode.genlinearlist(hp : pcaselabel);      var        first : boolean;        lastrange : boolean;        last : TConstExprInt;        cond_lt,cond_le : tresflags;        opcgsize: tcgsize;        procedure genitem(t : pcaselabel);          begin             if assigned(t^.less) then               genitem(t^.less);             { need we to test the first value }             if first and (t^._low>get_min_value(left.resultdef)) then               begin                 cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,opcgsize,jmp_lt,aint(t^._low.svalue),hregister,elselabel);               end;             if t^._low=t^._high then               begin                  if t^._low-last=0 then                    cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList, opcgsize, OC_EQ,0,hregister,blocklabel(t^.blockid))                  else                    begin                      cg.a_op_const_reg(current_asmdata.CurrAsmList, OP_SUB, opcgsize, aint(t^._low.svalue-last.svalue), hregister);                      cg.a_jmp_flags(current_asmdata.CurrAsmList,F_E,blocklabel(t^.blockid));                    end;                  last:=t^._low;                  lastrange:=false;               end             else               begin                  { it begins with the smallest label, if the value }                  { is even smaller then jump immediately to the    }                  { ELSE-label                                }                  if first then                    begin                       { have we to ajust the first value ? }                       if (t^._low>get_min_value(left.resultdef)) or (get_min_value(left.resultdef)<>0) then                         cg.a_op_const_reg(current_asmdata.CurrAsmList, OP_SUB, opcgsize, aint(t^._low.svalue), hregister);                    end                  else                    begin                      { if there is no unused label between the last and the }                      { present label then the lower limit can be checked    }                      { immediately. else check the range in between:       }                      { we need to use A_SUB, if cond_lt uses the carry flags                        because A_DEC does not set the correct flags, therefor                        using a_op_const_reg(OP_SUB) is not possible }                      if (cond_lt in [F_C,F_NC,F_A,F_AE,F_B,F_BE]) and (aint(t^._low.svalue-last.svalue)=1) then                        emit_const_reg(A_SUB,TCGSize2OpSize[opcgsize],aint(t^._low.svalue-last.svalue),hregister)                      else                        cg.a_op_const_reg(current_asmdata.CurrAsmList, OP_SUB, opcgsize, aint(t^._low.svalue-last.svalue), hregister);                      { no jump necessary here if the new range starts at                        at the value following the previous one           }                      if ((t^._low-last) <> 1) or                         (not lastrange) then                        cg.a_jmp_flags(current_asmdata.CurrAsmList,cond_lt,elselabel);                    end;                  { we need to use A_SUB, if cond_le uses the carry flags                    because A_DEC does not set the correct flags, therefor                    using a_op_const_reg(OP_SUB) is not possible }                  if (cond_le in [F_C,F_NC,F_A,F_AE,F_B,F_BE]) and (aint(t^._high.svalue-t^._low.svalue)=1) then                    emit_const_reg(A_SUB,TCGSize2OpSize[opcgsize],aint(t^._high.svalue-t^._low.svalue),hregister)                  else                    cg.a_op_const_reg(current_asmdata.CurrAsmList, OP_SUB, opcgsize, aint(t^._high.svalue-t^._low.svalue), hregister);                  cg.a_jmp_flags(current_asmdata.CurrAsmList,cond_le,blocklabel(t^.blockid));                  last:=t^._high;                  lastrange:=true;               end;             first:=false;             if assigned(t^.greater) then               genitem(t^.greater);          end;        begin           opcgsize:=def_cgsize(opsize);           if with_sign then             begin                cond_lt:=F_L;                cond_le:=F_LE;             end           else              begin                cond_lt:=F_B;                cond_le:=F_BE;             end;           { do we need to generate cmps? }{$ifdef i8086}           if (with_sign and (min_label<0)) or (opcgsize in [OS_32, OS_S32]) then{$else i8086}           if (with_sign and (min_label<0)) then{$endif i8086}             genlinearcmplist(hp)           else             begin                last:=0;                lastrange:=false;                first:=true;                genitem(hp);                cg.a_jmp_always(current_asmdata.CurrAsmList,elselabel);             end;        end;{*****************************************************************************                              TX86INNODE*****************************************************************************}    function tx86innode.pass_1 : tnode;      begin         result:=nil;         { this is the only difference from the generic version }         expectloc:=LOC_FLAGS;         firstpass(right);         firstpass(left);         if codegenerror then           exit;      end;    procedure tx86innode.pass_generate_code;       type         Tsetpart=record           range : boolean;      {Part is a range.}           start,stop : byte;    {Start/stop when range; Stop=element when an element.}         end;       var         hreg,hreg2,         pleftreg   : tregister;         opsize     : tcgsize;         opdef      : torddef;         orgopsize  : tcgsize;         setparts   : array[1..8] of Tsetpart;         setbase    : aint;         adjustment : longint;         l,l2       : tasmlabel;         i,numparts : byte;         genjumps,         use_small,         ranges     : boolean;{$ifdef CORRECT_SET_IN_FPC}         AM         : tasmop;{$endif CORRECT_SET_IN_FPC}{$ifdef i8086}         extra_offset_reg: TRegister;{$endif i8086}         function analizeset(Aset:pconstset;is_small:boolean):boolean;           var             compares,maxcompares:word;             i:byte;           begin             if tnormalset(Aset^)=[] then                {The expression...                    if expr in []                 ...is allways false. It should be optimized away in the                 resultdef pass, and thus never occur here. Since we                 do generate wrong code for it, do internalerror.}                internalerror(2002072301);             analizeset:=false;             ranges:=false;             numparts:=0;             compares:=0;             { Lots of comparisions take a lot of time, so do not allow               too much comparisions. 8 comparisions are, however, still               smalller than emitting the set }             if cs_opt_size in current_settings.optimizerswitches then               maxcompares:=8             else               maxcompares:=5;             { when smallset is possible allow only 3 compares the smallset               code is for littlesize also smaller when more compares are used }             if is_small then               maxcompares:=3;             for i:=0 to 255 do              if i in tnormalset(Aset^) then               begin                 if (numparts=0) or (i<>setparts[numparts].stop+1) then                  begin                  {Set element is a separate element.}                    inc(compares);                    if compares>maxcompares then                         exit;                    inc(numparts);                    setparts[numparts].range:=false;                    setparts[numparts].stop:=i;                  end                 else                  {Set element is part of a range.}                  if not setparts[numparts].range then                   begin                     {Transform an element into a range.}                     setparts[numparts].range:=true;                     setparts[numparts].start:=setparts[numparts].stop;                     setparts[numparts].stop:=i;                     ranges := true;                   end                  else                   begin                    {Extend a range.}                    setparts[numparts].stop:=i;                   end;              end;             analizeset:=true;           end;{$ifdef i8086}         procedure add_extra_offset(offset_reg:TRegister;var ref:treference);           var             reg: TRegister;           begin             if ref.index=NR_NO then               ref.index:=offset_reg             else if ref.base=NR_NO then               ref.base:=offset_reg             else               begin                 reg:=cg.getaddressregister(current_asmdata.CurrAsmList);                 cg.a_load_reg_reg(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,ref.index,reg);                 cg.a_op_reg_reg(current_asmdata.CurrAsmList,OP_ADD,OS_ADDR,offset_reg,reg);                 ref.index:=reg;               end;           end;{$endif i8086}       begin         ranges:=false;         numparts:=0;         fillchar(setparts,sizeof(setparts),0);         { We check first if we can generate jumps, this can be done           because the resultdef is already set in firstpass }         { check if we can use smallset operation using btl which is limited           to 32 bits, the left side may also not contain higher values or be signed !! }         use_small:=is_smallset(right.resultdef) and                    not is_signed(left.resultdef) and                    ((left.resultdef.typ=orddef) and (torddef(left.resultdef).high.svalue<{$ifdef i8086}16{$else}32{$endif}) or                     (left.resultdef.typ=enumdef) and (tenumdef(left.resultdef).max<{$ifdef i8086}16{$else}32{$endif}));         { Can we generate jumps? Possible for all types of sets }         genjumps:=(right.nodetype=setconstn) and                   analizeset(tsetconstnode(right).value_set,use_small);         { calculate both operators }         { the complex one first }         { not in case of genjumps, because then we don't secondpass    }         { right at all (so we have to make sure that "right" really is }         { "right" and not "swapped left" in that case)                 }         if not(genjumps) then           firstcomplex(self);         secondpass(left);         { Only process the right if we are not generating jumps }         if not genjumps then          begin            secondpass(right);          end;         if codegenerror then          exit;         { ofcourse not commutative }         if nf_swapped in flags then          swapleftright;         orgopsize := def_cgsize(left.resultdef);{$ifdef i8086}         opsize := OS_16;{$else i8086}         opsize := OS_32;{$endif i8086}         if is_signed(left.resultdef) then           opsize := tcgsize(ord(opsize)+(ord(OS_S8)-ord(OS_8)));         opdef:=cgsize_orddef(opsize);         if not(left.location.loc in [LOC_REGISTER,LOC_CREGISTER,LOC_REFERENCE,LOC_CREFERENCE,LOC_CONSTANT]) then           hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,opdef,true);         if (right.location.loc in [LOC_SUBSETREG,LOC_CSUBSETREG]) then           hlcg.location_force_reg(current_asmdata.CurrAsmList,right.location,left.resultdef,opdef,true);         if genjumps then          begin            { It gives us advantage to check for the set elements              separately instead of using the SET_IN_BYTE procedure.              To do: Build in support for LOC_JUMP }            { load and zero or sign extend as necessary }            hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,opdef,false);            pleftreg:=left.location.register;            { Get a label to jump to the end }            location_reset(location,LOC_FLAGS,OS_NO);            { It's better to use the zero flag when there are              no ranges }            if ranges then              location.resflags:=F_C            else              location.resflags:=F_E;            current_asmdata.getjumplabel(l);            { how much have we already substracted from the x in the }            { "x in [y..z]" expression                               }            adjustment := 0;            for i:=1 to numparts do             if setparts[i].range then              { use fact that a <= x <= b <=> cardinal(x-a) <= cardinal(b-a) }              begin                { is the range different from all legal values? }                if (setparts[i].stop-setparts[i].start <> 255) or not (orgopsize = OS_8) then                  begin                    { yes, is the lower bound <> 0? }                    if (setparts[i].start <> 0) then                      begin                        hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,opdef,false);                        hreg:=left.location.register;                        pleftreg:=hreg;                        cg.a_op_const_reg(current_asmdata.CurrAsmList,OP_SUB,opsize,setparts[i].start-adjustment,pleftreg);                      end;                    { new total value substracted from x:           }                    { adjustment + (setparts[i].start - adjustment) }                    adjustment := setparts[i].start;                    { check if result < b-a+1 (not "result <= b-a", since }                    { we need a carry in case the element is in the range }                    { (this will never overflow since we check at the     }                    { beginning whether stop-start <> 255)                }                    cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,opsize,OC_B,setparts[i].stop-setparts[i].start+1,pleftreg,l);                  end                else                  { if setparts[i].start = 0 and setparts[i].stop = 255,  }                  { it's always true since "in" is only allowed for bytes }                  begin                    current_asmdata.CurrAsmList.concat(taicpu.op_none(A_STC,S_NO));                    cg.a_jmp_always(current_asmdata.CurrAsmList,l);                  end;              end             else              begin                { Emit code to check if left is an element }                current_asmdata.CurrAsmList.concat(taicpu.op_const_reg(A_CMP,TCGSize2OpSize[opsize],setparts[i].stop-adjustment,                  pleftreg));                { Result should be in carry flag when ranges are used }                if ranges then                  current_asmdata.CurrAsmList.concat(taicpu.op_none(A_STC,S_NO));                { If found, jump to end }                cg.a_jmp_flags(current_asmdata.CurrAsmList,F_E,l);              end;             if ranges and                { if the last one was a range, the carry flag is already }                { set appropriately                                      }                not(setparts[numparts].range) then                  current_asmdata.CurrAsmList.concat(taicpu.op_none(A_CLC,S_NO));             { To compensate for not doing a second pass }             right.location.reference.symbol:=nil;             { Now place the end label }             cg.a_label(current_asmdata.CurrAsmList,l);          end         else          begin            location_reset(location,LOC_FLAGS,OS_NO);            setbase:=tsetdef(right.resultdef).setbase;            { We will now generated code to check the set itself, no jmps,              handle smallsets separate, because it allows faster checks }            if use_small then             begin               if left.location.loc=LOC_CONSTANT then                begin                  location.resflags:=F_NE;                  case right.location.loc of                    LOC_REGISTER,                    LOC_CREGISTER:                      begin                         emit_const_reg(A_TEST,TCGSize2OpSize[right.location.size],                           1 shl ((left.location.value-setbase) and 31),right.location.register);                      end;                    LOC_REFERENCE,                    LOC_CREFERENCE :                      begin                        emit_const_ref(A_TEST,TCGSize2OpSize[right.location.size],1 shl ((left.location.value-setbase) and 31),                           right.location.reference);                      end;                    else                      internalerror(200203312);                  end;                end               else                begin{$ifdef i8086}                  cg.getcpuregister(current_asmdata.CurrAsmList,NR_CX);                  if TCGSize2Size[left.location.size] > 2 then                    left.location.size := OS_16;                  cg.a_load_loc_reg(current_asmdata.CurrAsmList,OS_16,left.location,NR_CX);                  register_maybe_adjust_setbase(current_asmdata.CurrAsmList,left.location,setbase);                  if (tcgsize2size[right.location.size] < 2) or                     (right.location.loc = LOC_CONSTANT) then                    hlcg.location_force_reg(current_asmdata.CurrAsmList,right.location,right.resultdef,u16inttype,true);                  hreg:=cg.getintregister(current_asmdata.CurrAsmList,OS_16);                  emit_const_reg(A_MOV,S_W,1,hreg);                  emit_reg_reg(A_SHL,S_W,NR_CL,hreg);                  case right.location.loc of                    LOC_REGISTER,                    LOC_CREGISTER :                      begin                        emit_reg_reg(A_TEST,S_W,hreg,right.location.register);                      end;                     LOC_CREFERENCE,                     LOC_REFERENCE :                       begin                         emit_reg_ref(A_TEST,S_W,hreg,right.location.reference);                       end;                     else                       internalerror(2002032210);                  end;                  cg.ungetcpuregister(current_asmdata.CurrAsmList,NR_CX);                  location.resflags:=F_NE;{$else i8086}                  hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,u32inttype,true);                  register_maybe_adjust_setbase(current_asmdata.CurrAsmList,left.location,setbase);                  if (tcgsize2size[right.location.size] < 4) or                     (right.location.loc = LOC_CONSTANT) then                    hlcg.location_force_reg(current_asmdata.CurrAsmList,right.location,right.resultdef,u32inttype,true);                  hreg:=left.location.register;                  case right.location.loc of                    LOC_REGISTER,                    LOC_CREGISTER :                      begin                        emit_reg_reg(A_BT,S_L,hreg,right.location.register);                      end;                     LOC_CREFERENCE,                     LOC_REFERENCE :                       begin                         emit_reg_ref(A_BT,S_L,hreg,right.location.reference);                       end;                     else                       internalerror(2002032210);                  end;                  location.resflags:=F_C;{$endif i8086}                end;             end            else             begin               if right.location.loc=LOC_CONSTANT then                begin{$ifdef i8086}                  location.resflags:=F_NE;                  current_asmdata.getjumplabel(l);                  current_asmdata.getjumplabel(l2);                  { load constants to a register }                  if (left.location.loc=LOC_CONSTANT) or                     (setbase<>0) then                    begin                      hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,opdef,true);                      register_maybe_adjust_setbase(current_asmdata.CurrAsmList,left.location,setbase);                    end;                  cg.getcpuregister(current_asmdata.CurrAsmList,NR_CX);                  if TCGSize2Size[left.location.size] > 2 then                    left.location.size := OS_16;                  cg.a_load_loc_reg(current_asmdata.CurrAsmList,OS_16,left.location,NR_CX);                  cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,opsize,OC_BE,15,NR_CX,l);                  { set the zero flag }                  current_asmdata.CurrAsmList.concat(taicpu.op_const_reg(A_TEST,S_B,0,NR_AL));                  cg.a_jmp_always(current_asmdata.CurrAsmList,l2);                  hreg:=cg.getintregister(current_asmdata.CurrAsmList,OS_16);                  cg.a_label(current_asmdata.CurrAsmList,l);                  emit_const_reg(A_MOV,S_W,1,hreg);                  emit_reg_reg(A_SHL,S_W,NR_CL,hreg);                  cg.ungetcpuregister(current_asmdata.CurrAsmList,NR_CX);                  emit_const_reg(A_TEST,S_W,right.location.value,hreg);                  cg.a_label(current_asmdata.CurrAsmList,l2);{$else i8086}                  location.resflags:=F_C;                  current_asmdata.getjumplabel(l);                  current_asmdata.getjumplabel(l2);                  { load constants to a register }                  if (left.location.loc=LOC_CONSTANT) or                     (setbase<>0) then                    begin                      hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,opdef,true);                      register_maybe_adjust_setbase(current_asmdata.CurrAsmList,left.location,setbase);                    end;                  case left.location.loc of                     LOC_REGISTER,                     LOC_CREGISTER:                       begin                          hreg:=cg.makeregsize(current_asmdata.CurrAsmList,left.location.register,opsize);                          cg.a_load_reg_reg(current_asmdata.CurrAsmList,left.location.size,opsize,left.location.register,hreg);                          cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,opsize,OC_BE,31,hreg,l);                          { reset carry flag }                          current_asmdata.CurrAsmList.concat(taicpu.op_none(A_CLC,S_NO));                          cg.a_jmp_always(current_asmdata.CurrAsmList,l2);                          cg.a_label(current_asmdata.CurrAsmList,l);                          { We have to load the value into a register because                            btl does not accept values only refs or regs (PFV) }                          hreg2:=cg.getintregister(current_asmdata.CurrAsmList,OS_32);                          cg.a_load_const_reg(current_asmdata.CurrAsmList,OS_32,right.location.value,hreg2);                          emit_reg_reg(A_BT,S_L,hreg,hreg2);                       end;                     else                       begin                          emit_const_ref(A_CMP,TCGSize2OpSize[orgopsize],31,left.location.reference);                          cg.a_jmp_flags(current_asmdata.CurrAsmList,F_BE,l);                          { reset carry flag }                          current_asmdata.CurrAsmList.concat(taicpu.op_none(A_CLC,S_NO));                          cg.a_jmp_always(current_asmdata.CurrAsmList,l2);                          cg.a_label(current_asmdata.CurrAsmList,l);                          hreg:=cg.getintregister(current_asmdata.CurrAsmList,OS_32);                          cg.a_load_ref_reg(current_asmdata.CurrAsmList,OS_32,OS_32,left.location.reference,hreg);                          { We have to load the value into a register because                            btl does not accept values only refs or regs (PFV) }                          hreg2:=cg.getintregister(current_asmdata.CurrAsmList,OS_32);                          cg.a_load_const_reg(current_asmdata.CurrAsmList,OS_32,right.location.value,hreg2);                          emit_reg_reg(A_BT,S_L,hreg,hreg2);                       end;                  end;                  cg.a_label(current_asmdata.CurrAsmList,l2);{$endif i8086}                end { of right.location.loc=LOC_CONSTANT }               { do search in a normal set which could have >32 elementsm                 but also used if the left side contains values > 32 or < 0 }               else if left.location.loc=LOC_CONSTANT then                begin                  if (left.location.value<setbase) or (((left.location.value-setbase) shr 3) >= right.resultdef.size) then                    {should be caught earlier }                    internalerror(2007020201);                  location.resflags:=F_NE;                  case right.location.loc of                    LOC_REFERENCE,LOC_CREFERENCE:                      begin                        inc(right.location.reference.offset,(left.location.value-setbase) shr 3);                        emit_const_ref(A_TEST,S_B,1 shl ((left.location.value-setbase) and 7),right.location.reference);                      end;                    LOC_REGISTER,LOC_CREGISTER:                      begin                        emit_const_reg(A_TEST,TCGSize2OpSize[right.location.size],1 shl (left.location.value-setbase),right.location.register);                      end;                    else                      internalerror(2007051901);                  end;                end               else                begin{$ifdef i8086}                  hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,opdef,false);                  register_maybe_adjust_setbase(current_asmdata.CurrAsmList,left.location,setbase);                  if TCGSize2Size[left.location.size] > 2 then                    left.location.size := OS_16;                  if not use_small then                    begin                      extra_offset_reg:=cg.getintregister(current_asmdata.CurrAsmList,OS_16);                      cg.a_load_loc_reg(current_asmdata.CurrAsmList,OS_16,left.location,extra_offset_reg);                      cg.a_op_const_reg(current_asmdata.CurrAsmList,OP_SHR,OS_16,4,extra_offset_reg);                      cg.a_op_const_reg(current_asmdata.CurrAsmList,OP_SHL,OS_16,1,extra_offset_reg);                    end                  else                    extra_offset_reg:=NR_NO;                  cg.getcpuregister(current_asmdata.CurrAsmList,NR_CX);                  cg.a_load_loc_reg(current_asmdata.CurrAsmList,OS_16,left.location,NR_CX);                  if not use_small then                    current_asmdata.CurrAsmList.concat(taicpu.op_const_reg(A_AND,S_B,15,NR_CL));                  pleftreg:=cg.getintregister(current_asmdata.CurrAsmList,OS_16);                  if (right.location.loc in [LOC_REGISTER,LOC_CREGISTER]) then                    hlcg.location_force_reg(current_asmdata.CurrAsmList,right.location,right.resultdef,opdef,true);                  if (opsize >= OS_S8) or { = if signed }                     ((left.resultdef.typ=orddef) and                      ((torddef(left.resultdef).low < int64(tsetdef(right.resultdef).setbase)) or                       (torddef(left.resultdef).high > int64(tsetdef(right.resultdef).setmax)))) or                     ((left.resultdef.typ=enumdef) and                      ((tenumdef(left.resultdef).min < aint(tsetdef(right.resultdef).setbase)) or                       (tenumdef(left.resultdef).max > aint(tsetdef(right.resultdef).setmax)))) then                   begin                    { we have to check if the value is < 0 or > setmax }                    current_asmdata.getjumplabel(l);                    current_asmdata.getjumplabel(l2);                    { BE will be false for negative values }                    cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,opsize,OC_BE,tsetdef(right.resultdef).setmax-tsetdef(right.resultdef).setbase,pleftreg,l);                    { set the zero flag }                    current_asmdata.CurrAsmList.concat(taicpu.op_const_reg(A_TEST,S_B,0,NR_AL));                    cg.a_jmp_always(current_asmdata.CurrAsmList,l2);                    cg.a_label(current_asmdata.CurrAsmList,l);                    emit_const_reg(A_MOV,S_W,1,pleftreg);                    emit_reg_reg(A_SHL,S_W,NR_CL,pleftreg);                    cg.ungetcpuregister(current_asmdata.CurrAsmList,NR_CX);                    case right.location.loc of                      LOC_REGISTER, LOC_CREGISTER :                        emit_reg_reg(A_TEST,S_W,pleftreg,right.location.register);                      LOC_CREFERENCE, LOC_REFERENCE :                        begin                          if not use_small then                            add_extra_offset(extra_offset_reg,right.location.reference);                          emit_reg_ref(A_TEST,S_W,pleftreg,right.location.reference);                        end;                    else                      internalerror(2007020301);                    end;                    cg.a_label(current_asmdata.CurrAsmList,l2);                    location.resflags:=F_NE;                   end                  else                   begin                      emit_const_reg(A_MOV,S_W,1,pleftreg);                      emit_reg_reg(A_SHL,S_W,NR_CL,pleftreg);                      cg.ungetcpuregister(current_asmdata.CurrAsmList,NR_CX);                      case right.location.loc of                        LOC_REGISTER, LOC_CREGISTER :                          emit_reg_reg(A_TEST,S_W,pleftreg,right.location.register);                        LOC_CREFERENCE, LOC_REFERENCE :                          begin                            if not use_small then                              add_extra_offset(extra_offset_reg,right.location.reference);                            emit_reg_ref(A_TEST,S_W,pleftreg,right.location.reference);                          end;                      else                        internalerror(2007020302);                      end;                      location.resflags:=F_NE;                   end;{$else i8086}                  hlcg.location_force_reg(current_asmdata.CurrAsmList,left.location,left.resultdef,opdef,false);                  register_maybe_adjust_setbase(current_asmdata.CurrAsmList,left.location,setbase);                  if (right.location.loc in [LOC_REGISTER,LOC_CREGISTER]) then                    hlcg.location_force_reg(current_asmdata.CurrAsmList,right.location,right.resultdef,opdef,true);                  pleftreg:=left.location.register;                  if (opsize >= OS_S8) or { = if signed }                     ((left.resultdef.typ=orddef) and                      ((torddef(left.resultdef).low < int64(tsetdef(right.resultdef).setbase)) or                       (torddef(left.resultdef).high > int64(tsetdef(right.resultdef).setmax)))) or                     ((left.resultdef.typ=enumdef) and                      ((tenumdef(left.resultdef).min < aint(tsetdef(right.resultdef).setbase)) or                       (tenumdef(left.resultdef).max > aint(tsetdef(right.resultdef).setmax)))) then                   begin                    { we have to check if the value is < 0 or > setmax }                    current_asmdata.getjumplabel(l);                    current_asmdata.getjumplabel(l2);                    { BE will be false for negative values }                    cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,opsize,OC_BE,tsetdef(right.resultdef).setmax-tsetdef(right.resultdef).setbase,pleftreg,l);                    { reset carry flag }                    current_asmdata.CurrAsmList.concat(taicpu.op_none(A_CLC,S_NO));                    cg.a_jmp_always(current_asmdata.CurrAsmList,l2);                    cg.a_label(current_asmdata.CurrAsmList,l);                    pleftreg:=left.location.register;                    case right.location.loc of                      LOC_REGISTER, LOC_CREGISTER :                        emit_reg_reg(A_BT,S_L,pleftreg,right.location.register);                      LOC_CREFERENCE, LOC_REFERENCE :                        emit_reg_ref(A_BT,S_L,pleftreg,right.location.reference);                    else                      internalerror(2007020301);                    end;                    cg.a_label(current_asmdata.CurrAsmList,l2);                    location.resflags:=F_C;                   end                  else                   begin                      case right.location.loc of                        LOC_REGISTER, LOC_CREGISTER :                          emit_reg_reg(A_BT,S_L,pleftreg,right.location.register);                        LOC_CREFERENCE, LOC_REFERENCE :                          emit_reg_ref(A_BT,S_L,pleftreg,right.location.reference);                      else                        internalerror(2007020302);                      end;                      location.resflags:=F_C;                   end;{$endif i8086}                end;             end;          end;          if not genjumps then            location_freetemp(current_asmdata.CurrAsmList,right.location);       end;begin   cinnode:=tx86innode;   ccasenode:=tx86casenode;end.
 |