{ $Id$ Copyright (c) 1998-2002 by Florian Klaempfl Generate assembler for call 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 ncgcal; {$i fpcdefs.inc} interface uses cpubase, globtype, symdef,node,ncal; type tcgcallparanode = class(tcallparanode) private tempparaloc : tparalocation; procedure allocate_tempparaloc; procedure push_addr_para; procedure push_value_para; public procedure secondcallparan;override; end; tcgcallnode = class(tcallnode) private procedure release_para_temps; procedure normal_pass_2; procedure inlined_pass_2; protected { save the size of pushed parameter, needed po_clearstack and alignment } pushedparasize : longint; framepointer_paraloc : tparalocation; refcountedtemp : treference; procedure handle_return_value; {# This routine is used to push the current frame pointer on the stack. This is used in nested routines where the value of the frame pointer is always pushed as an extra parameter. The default handling is the standard handling used on most stack based machines, where the frame pointer is the first invisible parameter. } function align_parasize:longint;virtual; procedure pop_parasize(pop_size:longint);virtual; procedure extra_interrupt_code;virtual; procedure extra_call_code;virtual; procedure do_syscall;virtual;abstract; public procedure pass_2;override; end; implementation uses systems, cutils,verbose,globals, symconst,symsym,symtable,defutil,paramgr, {$ifdef GDB} {$ifdef delphi} sysutils, {$else} strings, {$endif} gdb, {$endif GDB} cgbase,pass_2, cpuinfo,aasmbase,aasmtai, nbas,nmem,nld,ncnv,nutils, {$ifdef x86} cga,cgx86, {$endif x86} ncgutil, cgutils,cgobj,tgobj, procinfo; {***************************************************************************** TCGCALLPARANODE *****************************************************************************} procedure tcgcallparanode.allocate_tempparaloc; begin { Allocate (temporary) paralocation } tempparaloc:=paraitem.paraloc[callerside]; case tempparaloc.loc of LOC_REGISTER,LOC_FPUREGISTER,LOC_MMREGISTER: paramanager.alloctempregs(exprasmlist,tempparaloc); {$ifdef cputargethasfixedstack} LOC_REFERENCE: begin { currently, we copy the value always to a secure location } if not(assigned(aktcallnode.inlinecode)) then paramanager.alloctempparaloc(exprasmlist,aktcallnode.procdefinition.proccalloption,paraitem,tempparaloc); end; {$endif cputargethasfixedstack} end; end; procedure tcgcallparanode.push_addr_para; begin if not(left.location.loc in [LOC_CREFERENCE,LOC_REFERENCE]) then internalerror(200304235); location_release(exprasmlist,left.location); cg.a_paramaddr_ref(exprasmlist,left.location.reference,tempparaloc); inc(tcgcallnode(aktcallnode).pushedparasize,POINTER_SIZE); end; procedure tcgcallparanode.push_value_para; var href : treference; size : longint; cgsize : tcgsize; begin { we've nothing to push when the size of the parameter is 0 } if left.resulttype.def.size=0 then exit; { Move flags and jump in register to make it less complex } if left.location.loc in [LOC_FLAGS,LOC_JUMP] then location_force_reg(exprasmlist,left.location,def_cgsize(left.resulttype.def),false); { Handle Floating point types differently } if left.resulttype.def.deftype=floatdef then begin location_release(exprasmlist,left.location); {$ifdef i386} if tempparaloc.loc<>LOC_REFERENCE then internalerror(200309291); case left.location.loc of LOC_FPUREGISTER, LOC_CFPUREGISTER: begin size:=align(TCGSize2Size[left.location.size],tempparaloc.alignment); inc(tcgcallnode(aktcallnode).pushedparasize,size); if tempparaloc.reference.index=NR_STACK_POINTER_REG then begin cg.g_stackpointer_alloc(exprasmlist,size); reference_reset_base(href,NR_STACK_POINTER_REG,0); end else reference_reset_base(href,tempparaloc.reference.index,tempparaloc.reference.offset); cg.a_loadfpu_reg_ref(exprasmlist,def_cgsize(left.resulttype.def),left.location.register,href); end; LOC_MMREGISTER, LOC_CMMREGISTER: begin size:=align(tfloatdef(left.resulttype.def).size,tempparaloc.alignment); inc(tcgcallnode(aktcallnode).pushedparasize,size); if tempparaloc.reference.index=NR_STACK_POINTER_REG then begin cg.g_stackpointer_alloc(exprasmlist,size); reference_reset_base(href,NR_STACK_POINTER_REG,0); end else reference_reset_base(href,tempparaloc.reference.index,tempparaloc.reference.offset); cg.a_loadmm_reg_ref(exprasmlist,def_cgsize(left.resulttype.def),def_cgsize(left.resulttype.def),left.location.register,href,mms_movescalar); end; LOC_REFERENCE, LOC_CREFERENCE : begin size:=align(left.resulttype.def.size,tempparaloc.alignment); if tempparaloc.reference.index=NR_STACK_POINTER_REG then begin href:=left.location.reference; inc(href.offset,size); while (size>0) do begin if (size>=4) or (tempparaloc.alignment>=4) then begin cgsize:=OS_32; inc(tcgcallnode(aktcallnode).pushedparasize,4); dec(href.offset,4); dec(size,4); end else begin cgsize:=OS_16; inc(tcgcallnode(aktcallnode).pushedparasize,2); dec(href.offset,2); dec(size,2); end; cg.a_param_ref(exprasmlist,cgsize,href,tempparaloc); end; end else begin reference_reset_base(href,tempparaloc.reference.index,tempparaloc.reference.offset); cg.g_concatcopy(exprasmlist,left.location.reference,href,size,false,false); inc(tcgcallnode(aktcallnode).pushedparasize,size); end; end; else internalerror(2002042430); end; {$else i386} case left.location.loc of LOC_MMREGISTER, LOC_CMMREGISTER: case tempparaloc.loc of LOC_REFERENCE, LOC_CREFERENCE, LOC_MMREGISTER, LOC_CMMREGISTER: cg.a_parammm_reg(exprasmlist,def_cgsize(left.resulttype.def),left.location.register,tempparaloc,mms_movescalar); LOC_FPUREGISTER, LOC_CFPUREGISTER: begin location_force_fpureg(exprasmlist,left.location,false); cg.a_paramfpu_reg(exprasmlist,def_cgsize(left.resulttype.def),left.location.register,tempparaloc); end; else internalerror(2002042433); end; LOC_FPUREGISTER, LOC_CFPUREGISTER: case tempparaloc.loc of LOC_MMREGISTER, LOC_CMMREGISTER: begin location_force_mmregscalar(exprasmlist,left.location,false); cg.a_parammm_reg(exprasmlist,def_cgsize(left.resulttype.def),left.location.register,tempparaloc,mms_movescalar); end; {$ifdef sparc} { sparc pushes floats in normal registers } LOC_REGISTER, LOC_CREGISTER, {$endif sparc} LOC_REFERENCE, LOC_CREFERENCE, LOC_FPUREGISTER, LOC_CFPUREGISTER: cg.a_paramfpu_reg(exprasmlist,def_cgsize(left.resulttype.def),left.location.register,tempparaloc); else internalerror(2002042433); end; LOC_REFERENCE, LOC_CREFERENCE: case tempparaloc.loc of LOC_MMREGISTER, LOC_CMMREGISTER: cg.a_parammm_ref(exprasmlist,def_cgsize(left.resulttype.def),left.location.reference,tempparaloc,mms_movescalar); {$ifdef sparc} { sparc pushes floats in normal registers } LOC_REGISTER, LOC_CREGISTER, {$endif sparc} LOC_REFERENCE, LOC_CREFERENCE, LOC_FPUREGISTER, LOC_CFPUREGISTER: cg.a_paramfpu_ref(exprasmlist,def_cgsize(left.resulttype.def),left.location.reference,tempparaloc); else internalerror(2002042431); end; else internalerror(2002042432); end; {$endif i386} end else begin { copy the value on the stack or use normal parameter push? Check for varargs first because that has no paraitem } if not(cpf_varargs_para in callparaflags) and paramanager.copy_value_on_stack(paraitem.paratyp,left.resulttype.def, aktcallnode.procdefinition.proccalloption) then begin location_release(exprasmlist,left.location); {$ifdef i386} if tempparaloc.loc<>LOC_REFERENCE then internalerror(200309292); if not (left.location.loc in [LOC_REFERENCE,LOC_CREFERENCE]) then internalerror(200204241); { push on stack } size:=align(left.resulttype.def.size,tempparaloc.alignment); inc(tcgcallnode(aktcallnode).pushedparasize,size); if tempparaloc.reference.index=NR_STACK_POINTER_REG then begin cg.g_stackpointer_alloc(exprasmlist,size); reference_reset_base(href,NR_STACK_POINTER_REG,0); end else reference_reset_base(href,tempparaloc.reference.index,tempparaloc.reference.offset); cg.g_concatcopy(exprasmlist,left.location.reference,href,size,false,false); {$else i386} cg.a_param_copy_ref(exprasmlist,left.resulttype.def.size,left.location.reference,tempparaloc); {$endif i386} end else begin case left.location.loc of LOC_CONSTANT, LOC_REGISTER, LOC_CREGISTER, LOC_REFERENCE, LOC_CREFERENCE : begin cgsize:=def_cgsize(left.resulttype.def); if cgsize in [OS_64,OS_S64] then begin inc(tcgcallnode(aktcallnode).pushedparasize,8); cg64.a_param64_loc(exprasmlist,left.location,tempparaloc); location_release(exprasmlist,left.location); end else begin location_release(exprasmlist,left.location); inc(tcgcallnode(aktcallnode).pushedparasize,align(tcgsize2size[tempparaloc.size],tempparaloc.alignment)); cg.a_param_loc(exprasmlist,left.location,tempparaloc); end; end; {$ifdef SUPPORT_MMX} LOC_MMXREGISTER, LOC_CMMXREGISTER: begin location_release(exprasmlist,left.location); inc(tcgcallnode(aktcallnode).pushedparasize,8); cg.a_parammm_reg(exprasmlist,left.location.register); end; {$endif SUPPORT_MMX} else internalerror(200204241); end; end; end; end; procedure tcgcallparanode.secondcallparan; var otlabel, oflabel : tasmlabel; hp : tnode; begin if not(assigned(paraitem)) or not(assigned(paraitem.paratype.def)) or not(assigned(paraitem.parasym) or (cpf_varargs_para in callparaflags)) then internalerror(200304242); { Skip nothingn nodes which are used after disabling a parameter } if (left.nodetype<>nothingn) then begin otlabel:=truelabel; oflabel:=falselabel; objectlibrary.getlabel(truelabel); objectlibrary.getlabel(falselabel); secondpass(left); allocate_tempparaloc; { handle varargs first, because paraitem.parasym is not valid } if (cpf_varargs_para in callparaflags) then begin if paramanager.push_addr_param(vs_value,left.resulttype.def, aktcallnode.procdefinition.proccalloption) then push_addr_para else push_value_para; end { hidden parameters } else if paraitem.is_hidden then begin { don't push a node that already generated a pointer type by address for implicit hidden parameters } if (vo_is_funcret in tvarsym(paraitem.parasym).varoptions) or (not(left.resulttype.def.deftype in [pointerdef,classrefdef]) and paramanager.push_addr_param(paraitem.paratyp,paraitem.paratype.def, aktcallnode.procdefinition.proccalloption)) then push_addr_para else push_value_para; end { formal def } else if (paraitem.paratype.def.deftype=formaldef) then begin { allow passing of a constant to a const formaldef } if (tvarsym(paraitem.parasym).varspez=vs_const) and (left.location.loc=LOC_CONSTANT) then location_force_mem(exprasmlist,left.location); { allow (typecasted) @var } hp:=left; while (hp.nodetype=typeconvn) do hp:=ttypeconvnode(hp).left; if (hp.nodetype=addrn) and (not(nf_procvarload in hp.flags)) then begin inc(tcgcallnode(aktcallnode).pushedparasize,POINTER_SIZE); location_release(exprasmlist,left.location); cg.a_param_loc(exprasmlist,left.location,tempparaloc); end else push_addr_para; end { Normal parameter } else begin { don't push a node that already generated a pointer type by address for implicit hidden parameters } if (not( paraitem.is_hidden and (left.resulttype.def.deftype in [pointerdef,classrefdef]) ) and paramanager.push_addr_param(paraitem.paratyp,paraitem.paratype.def, aktcallnode.procdefinition.proccalloption)) then begin { Check for passing a constant to var,out parameter } if (paraitem.paratyp in [vs_var,vs_out]) and (left.location.loc<>LOC_REFERENCE) then begin { passing self to a var parameter is allowed in TP and delphi } if not((left.location.loc=LOC_CREFERENCE) and is_self_node(left)) then internalerror(200106041); end; { Force to be in memory } if not(left.location.loc in [LOC_CREFERENCE,LOC_REFERENCE]) then location_force_mem(exprasmlist,left.location); push_addr_para; end else push_value_para; end; truelabel:=otlabel; falselabel:=oflabel; { update return location in callnode when this is the function result } if assigned(paraitem.parasym) and (vo_is_funcret in tvarsym(paraitem.parasym).varoptions) then location_copy(aktcallnode.location,left.location); end; { next parameter } if assigned(right) then tcallparanode(right).secondcallparan; end; {***************************************************************************** TCGCALLNODE *****************************************************************************} procedure tcgcallnode.extra_interrupt_code; begin end; procedure tcgcallnode.extra_call_code; begin end; function tcgcallnode.align_parasize:longint; begin result:=0; end; procedure tcgcallnode.pop_parasize(pop_size:longint); begin end; procedure tcgcallnode.handle_return_value; var cgsize : tcgsize; hregister : tregister; tempnode: tnode; begin { structured results are easy to handle.... } { needed also when result_no_used !! } if paramanager.ret_in_param(resulttype.def,procdefinition.proccalloption) then begin { Location should be setup by the funcret para } if location.loc<>LOC_REFERENCE then internalerror(200304241); end else { ansi/widestrings must be registered, so we can dispose them } if resulttype.def.needs_inittable then begin { the FUNCTION_RESULT_REG is already allocated } if not assigned(funcretnode) then begin location_reset(location,LOC_CREFERENCE,OS_ADDR); location.reference:=refcountedtemp; { a_load_reg_ref may allocate registers! } cg.a_load_reg_ref(exprasmlist,OS_ADDR,OS_ADDR,NR_FUNCTION_RESULT_REG,location.reference); cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT_REG); end else begin cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT_REG); hregister := cg.getaddressregister(exprasmlist); cg.a_load_reg_reg(exprasmlist,OS_ADDR,OS_ADDR,NR_FUNCTION_RESULT_REG,hregister); { in case of a regular funcretnode with ret_in_param, the } { original funcretnode isn't touched -> make sure it's } { the same here (not sure if it's necessary) } tempnode := funcretnode.getcopy; tempnode.pass_2; location := tempnode.location; tempnode.free; cg.g_decrrefcount(exprasmlist,resulttype.def,location.reference, false); cg.a_load_reg_ref(exprasmlist,OS_ADDR,OS_ADDR,hregister,location.reference); cg.ungetregister(exprasmlist,hregister); end; end else { we have only to handle the result if it is used } if (cnf_return_value_used in callnodeflags) then begin if (resulttype.def.deftype=floatdef) then begin location_reset(location,LOC_FPUREGISTER,def_cgsize(resulttype.def)); {$ifdef cpufpemu} if cs_fp_emulation in aktmoduleswitches then location.register:=NR_FUNCTION_RESULT_REG else {$endif cpufpemu} begin location.register:=NR_FPU_RESULT_REG; {$ifdef sparc} { Double are returned in F0:F1 } if location.size=OS_F64 then setsubreg(location.register,R_SUBFD); {$endif sparc} end; {$ifdef x86} tcgx86(cg).inc_fpu_stack; {$else x86} cg.ungetregister(exprasmlist,location.register); hregister := cg.getfpuregister(exprasmlist,location.size); cg.a_loadfpu_reg_reg(exprasmlist,location.size,location.register,hregister); location.register := hregister; {$endif x86} end else begin cgsize:=def_cgsize(resulttype.def); if cgsize<>OS_NO then begin location_reset(location,LOC_REGISTER,cgsize); {$ifndef cpu64bit} if cgsize in [OS_64,OS_S64] then begin { Move the function result to free registers, preferably the FUNCTION_RESULT_REG/FUNCTION_RESULTHIGH_REG, so no move is necessary.} { the FUNCTION_RESULT_LOW_REG/FUNCTION_RESULT_HIGH_REG are already allocated } cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT64_LOW_REG); location.registerlow:=cg.getintregister(exprasmlist,OS_INT); cg.a_load_reg_reg(exprasmlist,OS_32,OS_32,NR_FUNCTION_RESULT64_LOW_REG,location.registerlow); cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT64_HIGH_REG); location.registerhigh:=cg.getintregister(exprasmlist,OS_INT); cg.a_load_reg_reg(exprasmlist,OS_32,OS_32,NR_FUNCTION_RESULT64_HIGH_REG,location.registerhigh); end else {$endif cpu64bit} begin {Move the function result to a free register, preferably the FUNCTION_RESULT_REG, so no move is necessary.} { the FUNCTION_RESULT_REG is already allocated } cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT_REG); { change register size after the unget because the getregister was done for the full register } location.register:=cg.getintregister(exprasmlist,cgsize); cg.a_load_reg_reg(exprasmlist,cgsize,cgsize,cg.makeregsize(exprasmlist,NR_FUNCTION_RESULT_REG,cgsize),location.register); end; end else begin if resulttype.def.size>0 then internalerror(200305131); end; end; end else begin cgsize:=def_cgsize(resulttype.def); { an object constructor is a function with pointer result } if (procdefinition.proctypeoption=potype_constructor) then cgsize:=OS_ADDR; if cgsize<>OS_NO then {$ifndef cpu64bit} if cgsize in [OS_64,OS_S64] then begin cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT64_LOW_REG); cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT64_HIGH_REG); end else {$endif cpu64bit} cg.ungetregister(exprasmlist,NR_FUNCTION_RESULT_REG); location_reset(location,LOC_VOID,OS_NO); end; end; procedure tcgcallnode.release_para_temps; var hp : tnode; ppn : tcallparanode; begin { Release temps from parameters } ppn:=tcallparanode(left); while assigned(ppn) do begin if assigned(ppn.left) then begin { don't release the funcret temp } if not(assigned(ppn.paraitem.parasym)) or not(vo_is_funcret in tvarsym(ppn.paraitem.parasym).varoptions) then location_freetemp(exprasmlist,ppn.left.location); { process also all nodes of an array of const } if ppn.left.nodetype=arrayconstructorn then begin if assigned(tarrayconstructornode(ppn.left).left) then begin hp:=ppn.left; while assigned(hp) do begin location_freetemp(exprasmlist,tarrayconstructornode(hp).left.location); hp:=tarrayconstructornode(hp).right; end; end; end; end; ppn:=tcallparanode(ppn.right); end; end; procedure tcgcallnode.normal_pass_2; var regs_to_push_fpu, regs_to_alloc, regs_to_free : Tcpuregisterset; oldpushedparasize : longint; {$ifdef cputargethasfixedstack} href2, {$endif cputargethasfixedstack} href : treference; pop_size : longint; pvreg, vmtreg : tregister; oldaktcallnode : tcallnode; procedure pushparas; var ppn : tcgcallparanode; begin { copy all resources to the allocated registers } ppn:=tcgcallparanode(left); while assigned(ppn) do begin if (ppn.left.nodetype<>nothingn) then begin { better check for the real location of the parameter here, when stack passed parameters are saved temporary in registers, checking for the tempparaloc.loc is wrong } case ppn.paraitem.paraloc[callerside].loc of LOC_REGISTER: begin paramanager.freeparaloc(exprasmlist,ppn.tempparaloc); paramanager.allocparaloc(exprasmlist,ppn.paraitem.paraloc[callerside]); {$ifdef sparc} case ppn.tempparaloc.size of OS_F32 : ppn.tempparaloc.size:=OS_32; OS_F64 : ppn.tempparaloc.size:=OS_64; end; {$endif sparc} {$ifndef cpu64bit} if ppn.tempparaloc.size in [OS_64,OS_S64] then begin cg.a_load_reg_reg(exprasmlist,OS_32,OS_32,ppn.tempparaloc.registerlow, ppn.paraitem.paraloc[callerside].registerlow); cg.a_load_reg_reg(exprasmlist,OS_32,OS_32,ppn.tempparaloc.registerhigh, ppn.paraitem.paraloc[callerside].registerhigh); end else {$endif cpu64bit} cg.a_load_reg_reg(exprasmlist,ppn.tempparaloc.size,ppn.tempparaloc.size, ppn.tempparaloc.register,ppn.paraitem.paraloc[callerside].register); end; LOC_FPUREGISTER: begin paramanager.freeparaloc(exprasmlist,ppn.tempparaloc); paramanager.allocparaloc(exprasmlist,ppn.paraitem.paraloc[callerside]); cg.a_loadfpu_reg_reg(exprasmlist,ppn.tempparaloc.size, ppn.tempparaloc.register,ppn.paraitem.paraloc[callerside].register); end; LOC_MMREGISTER: begin paramanager.freeparaloc(exprasmlist,ppn.tempparaloc); paramanager.allocparaloc(exprasmlist,ppn.paraitem.paraloc[callerside]); cg.a_loadmm_reg_reg(exprasmlist,ppn.tempparaloc.size, ppn.tempparaloc.size,ppn.tempparaloc.register,ppn.paraitem.paraloc[callerside].register,mms_movescalar); end; LOC_REFERENCE: begin {$ifdef cputargethasfixedstack} { copy parameters in case they were moved to a temp. location because we've a fixed stack } paramanager.freeparaloc(exprasmlist,ppn.tempparaloc); paramanager.allocparaloc(exprasmlist,ppn.paraitem.paraloc[callerside]); case ppn.tempparaloc.loc of LOC_REFERENCE: begin reference_reset_base(href,ppn.tempparaloc.reference.index,ppn.tempparaloc.reference.offset); reference_reset_base(href2,ppn.paraitem.paraloc[callerside].reference.index,ppn.paraitem.paraloc[callerside].reference.offset); cg.g_concatcopy(exprasmlist,href,href2,ppn.paraitem.paratype.def.size,false,false); end; LOC_REGISTER: if ppn.tempparaloc.size in [OS_64,OS_S64] then begin reference_reset_base(href,ppn.paraitem.paraloc[callerside].reference.index,ppn.paraitem.paraloc[callerside].reference.offset); cg.a_load_reg_ref(exprasmlist,OS_32,OS_32,ppn.tempparaloc.registerlow, href); { we don't use a c64.load here because later (when fixed ;)) one dword could be on the stack and the other in a cpu register } reference_reset_base(href,ppn.paraitem.paraloc[callerside].reference.index,ppn.paraitem.paraloc[callerside].reference.offset+4); cg.a_load_reg_ref(exprasmlist,OS_32,OS_32,ppn.tempparaloc.registerhigh, href); end else cg.a_param_reg(exprasmlist,ppn.paraitem.paraloc[callerside].size,ppn.tempparaloc.register,ppn.paraitem.paraloc[callerside]); LOC_FPUREGISTER: cg.a_paramfpu_reg(exprasmlist,ppn.paraitem.paraloc[callerside].size,ppn.tempparaloc.register,ppn.paraitem.paraloc[callerside]); else internalerror(200402081); end; {$endif cputargethasfixedstack} end; else internalerror(200402091); end; end; ppn:=tcgcallparanode(ppn.right); end; end; procedure freeparas; var ppn : tcgcallparanode; begin { free the resources allocated for the parameters } ppn:=tcgcallparanode(left); while assigned(ppn) do begin paramanager.freeparaloc(exprasmlist,ppn.paraitem.paraloc[callerside]); ppn:=tcgcallparanode(ppn.right); end; end; begin if not assigned(procdefinition) or not procdefinition.has_paraloc_info then internalerror(200305264); if resulttype.def.needs_inittable and not paramanager.ret_in_param(resulttype.def,procdefinition.proccalloption) and not assigned(funcretnode) then begin tg.gettemptyped(exprasmlist,resulttype.def,tt_normal,refcountedtemp); cg.g_decrrefcount(exprasmlist,resulttype.def,refcountedtemp,false); end; regs_to_alloc:=paramanager.get_volatile_registers_int(procdefinition.proccalloption); regs_to_push_fpu:=paramanager.get_volatile_registers_fpu(procdefinition.proccalloption); { Include Function result registers } if (not is_void(resulttype.def)) then begin case procdefinition.funcret_paraloc[callerside].loc of LOC_REGISTER,LOC_CREGISTER: begin {$ifndef cpu64bit} if procdefinition.funcret_paraloc[callerside].size in [OS_S64,OS_64] then begin include(regs_to_alloc,getsupreg(procdefinition.funcret_paraloc[callerside].registerlow)); include(regs_to_alloc,getsupreg(procdefinition.funcret_paraloc[callerside].registerhigh)); end else {$endif cpu64bit} include(regs_to_alloc,getsupreg(procdefinition.funcret_paraloc[callerside].register)); end; LOC_FPUREGISTER,LOC_CFPUREGISTER: begin include(regs_to_push_fpu,getsupreg(procdefinition.funcret_paraloc[callerside].register)); end; LOC_MMREGISTER,LOC_CMMREGISTER: begin internalerror(2003102911); end; end; end; { Initialize for pushing the parameters } oldpushedparasize:=pushedparasize; pushedparasize:=0; { Process parameters, register parameters will be loaded in imaginary registers. The actual load to the correct register is done just before the call } oldaktcallnode:=aktcallnode; aktcallnode:=self; if assigned(left) then tcallparanode(left).secondcallparan; aktcallnode:=oldaktcallnode; { Align stack if required } pop_size:=align_parasize; { procedure variable or normal function call ? } if (right=nil) then begin if (po_virtualmethod in procdefinition.procoptions) and assigned(methodpointer) then begin secondpass(methodpointer); location_force_reg(exprasmlist,methodpointer.location,OS_ADDR,false); { virtual methods require an index } if tprocdef(procdefinition).extnumber=-1 then internalerror(200304021); { VMT should already be loaded in a register } if methodpointer.location.register=NR_NO then internalerror(200304022); { test validity of VMT } if not(is_interface(tprocdef(procdefinition)._class)) and not(is_cppclass(tprocdef(procdefinition)._class)) then cg.g_maybe_testvmt(exprasmlist,methodpointer.location.register,tprocdef(procdefinition)._class); end; {$warning fixme regvars} { rg.saveotherregvars(exprasmlist,regs_to_push_other);} if (po_virtualmethod in procdefinition.procoptions) and assigned(methodpointer) then begin vmtreg:=methodpointer.location.register; { release self } cg.ungetregister(exprasmlist,vmtreg); pvreg:=cg.getintregister(exprasmlist,OS_ADDR); reference_reset_base(href,vmtreg, tprocdef(procdefinition)._class.vmtmethodoffset(tprocdef(procdefinition).extnumber)); cg.a_load_ref_reg(exprasmlist,OS_ADDR,OS_ADDR,href,pvreg); { Load parameters that are in temporary registers in the correct parameter register } if assigned(left) then pushparas; { free the resources allocated for the parameters } freeparas; { Release register containing procvar } cg.ungetregister(exprasmlist,pvreg); cg.allocexplicitregisters(exprasmlist,R_INTREGISTER,regs_to_alloc); if cg.uses_registers(R_FPUREGISTER) then cg.allocexplicitregisters(exprasmlist,R_FPUREGISTER,regs_to_push_fpu); if cg.uses_registers(R_MMREGISTER) then cg.allocexplicitregisters(exprasmlist,R_MMREGISTER,paramanager.get_volatile_registers_mm(procdefinition.proccalloption)); { call method } extra_call_code; cg.a_call_reg(exprasmlist,pvreg); end else begin { Load parameters that are in temporary registers in the correct parameter register } if assigned(left) then pushparas; { free the resources allocated for the parameters } freeparas; cg.allocexplicitregisters(exprasmlist,R_INTREGISTER,regs_to_alloc); if cg.uses_registers(R_FPUREGISTER) then cg.allocexplicitregisters(exprasmlist,R_FPUREGISTER,regs_to_push_fpu); if cg.uses_registers(R_MMREGISTER) then cg.allocexplicitregisters(exprasmlist,R_MMREGISTER,paramanager.get_volatile_registers_mm(procdefinition.proccalloption)); if procdefinition.proccalloption=pocall_syscall then do_syscall else begin { Calling interrupt from the same code requires some extra code } if (po_interrupt in procdefinition.procoptions) then extra_interrupt_code; extra_call_code; cg.a_call_name(exprasmlist,tprocdef(procdefinition).mangledname); end; end; end else { now procedure variable case } begin secondpass(right); location_release(exprasmlist,right.location); pvreg:=cg.getintregister(exprasmlist,OS_ADDR); { Only load OS_ADDR from the reference } if right.location.loc in [LOC_REFERENCE,LOC_CREFERENCE] then cg.a_load_ref_reg(exprasmlist,OS_ADDR,OS_ADDR,right.location.reference,pvreg) else cg.a_load_loc_reg(exprasmlist,OS_ADDR,right.location,pvreg); location_freetemp(exprasmlist,right.location); { Load parameters that are in temporary registers in the correct parameter register } if assigned(left) then pushparas; { free the resources allocated for the parameters } freeparas; { Release register containing procvar } cg.ungetregister(exprasmlist,pvreg); cg.allocexplicitregisters(exprasmlist,R_INTREGISTER,regs_to_alloc); if cg.uses_registers(R_FPUREGISTER) then cg.allocexplicitregisters(exprasmlist,R_FPUREGISTER,regs_to_push_fpu); if cg.uses_registers(R_MMREGISTER) then cg.allocexplicitregisters(exprasmlist,R_MMREGISTER,paramanager.get_volatile_registers_mm(procdefinition.proccalloption)); { Calling interrupt from the same code requires some extra code } if (po_interrupt in procdefinition.procoptions) then extra_interrupt_code; {$warning fixme regvars.} { rg.saveotherregvars(exprasmlist,ALL_OTHERREGISTERS);} extra_call_code; cg.a_call_reg(exprasmlist,pvreg); end; { Need to remove the parameters from the stack? } if (procdefinition.proccalloption in clearstack_pocalls) then begin { the old pop_size was already included in pushedparasize } pop_size:=pushedparasize; { for Cdecl functions we don't need to pop the funcret when it was pushed by para } if paramanager.ret_in_param(procdefinition.rettype.def,procdefinition.proccalloption) then dec(pop_size,POINTER_SIZE); end; { Remove parameters/alignment from the stack } if pop_size>0 then pop_parasize(pop_size); { Reserve space for storing parameters that will be pushed } current_procinfo.allocate_push_parasize(pushedparasize); { Restore } pushedparasize:=oldpushedparasize; { Release registers, but not the registers that contain the function result } regs_to_free:=regs_to_alloc; if (not is_void(resulttype.def)) then begin case procdefinition.funcret_paraloc[callerside].loc of LOC_REGISTER,LOC_CREGISTER: begin {$ifndef cpu64bit} if procdefinition.funcret_paraloc[callerside].size in [OS_S64,OS_64] then begin exclude(regs_to_free,getsupreg(procdefinition.funcret_paraloc[callerside].registerlow)); exclude(regs_to_free,getsupreg(procdefinition.funcret_paraloc[callerside].registerhigh)); end else {$endif cpu64bit} exclude(regs_to_free,getsupreg(procdefinition.funcret_paraloc[callerside].register)); end; LOC_FPUREGISTER,LOC_CFPUREGISTER: begin exclude(regs_to_push_fpu,getsupreg(procdefinition.funcret_paraloc[callerside].register)); end; end; end; if cg.uses_registers(R_MMREGISTER) then cg.deallocexplicitregisters(exprasmlist,R_MMREGISTER,paramanager.get_volatile_registers_mm(procdefinition.proccalloption)); if cg.uses_registers(R_FPUREGISTER) then cg.deallocexplicitregisters(exprasmlist,R_FPUREGISTER,regs_to_push_fpu); cg.deallocexplicitregisters(exprasmlist,R_INTREGISTER,regs_to_free); { handle function results } if (not is_void(resulttype.def)) then handle_return_value else location_reset(location,LOC_VOID,OS_NO); { perhaps i/o check ? } if (cs_check_io in aktlocalswitches) and (po_iocheck in procdefinition.procoptions) and not(po_iocheck in current_procinfo.procdef.procoptions) and { no IO check for methods and procedure variables } (right=nil) and not(po_virtualmethod in procdefinition.procoptions) then begin cg.allocexplicitregisters(exprasmlist,R_INTREGISTER,paramanager.get_volatile_registers_int(pocall_default)); cg.a_call_name(exprasmlist,'FPC_IOCHECK'); cg.deallocexplicitregisters(exprasmlist,R_INTREGISTER,paramanager.get_volatile_registers_int(pocall_default)); end; { release temps of paras } release_para_temps; { if return value is not used } if (not(cnf_return_value_used in callnodeflags)) and (not is_void(resulttype.def)) then begin if location.loc in [LOC_CREFERENCE,LOC_REFERENCE] then begin { data which must be finalized ? } if (resulttype.def.needs_inittable) then cg.g_finalize(exprasmlist,resulttype.def,location.reference,false); { release unused temp } tg.ungetiftemp(exprasmlist,location.reference) end else if location.loc=LOC_FPUREGISTER then begin {$ifdef x86} { release FPU stack } emit_reg(A_FSTP,S_NO,NR_FPU_RESULT_REG); {$endif x86} end; end; end; procedure tcgcallnode.inlined_pass_2; var oldaktcallnode : tcallnode; oldprocinfo : tprocinfo; oldinlining_procedure : boolean; inlineentrycode,inlineexitcode : TAAsmoutput; usesacc,usesacchi,usesfpu : boolean; {$ifdef GDB} startlabel,endlabel : tasmlabel; pp : pchar; mangled_length : longint; {$endif GDB} begin if not(assigned(procdefinition) and (procdefinition.deftype=procdef)) then internalerror(200305262); oldinlining_procedure:=inlining_procedure; oldprocinfo:=current_procinfo; { we're inlining a procedure } inlining_procedure:=true; { Add inling start } {$ifdef GDB} exprasmlist.concat(Tai_force_line.Create); {$endif GDB} exprasmList.concat(Tai_Marker.Create(InlineStart)); {$ifdef extdebug} exprasmList.concat(tai_comment.Create(strpnew('Start of inlined proc '+tprocdef(procdefinition).procsym.name))); {$endif extdebug} { calculate registers to pass the parameters } paramanager.create_inline_paraloc_info(procdefinition); { Allocate parameters and locals } gen_alloc_inline_parast(exprasmlist,tparasymtable(procdefinition.parast)); if tprocdef(procdefinition).localst.symtabletype=localsymtable then gen_alloc_localst(exprasmlist,tlocalsymtable(tprocdef(procdefinition).localst)); { if we allocate the temp. location for ansi- or widestrings } { already here, we avoid later a push/pop } if resulttype.def.needs_inittable and not paramanager.ret_in_param(resulttype.def,procdefinition.proccalloption) then begin tg.gettemptyped(exprasmlist,resulttype.def,tt_normal,refcountedtemp); cg.g_decrrefcount(exprasmlist,resulttype.def,refcountedtemp,false); end; { Push parameters, still use the old current_procinfo. This is required that have the correct information available like _class and nested procedure } oldaktcallnode:=aktcallnode; aktcallnode:=self; if assigned(left) then tcallparanode(left).secondcallparan; aktcallnode:=oldaktcallnode; { create temp procinfo that will be used for the inlinecode tree } current_procinfo:=cprocinfo.create(nil); current_procinfo.procdef:=tprocdef(procdefinition); current_procinfo.flags:=oldprocinfo.flags; current_procinfo.aktlocaldata.destroy; current_procinfo.aktlocaldata:=oldprocinfo.aktlocaldata; { when the oldprocinfo is also being inlined reuse the inlining_procinfo } if assigned(oldprocinfo.inlining_procinfo) then current_procinfo.inlining_procinfo:=oldprocinfo.inlining_procinfo else current_procinfo.inlining_procinfo:=oldprocinfo; { takes care of local data initialization } inlineentrycode:=TAAsmoutput.Create; inlineexitcode:=TAAsmoutput.Create; {$ifdef GDB} if (cs_debuginfo in aktmoduleswitches) and not(cs_gdb_valgrind in aktglobalswitches) then begin objectlibrary.getaddrlabel(startlabel); objectlibrary.getaddrlabel(endlabel); cg.a_label(exprasmlist,startlabel); { Here we must include the para and local symtable info } procdefinition.concatstabto(withdebuglist); mangled_length:=length(current_procinfo.inlining_procinfo.procdef.mangledname); getmem(pp,mangled_length+50); strpcopy(pp,'192,0,0,'+startlabel.name); if (target_info.use_function_relative_addresses) then begin strpcopy(strend(pp),'-'); strpcopy(strend(pp),current_procinfo.inlining_procinfo.procdef.mangledname); end; withdebugList.concat(Tai_stabn.Create(strnew(pp))); end; {$endif GDB} gen_load_para_value(inlineentrycode); gen_initialize_code(inlineentrycode,true); if po_assembler in current_procinfo.procdef.procoptions then inlineentrycode.insert(Tai_marker.Create(asmblockstart)); exprasmList.concatlist(inlineentrycode); { process the inline code } secondpass(inlinecode); cg.a_label(exprasmlist,current_procinfo.aktexitlabel); gen_finalize_code(inlineexitcode,true); gen_load_return_value(inlineexitcode,usesacc,usesacchi,usesfpu); if po_assembler in current_procinfo.procdef.procoptions then inlineexitcode.concat(Tai_marker.Create(asmblockend)); exprasmlist.concatlist(inlineexitcode); inlineentrycode.free; inlineexitcode.free; {$ifdef extdebug} exprasmList.concat(tai_comment.Create(strpnew('End of inlined proc'))); {$endif extdebug} exprasmList.concat(Tai_Marker.Create(InlineEnd)); { handle function results } if (not is_void(resulttype.def)) then handle_return_value else location_reset(location,LOC_VOID,OS_NO); { perhaps i/o check ? } if (cs_check_io in aktlocalswitches) and (po_iocheck in procdefinition.procoptions) and not(po_iocheck in current_procinfo.procdef.procoptions) and { no IO check for methods and procedure variables } (right=nil) and not(po_virtualmethod in procdefinition.procoptions) then begin cg.allocexplicitregisters(exprasmlist,R_INTREGISTER,paramanager.get_volatile_registers_int(pocall_default)); cg.a_call_name(exprasmlist,'FPC_IOCHECK'); cg.deallocexplicitregisters(exprasmlist,R_INTREGISTER,paramanager.get_volatile_registers_int(pocall_default)); end; { release temps of paras } release_para_temps; { if return value is not used } if (not is_void(resulttype.def)) and (not(cnf_return_value_used in callnodeflags)) then begin if location.loc in [LOC_CREFERENCE,LOC_REFERENCE] then begin { data which must be finalized ? } if (resulttype.def.needs_inittable) then cg.g_finalize(exprasmlist,resulttype.def,location.reference,false); { release unused temp } tg.ungetiftemp(exprasmlist,location.reference) end else if location.loc=LOC_FPUREGISTER then begin {$ifdef x86} { release FPU stack } emit_reg(A_FSTP,S_NO,NR_FPU_RESULT_REG); {$endif x86} end; end; { Release parameters and locals } gen_free_parast(exprasmlist,tparasymtable(current_procinfo.procdef.parast)); if current_procinfo.procdef.localst.symtabletype=localsymtable then gen_free_localst(exprasmlist,tlocalsymtable(current_procinfo.procdef.localst)); {$ifdef GDB} if (cs_debuginfo in aktmoduleswitches) and not(cs_gdb_valgrind in aktglobalswitches) then begin cg.a_label(exprasmlist,endlabel); strpcopy(pp,'224,0,0,'+endlabel.name); if (target_info.use_function_relative_addresses) then begin strpcopy(strend(pp),'-'); strpcopy(strend(pp),current_procinfo.inlining_procinfo.procdef.mangledname); end; withdebugList.concat(Tai_stabn.Create(strnew(pp))); freemem(pp,mangled_length+50); end; {$endif GDB} { restore } current_procinfo.aktlocaldata:=nil; current_procinfo.destroy; current_procinfo:=oldprocinfo; inlining_procedure:=oldinlining_procedure; end; procedure tcgcallnode.pass_2; begin if assigned(methodpointerinit) then secondpass(methodpointerinit); if assigned(inlinecode) then inlined_pass_2 else normal_pass_2; if assigned(methodpointerdone) then secondpass(methodpointerdone); end; begin ccallparanode:=tcgcallparanode; ccallnode:=tcgcallnode; end. { $Log$ Revision 1.167 2004-05-23 18:28:41 peter * methodpointer is loaded into a temp when it was a calln Revision 1.166 2004/05/22 23:34:27 peter tai_regalloc.allocation changed to ratype to notify rgobj of register size changes Revision 1.165 2004/04/28 15:19:03 florian + syscall directive support for MorphOS added Revision 1.164 2004/03/14 20:10:56 peter * disable some debuginfo info when valgrind support is used Revision 1.163 2004/03/13 21:23:21 florian * fixed inlining on arm Revision 1.162 2004/03/09 16:28:31 peter * fix for sparc that pushes floats in int registers Revision 1.161 2004/03/09 13:04:12 mazen + difference between three similar internal errors Revision 1.160 2004/02/27 10:21:05 florian * top_symbol killed + refaddr to treference added + refsymbol to treference added * top_local stuff moved to an extra record to save memory + aint introduced * tppufile.get/putint64/aint implemented Revision 1.159 2004/02/26 16:12:04 peter * support typecasts for passing @var to formal const Revision 1.158 2004/02/22 13:01:15 daniel * Fixed memory leak Revision 1.157 2004/02/22 12:04:04 florian + nx86set added * some more x86-64 fixes Revision 1.156 2004/02/20 22:16:35 florian * handling of float parameters passed in mm registers fixed Revision 1.155 2004/02/20 21:55:59 peter * procvar cleanup Revision 1.154 2004/02/11 19:59:06 peter * fix compilation without GDB Revision 1.153 2004/02/09 22:48:45 florian * several fixes to parameter handling on arm Revision 1.152 2004/01/31 17:45:17 peter * Change several $ifdef i386 to x86 * Change several OS_32 to OS_INT/OS_ADDR Revision 1.151 2004/01/26 17:34:14 florian * set aktlocaldata for inlined procedures correctly Revision 1.150 2004/01/12 16:39:40 peter * sparc updates, mostly float related Revision 1.149 2003/12/28 22:09:12 florian + setting of bit 6 of cr for c var args on ppc implemented Revision 1.148 2003/12/26 13:19:16 florian * rtl and compiler compile with -Cfsse2 Revision 1.147 2003/12/21 19:42:42 florian * fixed ppc inlining stuff * fixed wrong unit writing + added some sse stuff Revision 1.146 2003/12/15 21:25:48 peter * reg allocations for imaginary register are now inserted just before reg allocation * tregister changed to enum to allow compile time check * fixed several tregister-tsuperregister errors Revision 1.145 2003/12/07 12:41:32 jonas * fixed ansistring/widestring results: deallocate result reg only after it has been stored to memory, as the storing itself may require extra results (e.g. on ppc) Revision 1.144 2003/12/06 01:15:22 florian * reverted Peter's alloctemp patch; hopefully properly Revision 1.143 2003/12/03 23:13:20 peter * delayed paraloc allocation, a_param_*() gets extra parameter if it needs to allocate temp or real paralocation * optimized/simplified int-real loading Revision 1.142 2003/12/02 21:23:34 peter * exitlabel for inline procs Revision 1.141 2003/11/23 17:39:33 peter * removed obsolete nf_cargs flag Revision 1.140 2003/11/23 17:05:15 peter * register calling is left-right * parameter ordering * left-right calling inserts result parameter last Revision 1.139 2003/11/10 22:02:52 peter * cross unit inlining fixed Revision 1.138 2003/11/07 15:58:32 florian * Florian's culmutative nr. 1; contains: - invalid calling conventions for a certain cpu are rejected - arm softfloat calling conventions - -Sp for cpu dependend code generation - several arm fixes - remaining code for value open array paras on heap Revision 1.137 2003/11/04 19:03:54 peter * fixes for temp type patch Revision 1.136 2003/11/04 15:35:13 peter * fix for referencecounted temps Revision 1.135 2003/10/30 17:12:49 peter * fixed rangecheck error Revision 1.134 2003/10/29 21:24:14 jonas + support for fpu temp parameters + saving/restoring of fpu register before/after a procedure call Revision 1.133 2003/10/20 19:28:17 peter * fixed inlining float parameters for i386 Revision 1.132 2003/10/17 14:38:32 peter * 64k registers supported * fixed some memory leaks Revision 1.131 2003/10/17 01:22:08 florian * compilation of the powerpc compiler fixed Revision 1.130 2003/10/11 16:06:42 florian * fixed some MMX<->SSE * started to fix ppc, needs an overhaul + stabs info improve for spilling, not sure if it works correctly/completly - MMX_SUPPORT removed from Makefile.fpc Revision 1.129 2003/10/10 17:48:13 peter * old trgobj moved to x86/rgcpu and renamed to trgx86fpu * tregisteralloctor renamed to trgobj * removed rgobj from a lot of units * moved location_* and reference_* to cgobj * first things for mmx register allocation Revision 1.128 2003/10/10 09:21:53 marco * typo fix from Wiktor Revision 1.127 2003/10/09 21:31:37 daniel * Register allocator splitted, ans abstract now Revision 1.126 2003/10/07 15:17:07 peter * inline supported again, LOC_REFERENCEs are used to pass the parameters * inlineparasymtable,inlinelocalsymtable removed * exitlabel inserting fixed Revision 1.125 2003/10/05 21:21:52 peter * c style array of const generates callparanodes * varargs paraloc fixes Revision 1.124 2003/10/03 22:00:33 peter * parameter alignment fixes Revision 1.123 2003/10/01 20:34:48 peter * procinfo unit contains tprocinfo * cginfo renamed to cgbase * moved cgmessage to verbose * fixed ppc and sparc compiles Revision 1.122 2003/09/30 21:02:37 peter * updates for inlining Revision 1.121 2003/09/30 19:55:19 peter * remove abt reg for vmtreg Revision 1.120 2003/09/29 20:58:55 peter * optimized releasing of registers Revision 1.119 2003/09/28 17:55:03 peter * parent framepointer changed to hidden parameter * tloadparentfpnode added Revision 1.118 2003/09/28 13:54:43 peter * removed a_call_ref Revision 1.117 2003/09/25 21:28:00 peter * parameter fixes Revision 1.116 2003/09/23 17:56:05 peter * locals and paras are allocated in the code generation * tvarsym.localloc contains the location of para/local when generating code for the current procedure Revision 1.115 2003/09/16 16:17:01 peter * varspez in calls to push_addr_param Revision 1.114 2003/09/14 19:17:39 peter * don't use a_call_ref because it can use a parameter register as temp Revision 1.113 2003/09/11 11:54:59 florian * improved arm code generation * move some protected and private field around * the temp. register for register parameters/arguments are now released before the move to the parameter register is done. This improves the code in a lot of cases. Revision 1.112 2003/09/10 08:31:47 marco * Patch from Peter for paraloc Revision 1.111 2003/09/07 22:09:35 peter * preparations for different default calling conventions * various RA fixes Revision 1.110 2003/09/04 15:39:58 peter * released useparatemp Revision 1.109 2003/09/03 15:55:00 peter * NEWRA branch merged Revision 1.108.2.4 2003/09/01 21:02:55 peter * sparc updates for new tregister Revision 1.108.2.3 2003/08/31 21:07:44 daniel * callparatemp ripped Revision 1.108.2.2 2003/08/29 17:28:59 peter * next batch of updates Revision 1.108.2.1 2003/08/27 20:23:55 peter * remove old ra code Revision 1.108 2003/08/21 22:14:16 olle - removed parameter from fpc_iocheck Revision 1.107 2003/08/17 16:59:20 jonas * fixed regvars so they work with newra (at least for ppc) * fixed some volatile register bugs + -dnotranslation option for -dnewra, which causes the registers not to be translated from virtual to normal registers. Requires support in the assembler writer as well, which is only implemented in aggas/ agppcgas currently Revision 1.106 2003/08/16 18:56:40 marco * fix from Jonas. Revision 1.105 2003/08/11 21:18:20 peter * start of sparc support for newra Revision 1.104 2003/08/11 14:22:06 mazen - dupplicated code removed Revision 1.103 2003/07/23 11:01:14 jonas * several rg.allocexplicitregistersint/rg.deallocexplicitregistersint pairs round calls to helpers Revision 1.102 2003/07/21 13:51:50 jonas * fixed 64bit int results with -dnewra (you can't free both registers and then allocate two new ones, because then the registers could be reversed afterwards -> you get something like "movl %eax, %edx; movl %edx,%eax") Revision 1.101 2003/07/08 21:24:59 peter * sparc fixes Revision 1.100 2003/07/06 21:50:33 jonas * fixed ppc compilation problems and changed VOLATILE_REGISTERS for x86 so that it doesn't include ebp and esp anymore Revision 1.99 2003/07/06 17:58:22 peter * framepointer fixes for sparc * parent framepointer code more generic Revision 1.98 2003/07/06 15:31:20 daniel * Fixed register allocator. *Lots* of fixes. Revision 1.97 2003/07/05 20:21:26 jonas * create_paraloc_info() is now called separately for the caller and callee info * fixed ppc cycle Revision 1.96 2003/07/02 22:18:04 peter * paraloc splitted in paraloc[callerside],calleeparaloc * sparc calling convention updates Revision 1.95 2003/06/17 16:34:44 jonas * lots of newra fixes (need getfuncretparaloc implementation for i386)! * renamed all_intregisters to paramanager.get_volatile_registers_int(pocall_default) and made it processor dependent Revision 1.94 2003/06/15 16:52:02 jonas * release function result registers if the functino result isn't used * don't allocate function result register with -dnewra if there is none * some optimizations for non-x86 processor (don't save any registers before a call) Revision 1.93 2003/06/13 21:19:30 peter * current_procdef removed, use current_procinfo.procdef instead Revision 1.92 2003/06/12 21:10:50 peter * newra fixes Revision 1.91 2003/06/12 18:38:45 jonas * deallocate parameter registers in time for newra * for non-i386, procvars and methodpointers always have to be processed in advance, whether or not newra is defined Revision 1.90 2003/06/09 14:54:26 jonas * (de)allocation of registers for parameters is now performed properly (and checked on the ppc) - removed obsolete allocation of all parameter registers at the start of a procedure (and deallocation at the end) Revision 1.89 2003/06/09 12:23:29 peter * init/final of procedure data splitted from genentrycode * use asmnode getposition to insert final at the correct position als for the implicit try...finally Revision 1.88 2003/06/08 20:01:53 jonas * optimized assignments with on the right side a function that returns an ansi- or widestring Revision 1.87 2003/06/08 18:21:47 jonas * fixed weird error in the copyleft statement :) Revision 1.86 2003/06/07 18:57:04 jonas + added freeintparaloc * ppc get/freeintparaloc now check whether the parameter regs are properly allocated/deallocated (and get an extra list para) * ppc a_call_* now internalerrors if pi_do_call is not yet set * fixed lot of missing pi_do_call's Revision 1.85 2003/06/04 06:43:36 jonas * fixed double secondpassing of procvar loads Revision 1.84 2003/06/03 21:11:09 peter * cg.a_load_* get a from and to size specifier * makeregsize only accepts newregister * i386 uses generic tcgnotnode,tcgunaryminus Revision 1.83 2003/06/03 20:27:02 daniel * Restored original methodpointer code for non newra case Revision 1.82 2003/06/03 13:01:59 daniel * Register allocator finished Revision 1.81 2003/06/01 21:38:06 peter * getregisterfpu size parameter added * op_const_reg size parameter added * sparc updates Revision 1.80 2003/05/31 15:05:28 peter * FUNCTION_RESULT64_LOW/HIGH_REG added for int64 results Revision 1.79 2003/05/31 00:59:44 peter * typo in FUNCTION_RESULT_REG Revision 1.78 2003/05/30 23:57:08 peter * more sparc cleanup * accumulator removed, splitted in function_return_reg (called) and function_result_reg (caller) Revision 1.77 2003/05/29 10:05:40 jonas * free callparatemps created for call-by-reference parameters Revision 1.76 2003/05/28 23:58:18 jonas * added missing initialization of rg.usedintin,byproc * ppc now also saves/restores used fpu registers * ncgcal doesn't add used registers to usedby/inproc anymore, except for i386 Revision 1.75 2003/05/26 21:17:17 peter * procinlinenode removed * aktexit2label removed, fast exit removed + tcallnode.inlined_pass_2 added Revision 1.74 2003/05/25 11:34:17 peter * methodpointer self pushing fixed Revision 1.73 2003/05/25 08:59:16 peter * inline fixes Revision 1.72 2003/05/24 13:36:54 jonas * save fpu results in a normal fpu register on non-x86 processors Revision 1.71 2003/05/23 19:35:50 jonas - undid previous commit, it was wrong Revision 1.70 2003/05/23 19:11:58 jonas * fixed tests for whether a certain int register is unused Revision 1.69 2003/05/23 18:01:56 jonas * fixed ppc compiler Revision 1.68 2003/05/23 14:27:35 peter * remove some unit dependencies * current_procinfo changes to store more info Revision 1.67 2003/05/17 13:30:08 jonas * changed tt_persistant to tt_persistent :) * tempcreatenode now doesn't accept a boolean anymore for persistent temps, but a ttemptype, so you can also create ansistring temps etc Revision 1.66 2003/05/16 14:33:31 peter * regvar fixes Revision 1.65 2003/05/15 18:58:53 peter * removed selfpointer_offset, vmtpointer_offset * tvarsym.adjusted_address * address in localsymtable is now in the real direction * removed some obsolete globals Revision 1.64 2003/05/14 19:36:54 jonas * patch from Peter for int64 function results Revision 1.63 2003/05/13 19:14:41 peter * failn removed * inherited result code check moven to pexpr Revision 1.62 2003/05/13 15:18:18 peter * generate code for procvar first before pushing parameters. Made the already existing code for powerpc available for all platforms Revision 1.61 2003/05/12 18:17:55 jonas * moved fpc_check_object call earlier for the ppc, so it can't destroy already-loaded parameter registers Revision 1.60 2003/05/11 21:48:38 jonas * fixed procvar bug on the ppc (load procvar before loading para's, because the procvar may otherwise destroy the already loaded paras) Revision 1.59 2003/05/09 17:47:02 peter * self moved to hidden parameter * removed hdisposen,hnewn,selfn Revision 1.58 2003/05/05 14:53:16 peter * vs_hidden replaced by is_hidden boolean Revision 1.57 2003/04/30 20:53:32 florian * error when address of an abstract method is taken * fixed some x86-64 problems * merged some more x86-64 and i386 code Revision 1.56 2003/04/29 07:28:52 michael + Patch from peter to fix wrong pushing of ansistring function results in open array Revision 1.55 2003/04/27 11:21:33 peter * aktprocdef renamed to current_procinfo.procdef * procinfo renamed to current_procinfo * procinfo will now be stored in current_module so it can be cleaned up properly * gen_main_procsym changed to create_main_proc and release_main_proc to also generate a tprocinfo structure * fixed unit implicit initfinal Revision 1.54 2003/04/27 07:29:50 peter * current_procinfo.procdef cleanup, current_procinfo.procdef is now always nil when parsing a new procdef declaration * aktprocsym removed * lexlevel removed, use symtable.symtablelevel instead * implicit init/final code uses the normal genentry/genexit * funcret state checking updated for new funcret handling Revision 1.53 2003/04/25 20:59:33 peter * removed funcretn,funcretsym, function result is now in varsym and aliases for result and function name are added using absolutesym * vs_hidden parameter for funcret passed in parameter * vs_hidden fixes * writenode changed to printnode and released from extdebug * -vp option added to generate a tree.log with the nodetree * nicer printnode for statements, callnode Revision 1.52 2003/04/25 08:25:26 daniel * Ifdefs around a lot of calls to cleartempgen * Fixed registers that are allocated but not freed in several nodes * Tweak to register allocator to cause less spills * 8-bit registers now interfere with esi,edi and ebp Compiler can now compile rtl successfully when using new register allocator Revision 1.51 2003/04/22 23:50:22 peter * firstpass uses expectloc * checks if there are differences between the expectloc and location.loc from secondpass in EXTDEBUG Revision 1.50 2003/04/22 14:33:38 peter * removed some notes/hints Revision 1.49 2003/04/22 13:47:08 peter * fixed C style array of const * fixed C array passing * fixed left to right with high parameters Revision 1.48 2003/04/22 10:09:34 daniel + Implemented the actual register allocator + Scratch registers unavailable when new register allocator used + maybe_save/maybe_restore unavailable when new register allocator used Revision 1.47 2003/04/22 09:49:44 peter * do not load self when calling a non-inherited class constructor Revision 1.46 2003/04/21 20:03:32 peter * forgot to copy vmtrefaddr to selfrefaddr when self=vmt Revision 1.45 2003/04/21 13:53:16 jonas - removed copying of all paras when secondpassing a callnode (this used to be necessary for inlinign support, but currently the whole inlined procedure is already copied in advance). Note that the compiler crashes when compiling ucomplex with -dTEST_INLINE (also after fixing the syntax errors), but that was also the case before this change. Revision 1.44 2003/04/10 17:57:52 peter * vs_hidden released Revision 1.43 2003/04/06 21:11:23 olle * changed newasmsymbol to newasmsymboldata for data symbols Revision 1.42 2003/04/04 15:38:56 peter * moved generic code from n386cal to ncgcal, i386 now also uses the generic ncgcal Revision 1.41 2003/03/28 19:16:56 peter * generic constructor working for i386 * remove fixed self register * esi added as address register for i386 Revision 1.40 2003/03/06 11:35:50 daniel * Fixed internalerror 7843 issue Revision 1.39 2003/02/19 22:00:14 daniel * Code generator converted to new register notation - Horribily outdated todo.txt removed Revision 1.38 2003/02/15 22:17:38 carl * bugfix of FPU emulation code Revision 1.37 2003/02/12 22:10:07 carl * load_frame_pointer is now generic * change fpu emulation routine names Revision 1.36 2003/01/30 21:46:57 peter * self fixes for static methods (merged) Revision 1.35 2003/01/22 20:45:15 mazen * making math code in RTL compiling. *NB : This does NOT mean necessary that it will generate correct code! Revision 1.34 2003/01/17 12:03:45 daniel * Optalign conditional code adapted to record Tregister Revision 1.33 2003/01/08 18:43:56 daniel * Tregister changed into a record Revision 1.32 2002/12/15 22:50:00 florian + some stuff for the new hidden parameter handling added Revision 1.31 2002/12/15 21:30:12 florian * tcallnode.paraitem introduced, all references to defcoll removed Revision 1.30 2002/11/27 20:04:39 peter * cdecl array of const fixes Revision 1.29 2002/11/25 17:43:17 peter * splitted defbase in defutil,symutil,defcmp * merged isconvertable and is_equal into compare_defs(_ext) * made operator search faster by walking the list only once Revision 1.28 2002/11/18 17:31:54 peter * pass proccalloption to ret_in_xxx and push_xxx functions Revision 1.27 2002/11/16 15:34:30 florian * generic location for float results Revision 1.26 2002/11/15 01:58:51 peter * merged changes from 1.0.7 up to 04-11 - -V option for generating bug report tracing - more tracing for option parsing - errors for cdecl and high() - win32 import stabs - win32 records<=8 are returned in eax:edx (turned off by default) - heaptrc update - more info for temp management in .s file with EXTDEBUG Revision 1.25 2002/10/05 12:43:25 carl * fixes for Delphi 6 compilation (warning : Some features do not work under Delphi) Revision 1.24 2002/09/30 07:00:45 florian * fixes to common code to get the alpha compiler compiled applied Revision 1.23 2002/09/17 18:54:02 jonas * a_load_reg_reg() now has two size parameters: source and dest. This allows some optimizations on architectures that don't encode the register size in the register name. Revision 1.22 2002/09/07 15:25:02 peter * old logs removed and tabs fixed Revision 1.21 2002/09/07 11:50:02 jonas * fixed small regalloction info bug Revision 1.20 2002/09/02 11:25:20 florian * fixed generic procedure variable calling Revision 1.19 2002/09/01 21:04:48 florian * several powerpc related stuff fixed Revision 1.18 2002/09/01 18:43:27 peter * include FUNCTION_RETURN_REG in regs_to_push list Revision 1.17 2002/09/01 12:13:00 peter * use a_call_reg * ungetiftemp for procvar of object temp Revision 1.16 2002/08/25 19:25:18 peter * sym.insert_in_data removed * symtable.insertvardata/insertconstdata added * removed insert_in_data call from symtable.insert, it needs to be called separatly. This allows to deref the address calculation * procedures now calculate the parast addresses after the procedure directives are parsed. This fixes the cdecl parast problem * push_addr_param has an extra argument that specifies if cdecl is used or not Revision 1.15 2002/08/23 16:14:48 peter * tempgen cleanup * tt_noreuse temp type added that will be used in genentrycode Revision 1.14 2002/08/20 16:55:38 peter * don't write (stabs)line info when inlining a procedure Revision 1.13 2002/08/19 19:36:42 peter * More fixes for cross unit inlining, all tnodes are now implemented * Moved pocall_internconst to po_internconst because it is not a calling type at all and it conflicted when inlining of these small functions was requested Revision 1.12 2002/08/18 20:06:23 peter * inlining is now also allowed in interface * renamed write/load to ppuwrite/ppuload * tnode storing in ppu * nld,ncon,nbas are already updated for storing in ppu Revision 1.11 2002/08/17 22:09:44 florian * result type handling in tcgcal.pass_2 overhauled * better tnode.dowrite * some ppc stuff fixed Revision 1.10 2002/08/17 09:23:35 florian * first part of procinfo rewrite Revision 1.9 2002/08/13 21:40:55 florian * more fixes for ppc calling conventions Revision 1.8 2002/08/13 18:01:51 carl * rename swatoperands to swapoperands + m68k first compilable version (still needs a lot of testing): assembler generator, system information , inline assembler reader. Revision 1.7 2002/08/12 15:08:39 carl + stab register indexes for powerpc (moved from gdb to cpubase) + tprocessor enumeration moved to cpuinfo + linker in target_info is now a class * many many updates for m68k (will soon start to compile) - removed some ifdef or correct them for correct cpu Revision 1.6 2002/08/11 14:32:26 peter * renamed current_library to objectlibrary Revision 1.5 2002/08/11 13:24:11 peter * saving of asmsymbols in ppu supported * asmsymbollist global is removed and moved into a new class tasmlibrarydata that will hold the info of a .a file which corresponds with a single module. Added librarydata to tmodule to keep the library info stored for the module. In the future the objectfiles will also be stored to the tasmlibrarydata class * all getlabel/newasmsymbol and friends are moved to the new class Revision 1.4 2002/08/06 20:55:20 florian * first part of ppc calling conventions fix Revision 1.3 2002/07/20 11:57:53 florian * types.pas renamed to defbase.pas because D6 contains a types unit so this would conflicts if D6 programms are compiled + Willamette/SSE2 instructions to assembler added Revision 1.2 2002/07/13 19:38:43 florian * some more generic calling stuff fixed }