| 1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192939495969798991001011021031041051061071081091101111121131141151161171181191201211221231241251261271281291301311321331341351361371381391401411421431441451461471481491501511521531541551561571581591601611621631641651661671681691701711721731741751761771781791801811821831841851861871881891901911921931941951961971981992002012022032042052062072082092102112122132142152162172182192202212222232242252262272282292302312322332342352362372382392402412422432442452462472482492502512522532542552562572582592602612622632642652662672682692702712722732742752762772782792802812822832842852862872882892902912922932942952962972982993003013023033043053063073083093103113123133143153163173183193203213223233243253263273283293303313323333343353363373383393403413423433443453463473483493503513523533543553563573583593603613623633643653663673683693703713723733743753763773783793803813823833843853863873883893903913923933943953963973983994004014024034044054064074084094104114124134144154164174184194204214224234244254264274284294304314324334344354364374384394404414424434444454464474484494504514524534544554564574584594604614624634644654664674684694704714724734744754764774784794804814824834844854864874884894904914924934944954964974984995005015025035045055065075085095105115125135145155165175185195205215225235245255265275285295305315325335345355365375385395405415425435445455465475485495505515525535545555565575585595605615625635645655665675685695705715725735745755765775785795805815825835845855865875885895905915925935945955965975985996006016026036046056066076086096106116126136146156166176186196206216226236246256266276286296306316326336346356366376386396406416426436446456466476486496506516526536546556566576586596606616626636646656666676686696706716726736746756766776786796806816826836846856866876886896906916926936946956966976986997007017027037047057067077087097107117127137147157167177187197207217227237247257267277287297307317327337347357367377387397407417427437447457467477487497507517527537547557567577587597607617627637647657667677687697707717727737747757767777787797807817827837847857867877887897907917927937947957967977987998008018028038048058068078088098108118128138148158168178188198208218228238248258268278288298308318328338348358368378388398408418428438448458468478488498508518528538548558568578588598608618628638648658668678688698708718728738748758768778788798808818828838848858868878888898908918928938948958968978988999009019029039049059069079089099109119129139149159169179189199209219229239249259269279289299309319329339349359369379389399409419429439449459469479489499509519529539549559569579589599609619629639649659669679689699709719729739749759769779789799809819829839849859869879889899909919929939949959969979989991000100110021003100410051006100710081009101010111012101310141015101610171018101910201021102210231024102510261027102810291030103110321033103410351036103710381039104010411042104310441045104610471048104910501051105210531054105510561057105810591060106110621063106410651066106710681069107010711072 | {    Copyright (c) 1998-2002 by Florian Klaempfl    Generate assembler for nodes that handle loads and assignments which    are the same for all (most) processors    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 ncgld;{$i fpcdefs.inc}interface    uses      node,nld,cgutils;    type       tcgloadnode = class(tloadnode)          procedure pass_generate_code;override;          procedure generate_picvaraccess;virtual;          procedure changereflocation(const ref: treference);       end;       tcgassignmentnode = class(tassignmentnode)          procedure pass_generate_code;override;       end;       tcgarrayconstructornode = class(tarrayconstructornode)          procedure pass_generate_code;override;       end;       tcgrttinode = class(trttinode)          procedure pass_generate_code;override;       end;implementation    uses      cutils,      systems,      verbose,globtype,globals,      nutils,      symconst,symtype,symdef,symsym,defutil,paramgr,      ncnv,ncon,nmem,nbas,ncgrtti,      aasmbase,aasmtai,aasmdata,aasmcpu,      cgbase,pass_2,      procinfo,      cpubase,parabase,      tgobj,ncgutil,      cgobj,      ncgbas,ncgflw;{*****************************************************************************                   SSA (for memory temps) support*****************************************************************************}    type      preplacerefrec = ^treplacerefrec;      treplacerefrec = record        old, new: preference;        ressym: tsym;      end;    function doreplaceref(var n: tnode; para: pointer): foreachnoderesult;      var        rr: preplacerefrec absolute para;      begin        result := fen_false;        case n.nodetype of          loadn:            begin                 { regular variable }              if (tabstractvarsym(tloadnode(n).symtableentry).varoptions * [vo_is_dll_var, vo_is_thread_var] = []) and                 not assigned(tloadnode(n).left) and                 { not function result, or no exit in function }                 (((tloadnode(n).symtableentry <> rr^.ressym) and                   not(vo_is_funcret in tabstractvarsym(tloadnode(n).symtableentry).varoptions)) or                  not(fc_exit in flowcontrol)) and                 { stored in memory... }                 (tabstractnormalvarsym(tloadnode(n).symtableentry).localloc.loc in [LOC_REFERENCE]) and                 { ... at the place we are looking for }                 references_equal(tabstractnormalvarsym(tloadnode(n).symtableentry).localloc.reference,rr^.old^) then                begin                  { relocate variable }                  tcgloadnode(n).changereflocation(rr^.new^);                  result := fen_norecurse_true;                end;            end;          temprefn:            begin              if (ttemprefnode(n).tempinfo^.valid) and                 { memory temp... }                 (ttemprefnode(n).tempinfo^.location.loc in [LOC_REFERENCE]) and                 { ... at the place we are looking for }                 references_equal(ttemprefnode(n).tempinfo^.location.reference,rr^.old^) then                begin                  { relocate the temp }                  tcgtemprefnode(n).changelocation(rr^.new^);                  result := fen_norecurse_true;                end;            end;          { optimize the searching a bit }          derefn,addrn,          calln,inlinen,casen,          addn,subn,muln,          andn,orn,xorn,          ltn,lten,gtn,gten,equaln,unequaln,          slashn,divn,shrn,shln,notn,          inn,          asn,isn:            result := fen_norecurse_false;        end;      end;    function maybechangetemp(list: TAsmList; var n: tnode; const newref: treference): boolean;      var        rr: treplacerefrec;      begin        result := false;           { only do for -O2 or higher (breaks debugging since }           { variables move to different memory locations)     }        if not(cs_opt_level2 in current_settings.optimizerswitches) or           { must be a copy to a memory location ... }           (n.location.loc <> LOC_REFERENCE) or           { not inside a control flow statement and no goto's in sight }           ([fc_inflowcontrol,fc_gotolabel] * flowcontrol <> []) or           { source and destination are temps (= not global variables) }           not tg.istemp(n.location.reference) or           not tg.istemp(newref) or           { and both point to the start of a temp, and the source is a }           { non-persistent temp (otherwise we need some kind of copy-  }           { on-write support in case later on both are still used)     }           (tg.gettypeoftemp(newref) <> tt_normal) or           not (tg.gettypeoftemp(n.location.reference) in [tt_normal,tt_persistent]) or           { and both have the same size }           (tg.sizeoftemp(current_asmdata.CurrAsmList,newref) <> tg.sizeoftemp(current_asmdata.CurrAsmList,n.location.reference)) then          exit;        { find the source of the old reference (loadnode or tempnode) }        { and replace it with the new reference                       }        rr.old := @n.location.reference;        rr.new := @newref;        rr.ressym := nil;        if (current_procinfo.procdef.funcretloc[calleeside].loc<>LOC_VOID) and           assigned(current_procinfo.procdef.funcretsym) and           (tabstractvarsym(current_procinfo.procdef.funcretsym).refs <> 0) then          if (current_procinfo.procdef.proctypeoption=potype_constructor) then            rr.ressym:=tsym(current_procinfo.procdef.parast.Find('self'))         else            rr.ressym:=current_procinfo.procdef.funcretsym;        { if source not found, don't do anything }        if not foreachnodestatic(n,@doreplaceref,@rr) then          exit;        n.location.reference := newref;        result:=true;      end;{*****************************************************************************                             SecondLoad*****************************************************************************}    procedure tcgloadnode.generate_picvaraccess;      begin{$ifndef sparc}        location.reference.base:=current_procinfo.got;        location.reference.symbol:=current_asmdata.RefAsmSymbol(tstaticvarsym(symtableentry).mangledname+'@GOT');{$endif sparc}      end;    procedure tcgloadnode.changereflocation(const ref: treference);      var        oldtemptype: ttemptype;      begin        if (location.loc<>LOC_REFERENCE) then          internalerror(2007020812);        if not tg.istemp(location.reference) then          internalerror(2007020813);        oldtemptype:=tg.gettypeoftemp(location.reference);        if (oldtemptype = tt_persistent) then          tg.ChangeTempType(current_asmdata.CurrAsmList,location.reference,tt_normal);        tg.ungettemp(current_asmdata.CurrAsmList,location.reference);        location.reference:=ref;        tg.ChangeTempType(current_asmdata.CurrAsmList,location.reference,oldtemptype);        tabstractnormalvarsym(symtableentry).localloc:=location;      end;    procedure tcgloadnode.pass_generate_code;      var        hregister : tregister;        vs   : tabstractnormalvarsym;        gvs  : tstaticvarsym;        pd   : tprocdef;        href : treference;        newsize : tcgsize;        endrelocatelab,        norelocatelab : tasmlabel;        paraloc1 : tcgpara;      begin         { we don't know the size of all arrays }         newsize:=def_cgsize(resultdef);         location_reset(location,LOC_REFERENCE,newsize);         case symtableentry.typ of            absolutevarsym :               begin                  { this is only for toasm and toaddr }                  case tabsolutevarsym(symtableentry).abstyp of                    toaddr :                      begin{$ifdef i386}                        if tabsolutevarsym(symtableentry).absseg then                          location.reference.segment:=NR_FS;{$endif i386}                        location.reference.offset:=tabsolutevarsym(symtableentry).addroffset;                      end;                    toasm :                      location.reference.symbol:=current_asmdata.RefAsmSymbol(tabsolutevarsym(symtableentry).mangledname);                    else                      internalerror(200310283);                  end;               end;            constsym:              begin                 if tconstsym(symtableentry).consttyp=constresourcestring then                   begin                      location_reset(location,LOC_CREFERENCE,OS_ADDR);                      location.reference.symbol:=current_asmdata.RefAsmSymbol(make_mangledname('RESSTR',symtableentry.owner,symtableentry.name));                      { Resourcestring layout:                          TResourceStringRecord = Packed Record                             Name,                             CurrentValue,                             DefaultValue : AnsiString;                             HashValue    : LongWord;                           end;                      }                      location.reference.offset:=sizeof(aint);                   end                 else                   internalerror(22798);              end;            staticvarsym :              begin                gvs:=tstaticvarsym(symtableentry);                if ([vo_is_dll_var,vo_is_external] * gvs.varoptions <> []) then                  begin                    location.reference.base := cg.g_indirect_sym_load(current_asmdata.CurrAsmList,tstaticvarsym(symtableentry).mangledname);                    if (location.reference.base <> NR_NO) then                      exit;                  end;                if (vo_is_dll_var in gvs.varoptions) then                { DLL variable }                  begin                    hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                    location.reference.symbol:=current_asmdata.RefAsmSymbol(tstaticvarsym(symtableentry).mangledname);                    cg.a_load_ref_reg(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,location.reference,hregister);                    reference_reset_base(location.reference,hregister,0);                  end                { Thread variable }                else if (vo_is_thread_var in gvs.varoptions) and                        not(tf_section_threadvars in target_info.flags) then                  begin                     if (tf_section_threadvars in target_info.flags) then                       begin                         if gvs.localloc.loc=LOC_INVALID then                           reference_reset_symbol(location.reference,current_asmdata.RefAsmSymbol(gvs.mangledname),0)                         else                           location:=gvs.localloc;{$ifdef i386}                         case target_info.system of                           system_i386_linux:                             location.reference.segment:=NR_GS;                           system_i386_win32:                             location.reference.segment:=NR_FS;                         end;{$endif i386}                       end                     else                       begin                         {                           Thread var loading is optimized to first check if                           a relocate function is available. When the function                           is available it is called to retrieve the address.                           Otherwise the address is loaded with the symbol                           The code needs to be in the order to first handle the                           call and then the address load to be sure that the                           register that is used for returning is the same (PFV)                         }                         current_asmdata.getjumplabel(norelocatelab);                         current_asmdata.getjumplabel(endrelocatelab);                         { make sure hregister can't allocate the register necessary for the parameter }                         paraloc1.init;                         paramanager.getintparaloc(pocall_default,1,paraloc1);                         hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                         reference_reset_symbol(href,current_asmdata.RefAsmSymbol('FPC_THREADVAR_RELOCATE'),0);                         cg.a_load_ref_reg(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,href,hregister);                         cg.a_cmp_const_reg_label(current_asmdata.CurrAsmList,OS_ADDR,OC_EQ,0,hregister,norelocatelab);                         { don't save the allocated register else the result will be destroyed later }                         reference_reset_symbol(href,current_asmdata.RefAsmSymbol(tstaticvarsym(symtableentry).mangledname),0);                         paramanager.allocparaloc(current_asmdata.CurrAsmList,paraloc1);                         cg.a_param_ref(current_asmdata.CurrAsmList,OS_32,href,paraloc1);                         paramanager.freeparaloc(current_asmdata.CurrAsmList,paraloc1);                         paraloc1.done;                         cg.allocallcpuregisters(current_asmdata.CurrAsmList);                         cg.a_call_reg(current_asmdata.CurrAsmList,hregister);                         cg.deallocallcpuregisters(current_asmdata.CurrAsmList);                         cg.getcpuregister(current_asmdata.CurrAsmList,NR_FUNCTION_RESULT_REG);                         cg.ungetcpuregister(current_asmdata.CurrAsmList,NR_FUNCTION_RESULT_REG);                         hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                         cg.a_load_reg_reg(current_asmdata.CurrAsmList,OS_INT,OS_ADDR,NR_FUNCTION_RESULT_REG,hregister);                         cg.a_jmp_always(current_asmdata.CurrAsmList,endrelocatelab);                         cg.a_label(current_asmdata.CurrAsmList,norelocatelab);                         { no relocation needed, load the address of the variable only, the                           layout of a threadvar is (4 bytes pointer):                             0 - Threadvar index                             4 - Threadvar value in single threading }                         reference_reset_symbol(href,current_asmdata.RefAsmSymbol(tstaticvarsym(symtableentry).mangledname),sizeof(aint));                         cg.a_loadaddr_ref_reg(current_asmdata.CurrAsmList,href,hregister);                         cg.a_label(current_asmdata.CurrAsmList,endrelocatelab);                         location.reference.base:=hregister;                       end;                   end                 { Normal (or external) variable }                 else                   begin                     if gvs.localloc.loc=LOC_INVALID then                       reference_reset_symbol(location.reference,current_asmdata.RefAsmSymbol(gvs.mangledname),0)                     else                       location:=gvs.localloc;                   end;                 { make const a LOC_CREFERENCE }                 if (gvs.varspez=vs_const) and                    (location.loc=LOC_REFERENCE) then                   location.loc:=LOC_CREFERENCE;               end;             paravarsym,             localvarsym :               begin                 vs:=tabstractnormalvarsym(symtableentry);                 { Nested variable }                 if assigned(left) then                   begin                     secondpass(left);                     if left.location.loc<>LOC_REGISTER then                       internalerror(200309286);                     if vs.localloc.loc<>LOC_REFERENCE then                       internalerror(200409241);                     reference_reset_base(location.reference,left.location.register,vs.localloc.reference.offset);                   end                 else                   location:=vs.localloc;                 { handle call by reference variables when they are not                   alreayd copied to local copies. Also ignore the reference                   when we need to load the self pointer for objects }                 if is_addr_param_load then                   begin                     if (location.loc in [LOC_CREGISTER,LOC_REGISTER]) then                       hregister:=location.register                     else                       begin                         hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                         { we need to load only an address }                         location.size:=OS_ADDR;                         cg.a_load_loc_reg(current_asmdata.CurrAsmList,location.size,location,hregister);                       end;                     location_reset(location,LOC_REFERENCE,newsize);                     location.reference.base:=hregister;                   end;                 { make const a LOC_CREFERENCE }                 if (vs.varspez=vs_const) and                    (location.loc=LOC_REFERENCE) then                   location.loc:=LOC_CREFERENCE;               end;            procsym:               begin                  if not assigned(procdef) then                    internalerror(200312011);                  if assigned(left) then                    begin                      if (sizeof(aint) = 4) then                         location_reset(location,LOC_CREFERENCE,OS_64)                      else if (sizeof(aint) = 8) then                         location_reset(location,LOC_CREFERENCE,OS_128)                      else                         internalerror(20020520);                      tg.GetTemp(current_asmdata.CurrAsmList,2*sizeof(aint),tt_normal,location.reference);                      secondpass(left);                      { load class instance address }                      if left.location.loc=LOC_CONSTANT then                        location_force_reg(current_asmdata.CurrAsmList,left.location,OS_ADDR,false);                      case left.location.loc of                         LOC_CREGISTER,                         LOC_REGISTER:                           begin                              { this is not possible for objects }                              if is_object(left.resultdef) then                                internalerror(200304234);                              hregister:=left.location.register;                           end;                         LOC_CREFERENCE,                         LOC_REFERENCE:                           begin                              hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                              if is_class_or_interface(left.resultdef) then                                cg.a_load_ref_reg(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,left.location.reference,hregister)                              else                                cg.a_loadaddr_ref_reg(current_asmdata.CurrAsmList,left.location.reference,hregister);                              location_freetemp(current_asmdata.CurrAsmList,left.location);                           end;                         else                           internalerror(200610311);                      end;                      { store the class instance address }                      href:=location.reference;                      inc(href.offset,sizeof(aint));                      cg.a_load_reg_ref(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,hregister,href);                      { virtual method ? }                      if (po_virtualmethod in procdef.procoptions) and                         not(nf_inherited in flags) then                        begin                          { load vmt pointer }                          reference_reset_base(href,hregister,0);                          hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                          cg.a_load_ref_reg(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,href,hregister);                          { load method address }                          reference_reset_base(href,hregister,procdef._class.vmtmethodoffset(procdef.extnumber));                          hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                          cg.a_load_ref_reg(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,href,hregister);                          { ... and store it }                          cg.a_load_reg_ref(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,hregister,location.reference);                        end                      else                        begin                          { load address of the function }                          reference_reset_symbol(href,current_asmdata.RefAsmSymbol(procdef.mangledname),0);                          hregister:=cg.getaddressregister(current_asmdata.CurrAsmList);                          cg.a_loadaddr_ref_reg(current_asmdata.CurrAsmList,href,hregister);                          cg.a_load_reg_ref(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,hregister,location.reference);                        end;                    end                  else                    begin                       pd:=tprocdef(tprocsym(symtableentry).ProcdefList[0]);                       if (po_external in pd.procoptions) then                         location.reference.base := cg.g_indirect_sym_load(current_asmdata.CurrAsmList,pd.mangledname);                       {!!!!! Be aware, work on virtual methods too }                       if (location.reference.base = NR_NO) then                         location.reference.symbol:=current_asmdata.RefAsmSymbol(procdef.mangledname);                    end;               end;            labelsym :              location.reference.symbol:=tcglabelnode((tlabelsym(symtableentry).code)).getasmlabel;            else internalerror(200510032);         end;      end;{*****************************************************************************                             SecondAssignment*****************************************************************************}    procedure tcgassignmentnode.pass_generate_code;      var         otlabel,hlabel,oflabel : tasmlabel;         href : treference;         releaseright : boolean;         len : aint;         r:Tregister;      begin        location_reset(location,LOC_VOID,OS_NO);        otlabel:=current_procinfo.CurrTrueLabel;        oflabel:=current_procinfo.CurrFalseLabel;        current_asmdata.getjumplabel(current_procinfo.CurrTrueLabel);        current_asmdata.getjumplabel(current_procinfo.CurrFalseLabel);        {          in most cases we can process first the right node which contains          the most complex code. Exceptions for this are:            - result is in flags, loading left will then destroy the flags            - result is a jump, loading left must be already done before the jump is made            - result need reference count, when left points to a value used in              right then decreasing the refcnt on left can possibly release              the memory before right increased the refcnt, result is that an              empty value is assigned            - calln, call destroys most registers and is therefor 'complex'           But not when the result is in the flags, then          loading the left node afterwards can destroy the flags.        }        if not(right.expectloc in [LOC_FLAGS,LOC_JUMP]) and           ((right.nodetype=calln) or            (right.resultdef.needs_inittable) or            (right.registersint>=left.registersint)) then         begin           secondpass(right);           { increment source reference counter, this is             useless for string constants}           if (right.resultdef.needs_inittable) and              (right.nodetype<>stringconstn) then            begin              location_force_mem(current_asmdata.CurrAsmList,right.location);              location_get_data_ref(current_asmdata.CurrAsmList,right.location,href,false);              cg.g_incrrefcount(current_asmdata.CurrAsmList,right.resultdef,href);            end;           if codegenerror then             exit;           { left can't be never a 64 bit LOC_REGISTER, so the 3. arg }           { can be false                                             }           secondpass(left);           { decrement destination reference counter }           if (left.resultdef.needs_inittable) then             begin               location_get_data_ref(current_asmdata.CurrAsmList,left.location,href,false);               cg.g_decrrefcount(current_asmdata.CurrAsmList,left.resultdef,href);             end;           if codegenerror then             exit;         end        else         begin           { calculate left sides }           secondpass(left);           { decrement destination reference counter }           if (left.resultdef.needs_inittable) then             begin               location_get_data_ref(current_asmdata.CurrAsmList,left.location,href,false);               cg.g_decrrefcount(current_asmdata.CurrAsmList,left.resultdef,href);             end;           if codegenerror then             exit;           { left can't be never a 64 bit LOC_REGISTER, so the 3. arg }           { can be false                                             }           secondpass(right);           { increment source reference counter, this is             useless for string constants}           if (right.resultdef.needs_inittable) and              (right.nodetype<>stringconstn) then             begin               location_force_mem(current_asmdata.CurrAsmList,right.location);               location_get_data_ref(current_asmdata.CurrAsmList,right.location,href,false);               cg.g_incrrefcount(current_asmdata.CurrAsmList,right.resultdef,href);             end;           if codegenerror then             exit;         end;        releaseright:=true;        { shortstring assignments are handled separately }        if is_shortstring(left.resultdef) then          begin            {              we can get here only in the following situations              for the right node:               - empty constant string               - char            }            { The addn is replaced by a blockn or calln }            if right.nodetype in [blockn,calln] then              begin                { nothing to do }              end            { empty constant string }            else if (right.nodetype=stringconstn) and               (tstringconstnode(right).len=0) then              begin                cg.a_load_const_ref(current_asmdata.CurrAsmList,OS_8,0,left.location.reference);              end            { char loading }            else if is_char(right.resultdef) then              begin                if right.nodetype=ordconstn then                  begin                    if (target_info.endian = endian_little) then                      cg.a_load_const_ref(current_asmdata.CurrAsmList,OS_16,(tordconstnode(right).value shl 8) or 1,                          left.location.reference)                    else                      cg.a_load_const_ref(current_asmdata.CurrAsmList,OS_16,tordconstnode(right).value or (1 shl 8),                          left.location.reference);                  end                else                  begin                    href:=left.location.reference;                    cg.a_load_const_ref(current_asmdata.CurrAsmList,OS_8,1,href);                    inc(href.offset,1);                    case right.location.loc of                      LOC_REGISTER,                      LOC_CREGISTER :                        begin                          r:=cg.makeregsize(current_asmdata.CurrAsmList,right.location.register,OS_8);                          cg.a_load_reg_ref(current_asmdata.CurrAsmList,OS_8,OS_8,r,href);                        end;                      LOC_REFERENCE,                      LOC_CREFERENCE :                        cg.a_load_ref_ref(current_asmdata.CurrAsmList,OS_8,OS_8,right.location.reference,href);                      else                        internalerror(200205111);                    end;                  end;              end            else              internalerror(200204249);          end       { try to reuse memory locations instead of copying }           { copy to a memory location ... }        else if (right.location.loc = LOC_REFERENCE) and           maybechangetemp(current_asmdata.CurrAsmList,left,right.location.reference) then          begin            { if it worked, we're done }          end        else          begin            { SSA support }            maybechangeloadnodereg(current_asmdata.CurrAsmList,left,false);            maybechangeloadnodereg(current_asmdata.CurrAsmList,right,true);            case right.location.loc of              LOC_CONSTANT :                begin{$ifndef cpu64bit}                  if right.location.size in [OS_64,OS_S64] then                   cg64.a_load64_const_loc(current_asmdata.CurrAsmList,right.location.value64,left.location)                  else{$endif cpu64bit}                   cg.a_load_const_loc(current_asmdata.CurrAsmList,right.location.value,left.location);                end;              LOC_REFERENCE,              LOC_CREFERENCE :                begin                  case left.location.loc of                    LOC_REGISTER,                    LOC_CREGISTER :                      begin{$ifndef cpu64bit}                        if left.location.size in [OS_64,OS_S64] then                          cg64.a_load64_ref_reg(current_asmdata.CurrAsmList,right.location.reference,left.location.register64)                        else{$endif cpu64bit}                          cg.a_load_ref_reg(current_asmdata.CurrAsmList,right.location.size,left.location.size,right.location.reference,left.location.register);                      end;                    LOC_FPUREGISTER,                    LOC_CFPUREGISTER :                      begin                        cg.a_loadfpu_ref_reg(current_asmdata.CurrAsmList,                            right.location.size,left.location.size,                            right.location.reference,                            left.location.register);                      end;                    LOC_REFERENCE,                    LOC_CREFERENCE :                      begin{$warning HACK: unaligned test, maybe remove all unaligned locations (array of char) from the compiler}                        { Use unaligned copy when the offset is not aligned }                        len:=left.resultdef.size;                        if (right.location.reference.offset mod sizeof(aint)<>0) or                          (left.location.reference.offset mod sizeof(aint)<>0) or                          (right.resultdef.alignment<sizeof(aint)) then                          cg.g_concatcopy_unaligned(current_asmdata.CurrAsmList,right.location.reference,left.location.reference,len)                        else                          cg.g_concatcopy(current_asmdata.CurrAsmList,right.location.reference,left.location.reference,len);                      end;                    LOC_MMREGISTER,                    LOC_CMMREGISTER:                      cg.a_loadmm_ref_reg(current_asmdata.CurrAsmList,                        right.location.size,                        left.location.size,                        right.location.reference,                        left.location.register,mms_movescalar);                    LOC_SUBSETREG,                    LOC_CSUBSETREG:                      cg.a_load_ref_subsetreg(current_asmdata.CurrAsmList,right.location.size,left.location.size,right.location.reference,left.location.sreg);                    LOC_SUBSETREF,                    LOC_CSUBSETREF:{$ifndef cpu64bit}                      if right.location.size in [OS_64,OS_S64] then                       cg64.a_load64_ref_subsetref(current_asmdata.CurrAsmList,right.location.reference,left.location.sref)                      else{$endif cpu64bit}                       cg.a_load_ref_subsetref(current_asmdata.CurrAsmList,right.location.size,left.location.size,right.location.reference,left.location.sref);                    else                      internalerror(200203284);                  end;                end;{$ifdef SUPPORT_MMX}              LOC_CMMXREGISTER,              LOC_MMXREGISTER:                begin                  if left.location.loc=LOC_CMMXREGISTER then                    cg.a_loadmm_reg_reg(current_asmdata.CurrAsmList,OS_M64,OS_M64,right.location.register,left.location.register,nil)                  else                    cg.a_loadmm_reg_ref(current_asmdata.CurrAsmList,OS_M64,OS_M64,right.location.register,left.location.reference,nil);                end;{$endif SUPPORT_MMX}              LOC_MMREGISTER,              LOC_CMMREGISTER:                begin                  if left.resultdef.typ=arraydef then                    begin                    end                  else                    begin                      if left.location.loc=LOC_CMMREGISTER then                        cg.a_loadmm_reg_reg(current_asmdata.CurrAsmList,right.location.size,left.location.size,right.location.register,left.location.register,mms_movescalar)                      else                        cg.a_loadmm_reg_ref(current_asmdata.CurrAsmList,right.location.size,left.location.size,right.location.register,left.location.reference,mms_movescalar);                    end;                end;              LOC_REGISTER,              LOC_CREGISTER :                begin{$ifndef cpu64bit}                  if left.location.size in [OS_64,OS_S64] then                    cg64.a_load64_reg_loc(current_asmdata.CurrAsmList,                      right.location.register64,left.location)                  else{$endif cpu64bit}                    cg.a_load_reg_loc(current_asmdata.CurrAsmList,right.location.size,right.location.register,left.location);                end;              LOC_FPUREGISTER,              LOC_CFPUREGISTER :                begin                  { we can't do direct moves between fpu and mm registers }                  if left.location.loc in [LOC_MMREGISTER,LOC_CMMREGISTER] then                    begin                      location_force_mmregscalar(current_asmdata.CurrAsmList,right.location,false);                      cg.a_loadmm_reg_reg(current_asmdata.CurrAsmList,                          right.location.size,left.location.size,                          right.location.register,left.location.register,mms_movescalar);                    end                  else                    cg.a_loadfpu_reg_loc(current_asmdata.CurrAsmList,                        right.location.size,                        right.location.register,left.location);                end;              LOC_SUBSETREG,              LOC_CSUBSETREG:                begin                  cg.a_load_subsetreg_loc(current_asmdata.CurrAsmList,                      right.location.size,right.location.sreg,left.location);                end;              LOC_SUBSETREF,              LOC_CSUBSETREF:                begin{$ifndef cpu64bit}                  if right.location.size in [OS_64,OS_S64] then                   cg64.a_load64_subsetref_loc(current_asmdata.CurrAsmList,right.location.sref,left.location)                  else{$endif cpu64bit}                  cg.a_load_subsetref_loc(current_asmdata.CurrAsmList,                      right.location.size,right.location.sref,left.location);                end;              LOC_JUMP :                begin                  current_asmdata.getjumplabel(hlabel);                  cg.a_label(current_asmdata.CurrAsmList,current_procinfo.CurrTrueLabel);                  cg.a_load_const_loc(current_asmdata.CurrAsmList,1,left.location);                  cg.a_jmp_always(current_asmdata.CurrAsmList,hlabel);                  cg.a_label(current_asmdata.CurrAsmList,current_procinfo.CurrFalseLabel);                  cg.a_load_const_loc(current_asmdata.CurrAsmList,0,left.location);                  cg.a_label(current_asmdata.CurrAsmList,hlabel);                end;{$ifdef cpuflags}              LOC_FLAGS :                begin                  {This can be a wordbool or longbool too, no?}                  case left.location.loc of                    LOC_REGISTER,LOC_CREGISTER:                      cg.g_flags2reg(current_asmdata.CurrAsmList,def_cgsize(left.resultdef),right.location.resflags,left.location.register);                    LOC_REFERENCE:                      cg.g_flags2ref(current_asmdata.CurrAsmList,def_cgsize(left.resultdef),right.location.resflags,left.location.reference);                    LOC_SUBSETREG,LOC_SUBSETREF:                      begin                        r:=cg.getintregister(current_asmdata.CurrAsmList,def_cgsize(left.resultdef));                        cg.g_flags2reg(current_asmdata.CurrAsmList,def_cgsize(left.resultdef),right.location.resflags,r);                        cg.a_load_reg_loc(current_asmdata.CurrAsmList,def_cgsize(left.resultdef),r,left.location);                      end;                    else                      internalerror(200203273);                    end;                end;{$endif cpuflags}            end;         end;        if releaseright then          location_freetemp(current_asmdata.CurrAsmList,right.location);        current_procinfo.CurrTrueLabel:=otlabel;        current_procinfo.CurrFalseLabel:=oflabel;      end;{*****************************************************************************                           SecondArrayConstruct*****************************************************************************}      const        vtInteger    = 0;        vtBoolean    = 1;        vtChar       = 2;        vtExtended   = 3;        vtString     = 4;        vtPointer    = 5;        vtPChar      = 6;        vtObject     = 7;        vtClass      = 8;        vtWideChar   = 9;        vtPWideChar  = 10;        vtAnsiString32 = 11;        vtCurrency   = 12;        vtVariant    = 13;        vtInterface  = 14;        vtWideString = 15;        vtInt64      = 16;        vtQWord      = 17;        vtAnsiString16 = 18;        vtAnsiString64 = 19;    procedure tcgarrayconstructornode.pass_generate_code;      var        hp    : tarrayconstructornode;        href  : treference;        lt    : tdef;        vaddr : boolean;        vtype : longint;        freetemp,        dovariant : boolean;        elesize : longint;        tmpreg  : tregister;        paraloc : tcgparalocation;      begin        if is_packed_array(resultdef) then          internalerror(200608042);        dovariant:=(nf_forcevaria in flags) or is_variant_array(resultdef);        if dovariant then          elesize:=sizeof(aint)+sizeof(aint)        else          elesize:=tarraydef(resultdef).elesize;        location_reset(location,LOC_CREFERENCE,OS_NO);        fillchar(paraloc,sizeof(paraloc),0);        { Allocate always a temp, also if no elements are required, to          be sure that location is valid (PFV) }         if tarraydef(resultdef).highrange=-1 then           tg.GetTemp(current_asmdata.CurrAsmList,elesize,tt_normal,location.reference)         else           tg.GetTemp(current_asmdata.CurrAsmList,(tarraydef(resultdef).highrange+1)*elesize,tt_normal,location.reference);         href:=location.reference;        { Process nodes in array constructor }        hp:=self;        while assigned(hp) do         begin           if assigned(hp.left) then            begin              freetemp:=true;              secondpass(hp.left);              if codegenerror then               exit;              { Move flags and jump in register }              if hp.left.location.loc in [LOC_FLAGS,LOC_JUMP] then                location_force_reg(current_asmdata.CurrAsmList,hp.left.location,def_cgsize(hp.left.resultdef),false);              if dovariant then               begin                 { find the correct vtype value }                 vtype:=$ff;                 vaddr:=false;                 lt:=hp.left.resultdef;                 case lt.typ of                   enumdef,                   orddef :                     begin                       if is_64bit(lt) then                         begin                            case torddef(lt).ordtype of                              scurrency:                                vtype:=vtCurrency;                              s64bit:                                vtype:=vtInt64;                              u64bit:                                vtype:=vtQWord;                            end;                            freetemp:=false;                            vaddr:=true;                         end                       else if (lt.typ=enumdef) or                         is_integer(lt) then                         vtype:=vtInteger                       else                         if is_boolean(lt) then                           vtype:=vtBoolean                         else                           if (lt.typ=orddef) then                             begin                               case torddef(lt).ordtype of                                 uchar:                                   vtype:=vtChar;                                 uwidechar:                                   vtype:=vtWideChar;                               end;                             end;                     end;                   floatdef :                     begin                       if is_currency(lt) then                         vtype:=vtCurrency                       else                         vtype:=vtExtended;                       freetemp:=false;                       vaddr:=true;                     end;                   procvardef,                   pointerdef :                     begin                       if is_pchar(lt) then                         vtype:=vtPChar                       else if is_pwidechar(lt) then                         vtype:=vtPWideChar                       else                         vtype:=vtPointer;                     end;                   variantdef :                     begin                        vtype:=vtVariant;                        vaddr:=true;                        freetemp:=false;                     end;                   classrefdef :                     vtype:=vtClass;                   objectdef :                     if is_interface(lt) then                       vtype:=vtInterface                     { vtObject really means a class based on TObject }                     else if is_class(lt) then                       vtype:=vtObject                     else                       internalerror(200505171);                   stringdef :                     begin                       if is_shortstring(lt) then                        begin                          vtype:=vtString;                          vaddr:=true;                          freetemp:=false;                        end                       else                        if is_ansistring(lt) then                         begin                           vtype:=vtAnsiString;                           freetemp:=false;                         end                       else                        if is_widestring(lt) then                         begin                           vtype:=vtWideString;                           freetemp:=false;                         end;                     end;                 end;                 if vtype=$ff then                   internalerror(14357);                 { write changing field update href to the next element }                 inc(href.offset,sizeof(aint));                 if vaddr then                  begin                    location_force_mem(current_asmdata.CurrAsmList,hp.left.location);                    tmpreg:=cg.getaddressregister(current_asmdata.CurrAsmList);                    cg.a_loadaddr_ref_reg(current_asmdata.CurrAsmList,hp.left.location.reference,tmpreg);                    cg.a_load_reg_ref(current_asmdata.CurrAsmList,OS_ADDR,OS_ADDR,tmpreg,href);                  end                 else                  cg.a_load_loc_ref(current_asmdata.CurrAsmList,OS_ADDR,hp.left.location,href);                 { update href to the vtype field and write it }                 dec(href.offset,sizeof(aint));                 cg.a_load_const_ref(current_asmdata.CurrAsmList, OS_INT,vtype,href);                 { goto next array element }                 inc(href.offset,sizeof(aint)*2);               end              else              { normal array constructor of the same type }               begin                 if resultdef.needs_inittable then                   freetemp:=false;                 case hp.left.location.loc of                   LOC_MMREGISTER,                   LOC_CMMREGISTER:                     cg.a_loadmm_reg_ref(current_asmdata.CurrAsmList,hp.left.location.size,hp.left.location.size,                       hp.left.location.register,href,mms_movescalar);                   LOC_FPUREGISTER,                   LOC_CFPUREGISTER :                     cg.a_loadfpu_reg_ref(current_asmdata.CurrAsmList,hp.left.location.size,hp.left.location.size,hp.left.location.register,href);                   LOC_REFERENCE,                   LOC_CREFERENCE :                     begin                       if is_shortstring(hp.left.resultdef) then                         cg.g_copyshortstring(current_asmdata.CurrAsmList,hp.left.location.reference,href,                             Tstringdef(hp.left.resultdef).len)                       else                         cg.g_concatcopy(current_asmdata.CurrAsmList,hp.left.location.reference,href,elesize);                     end;                   else                     begin{$ifndef cpu64bit}                       if hp.left.location.size in [OS_64,OS_S64] then                         cg64.a_load64_loc_ref(current_asmdata.CurrAsmList,hp.left.location,href)                       else{$endif cpu64bit}                         cg.a_load_loc_ref(current_asmdata.CurrAsmList,hp.left.location.size,hp.left.location,href);                     end;                 end;                 inc(href.offset,elesize);               end;              if freetemp then                location_freetemp(current_asmdata.CurrAsmList,hp.left.location);            end;           { load next entry }           hp:=tarrayconstructornode(hp.right);         end;      end;{*****************************************************************************                           SecondRTTI*****************************************************************************}    procedure tcgrttinode.pass_generate_code;      begin        location_reset(location,LOC_CREFERENCE,OS_NO);        location.reference.symbol:=RTTIWriter.get_rtti_label(rttidef,rttitype);      end;begin   cloadnode:=tcgloadnode;   cassignmentnode:=tcgassignmentnode;   carrayconstructornode:=tcgarrayconstructornode;   crttinode:=tcgrttinode;end.
 |