123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613 |
- {
- $Id$
- Copyright (c) 1998-2002 by Florian Klaempfl
- Generate generic mathematical 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 ncgmat;
- {$i fpcdefs.inc}
- interface
- uses
- node,nmat,cpubase,cgbase;
- type
- tcgunaryminusnode = class(tunaryminusnode)
- protected
- { This routine is called to change the sign of the
- floating point value in the floating point
- register r.
- This routine should be overriden, since
- the generic version is not optimal at all. The
- generic version assumes that floating
- point values are stored in the register
- in IEEE-754 format.
- }
- procedure emit_float_sign_change(r: tregister; _size : tcgsize);virtual;
- {$ifdef SUPPORT_MMX}
- procedure second_mmx;virtual;abstract;
- {$endif SUPPORT_MMX}
- procedure second_64bit;virtual;
- procedure second_integer;virtual;
- procedure second_float;virtual;
- public
- procedure pass_2;override;
- end;
- tcgmoddivnode = class(tmoddivnode)
- procedure pass_2;override;
- protected
- { This routine must do an actual 32-bit division, be it
- signed or unsigned. The result must set into the the
- @var(num) register.
- @param(signed Indicates if the division must be signed)
- @param(denum Register containing the denominator
- @param(num Register containing the numerator, will also receive result)
- The actual optimizations regarding shifts have already
- been done and emitted, so this should really a do a divide.
- }
- procedure emit_div_reg_reg(signed: boolean;denum,num : tregister);virtual;abstract;
- { This routine must do an actual 32-bit modulo, be it
- signed or unsigned. The result must set into the the
- @var(num) register.
- @param(signed Indicates if the modulo must be signed)
- @param(denum Register containing the denominator
- @param(num Register containing the numerator, will also receive result)
- The actual optimizations regarding shifts have already
- been done and emitted, so this should really a do a modulo.
- }
- procedure emit_mod_reg_reg(signed: boolean;denum,num : tregister);virtual;abstract;
- { This routine must do an actual 64-bit division, be it
- signed or unsigned. The result must set into the the
- @var(num) register.
- @param(signed Indicates if the division must be signed)
- @param(denum Register containing the denominator
- @param(num Register containing the numerator, will also receive result)
- The actual optimizations regarding shifts have already
- been done and emitted, so this should really a do a divide.
- Currently, this routine should only be implemented on
- 64-bit systems, otherwise a helper is called in 1st pass.
- }
- procedure emit64_div_reg_reg(signed: boolean;denum,num : tregister64);virtual;
- end;
- tcgshlshrnode = class(tshlshrnode)
- procedure second_64bit;virtual;
- procedure second_integer;virtual;
- procedure pass_2;override;
- end;
- tcgnotnode = class(tnotnode)
- protected
- procedure second_boolean;virtual;abstract;
- {$ifdef SUPPORT_MMX}
- procedure second_mmx;virtual;abstract;
- {$endif SUPPORT_MMX}
- procedure second_64bit;virtual;
- procedure second_integer;virtual;
- public
- procedure pass_2;override;
- end;
- implementation
- uses
- globtype,systems,
- cutils,verbose,globals,
- symconst,symdef,aasmbase,aasmtai,aasmcpu,defutil,
- pass_1,pass_2,
- ncon,
- cpuinfo,
- tgobj,ncgutil,cgobj,paramgr,cg64f32;
- {*****************************************************************************
- TCGUNARYMINUSNODE
- *****************************************************************************}
- procedure tcgunaryminusnode.emit_float_sign_change(r: tregister; _size : tcgsize);
- var
- href : treference;
- hreg : tregister;
- begin
- { get a temporary memory reference to store the floating
- point value
- }
- tg.gettemp(exprasmlist,tcgsize2size[_size],tt_normal,href);
- { store the floating point value in the temporary memory area }
- cg.a_loadfpu_reg_ref(exprasmlist,_size,r,href);
- { only single and double ieee are supported }
- if _size = OS_F64 then
- begin
- { on little-endian machine the most significant
- 32-bit value is stored at the highest address
- }
- if target_info.endian = endian_little then
- inc(href.offset,4);
- end
- else
- if _size <> OS_F32 then
- internalerror(20020814);
- hreg := cg.getintregister(exprasmlist,OS_32);
- { load value }
- cg.a_load_ref_reg(exprasmlist,OS_32,OS_32,href,hreg);
- { bitwise complement copied value }
- cg.a_op_reg_reg(exprasmlist,OP_NOT,OS_32,hreg,hreg);
- { sign-bit is bit 31/63 of single/double }
- cg.a_op_const_reg(exprasmlist,OP_AND,OS_32,aword($80000000),hreg);
- { or with value in reference memory }
- cg.a_op_reg_ref(exprasmlist,OP_OR,OS_32,hreg,href);
- cg.ungetregister(exprasmlist,hreg);
- { store the floating point value in the temporary memory area }
- if _size = OS_F64 then
- begin
- { on little-endian machine the most significant
- 32-bit value is stored at the highest address
- }
- if target_info.endian = endian_little then
- dec(href.offset,4);
- end;
- cg.a_loadfpu_ref_reg(exprasmlist,_size,href,r);
- end;
- procedure tcgunaryminusnode.second_64bit;
- begin
- secondpass(left);
- { load left operator in a register }
- location_copy(location,left.location);
- location_force_reg(exprasmlist,location,OS_64,false);
- cg64.a_op64_loc_reg(exprasmlist,OP_NEG,
- location,joinreg64(location.registerlow,location.registerhigh));
- end;
- procedure tcgunaryminusnode.second_float;
- begin
- secondpass(left);
- location_reset(location,LOC_FPUREGISTER,def_cgsize(resulttype.def));
- case left.location.loc of
- LOC_REFERENCE,
- LOC_CREFERENCE :
- begin
- reference_release(exprasmlist,left.location.reference);
- location.register:=cg.getfpuregister(exprasmlist,location.size);
- cg.a_loadfpu_ref_reg(exprasmlist,
- def_cgsize(left.resulttype.def),
- left.location.reference,location.register);
- emit_float_sign_change(location.register,def_cgsize(left.resulttype.def));
- end;
- LOC_FPUREGISTER:
- begin
- location.register:=left.location.register;
- emit_float_sign_change(location.register,def_cgsize(left.resulttype.def));
- end;
- LOC_CFPUREGISTER:
- begin
- location.register:=cg.getfpuregister(exprasmlist,location.size);
- cg.a_loadfpu_reg_reg(exprasmlist,left.location.size,left.location.register,location.register);
- emit_float_sign_change(location.register,def_cgsize(left.resulttype.def));
- end;
- else
- internalerror(200306021);
- end;
- end;
- procedure tcgunaryminusnode.second_integer;
- begin
- secondpass(left);
- { load left operator in a register }
- location_copy(location,left.location);
- location_force_reg(exprasmlist,location,OS_INT,false);
- cg.a_op_reg_reg(exprasmlist,OP_NEG,OS_INT,location.register,location.register);
- end;
- procedure tcgunaryminusnode.pass_2;
- begin
- if is_64bit(left.resulttype.def) then
- second_64bit
- {$ifdef SUPPORT_MMX}
- else
- if (cs_mmx in aktlocalswitches) and is_mmx_able_array(left.resulttype.def) then
- second_mmx
- {$endif SUPPORT_MMX}
- else
- if (left.resulttype.def.deftype=floatdef) then
- second_float
- else
- second_integer;
- end;
- {*****************************************************************************
- TCGMODDIVNODE
- *****************************************************************************}
- procedure tcgmoddivnode.emit64_div_reg_reg(signed: boolean; denum,num:tregister64);
- begin
- { handled in pass_1 already, unless pass_1 is
- overriden
- }
- { should be handled in pass_1 (JM) }
- internalerror(200109052);
- end;
- procedure tcgmoddivnode.pass_2;
- var
- hreg1 : tregister;
- hdenom : tregister;
- power : longint;
- hl : tasmlabel;
- paraloc1 : tparalocation;
- begin
- secondpass(left);
- if codegenerror then
- exit;
- secondpass(right);
- if codegenerror then
- exit;
- location_copy(location,left.location);
- if is_64bit(resulttype.def) then
- begin
- { this code valid for 64-bit cpu's only ,
- otherwise helpers are called in pass_1
- }
- location_force_reg(exprasmlist,location,OS_64,false);
- location_copy(location,left.location);
- location_force_reg(exprasmlist,right.location,OS_64,false);
- emit64_div_reg_reg(is_signed(left.resulttype.def),
- joinreg64(right.location.registerlow,right.location.registerhigh),
- joinreg64(location.registerlow,location.registerhigh));
- end
- else
- begin
- { put numerator in register }
- location_force_reg(exprasmlist,left.location,OS_INT,false);
- hreg1:=left.location.register;
- if (nodetype=divn) and
- (right.nodetype=ordconstn) and
- ispowerof2(tordconstnode(right).value,power) then
- Begin
- { for signed numbers, the numerator must be adjusted before the
- shift instruction, but not wih unsigned numbers! Otherwise,
- "Cardinal($ffffffff) div 16" overflows! (JM) }
- If is_signed(left.resulttype.def) Then
- Begin
- objectlibrary.getlabel(hl);
- cg.a_cmp_const_reg_label(exprasmlist,OS_INT,OC_GT,0,hreg1,hl);
- if power=1 then
- cg.a_op_const_reg(exprasmlist,OP_ADD,OS_INT,1,hreg1)
- else
- cg.a_op_const_reg(exprasmlist,OP_ADD,OS_INT,tordconstnode(right).value-1,hreg1);
- cg.a_label(exprasmlist,hl);
- cg.a_op_const_reg(exprasmlist,OP_SAR,OS_INT,power,hreg1);
- End
- Else { not signed }
- cg.a_op_const_reg(exprasmlist,OP_SHR,OS_INT,power,hreg1);
- End
- else
- begin
- { bring denominator to hdenom }
- { hdenom is always free, it's }
- { only used for temporary }
- { purposes }
- hdenom := cg.getintregister(exprasmlist,OS_INT);
- if right.location.loc<>LOC_CREGISTER then
- location_release(exprasmlist,right.location);
- cg.a_load_loc_reg(exprasmlist,right.location.size,right.location,hdenom);
- { verify if the divisor is zero, if so return an error
- immediately
- }
- objectlibrary.getlabel(hl);
- cg.a_cmp_const_reg_label(exprasmlist,OS_INT,OC_NE,0,hdenom,hl);
- paraloc1:=paramanager.getintparaloc(pocall_default,1);
- paramanager.allocparaloc(exprasmlist,paraloc1);
- cg.a_param_const(exprasmlist,OS_S32,200,paraloc1);
- paramanager.freeparaloc(exprasmlist,paraloc1);
- cg.a_call_name(exprasmlist,'FPC_HANDLERROR');
- cg.a_label(exprasmlist,hl);
- if nodetype = modn then
- emit_mod_reg_reg(is_signed(left.resulttype.def),hdenom,hreg1)
- else
- emit_div_reg_reg(is_signed(left.resulttype.def),hdenom,hreg1);
- end;
- location_reset(location,LOC_REGISTER,OS_INT);
- location.register:=hreg1;
- end;
- cg.g_overflowcheck(exprasmlist,location,resulttype.def);
- end;
- {*****************************************************************************
- TCGSHLRSHRNODE
- *****************************************************************************}
- procedure tcgshlshrnode.second_64bit;
- var
- freescratch : boolean;
- op : topcg;
- begin
- {$ifdef cpu64bit}
- freescratch:=false;
- secondpass(left);
- secondpass(right);
- { determine operator }
- case nodetype of
- shln: op:=OP_SHL;
- shrn: op:=OP_SHR;
- end;
- freescratch:=false;
- location_reset(location,LOC_REGISTER,OS_64);
- { load left operator in a register }
- location_force_reg(exprasmlist,left.location,OS_64,false);
- location_copy(location,left.location);
- if (right.nodetype=ordconstn) then
- begin
- cg64.a_op64_const_reg(exprasmlist,op,tordconstnode(right).value,
- joinreg64(location.registerlow,location.registerhigh));
- end
- else
- begin
- { this should be handled in pass_1 }
- internalerror(2002081501);
- end;
- {$else cpu64bit}
- { already hanled in 1st pass }
- internalerror(2002081501);
- {$endif cpu64bit}
- end;
- procedure tcgshlshrnode.second_integer;
- var
- freescratch : boolean;
- op : topcg;
- hcountreg : tregister;
- begin
- freescratch:=false;
- { determine operator }
- case nodetype of
- shln: op:=OP_SHL;
- shrn: op:=OP_SHR;
- end;
- { load left operators in a register }
- location_copy(location,left.location);
- location_force_reg(exprasmlist,location,OS_INT,false);
- { shifting by a constant directly coded: }
- if (right.nodetype=ordconstn) then
- begin
- { l shl 32 should 0 imho, but neither TP nor Delphi do it in this way (FK)
- if right.value<=31 then
- }
- cg.a_op_const_reg(exprasmlist,op,location.size,
- tordconstnode(right).value and 31,location.register);
- {
- else
- emit_reg_reg(A_XOR,S_L,hregister1,
- hregister1);
- }
- end
- else
- begin
- { load right operators in a register - this
- is done since most target cpu which will use this
- node do not support a shift count in a mem. location (cec)
- }
- if right.location.loc<>LOC_REGISTER then
- begin
- if right.location.loc<>LOC_CREGISTER then
- location_release(exprasmlist,right.location);
- hcountreg:=cg.getintregister(exprasmlist,OS_INT);
- freescratch := true;
- cg.a_load_loc_reg(exprasmlist,right.location.size,right.location,hcountreg);
- end
- else
- hcountreg:=right.location.register;
- cg.a_op_reg_reg(exprasmlist,op,OS_INT,hcountreg,location.register);
- if freescratch then
- cg.ungetregister(exprasmlist,hcountreg);
- end;
- end;
- procedure tcgshlshrnode.pass_2;
- begin
- secondpass(left);
- secondpass(right);
- if is_64bit(left.resulttype.def) then
- second_64bit
- else
- second_integer;
- end;
- {*****************************************************************************
- TCGNOTNODE
- *****************************************************************************}
- procedure tcgnotnode.second_64bit;
- begin
- secondpass(left);
- location_force_reg(exprasmlist,left.location,def_cgsize(left.resulttype.def),false);
- location_copy(location,left.location);
- { perform the NOT operation }
- cg64.a_op64_reg_reg(exprasmlist,OP_NOT,left.location.register64,location.register64);
- end;
- procedure tcgnotnode.second_integer;
- begin
- secondpass(left);
- location_force_reg(exprasmlist,left.location,def_cgsize(left.resulttype.def),false);
- location_copy(location,left.location);
- { perform the NOT operation }
- cg.a_op_reg_reg(exprasmlist,OP_NOT,location.size,location.register,location.register);
- end;
- procedure tcgnotnode.pass_2;
- begin
- if is_boolean(resulttype.def) then
- second_boolean
- {$ifdef SUPPORT_MMX}
- else if (cs_mmx in aktlocalswitches) and is_mmx_able_array(left.resulttype.def) then
- second_mmx
- {$endif SUPPORT_MMX}
- else if is_64bit(left.resulttype.def) then
- second_64bit
- else
- second_integer;
- end;
- begin
- cmoddivnode:=tcgmoddivnode;
- cunaryminusnode:=tcgunaryminusnode;
- cshlshrnode:=tcgshlshrnode;
- cnotnode:=tcgnotnode;
- end.
- {
- $Log$
- Revision 1.21 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.20 2003/10/09 21:31:37 daniel
- * Register allocator splitted, ans abstract now
- Revision 1.19 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.18 2003/09/10 08:31:47 marco
- * Patch from Peter for paraloc
- Revision 1.17 2003/09/03 15:55:00 peter
- * NEWRA branch merged
- Revision 1.16 2003/09/03 11:18:37 florian
- * fixed arm concatcopy
- + arm support in the common compiler sources added
- * moved some generic cg code around
- + tfputype added
- * ...
- Revision 1.15.2.2 2003/08/31 15:46:26 peter
- * more updates for tregister
- Revision 1.15.2.1 2003/08/31 13:50:15 daniel
- * Remove sorting and use pregenerated indexes
- * Some work on making things compile
- Revision 1.15 2003/07/02 22:18:04 peter
- * paraloc splitted in callerparaloc,calleeparaloc
- * sparc calling convention updates
- Revision 1.14 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.13 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.12 2003/06/01 21:38:06 peter
- * getregisterfpu size parameter added
- * op_const_reg size parameter added
- * sparc updates
- Revision 1.11 2003/05/30 23:49:18 jonas
- * a_load_loc_reg now has an extra size parameter for the destination
- register (properly fixes what I worked around in revision 1.106 of
- ncgutil.pas)
- Revision 1.10 2003/05/23 14:27:35 peter
- * remove some unit dependencies
- * current_procinfo changes to store more info
- Revision 1.9 2003/04/23 20:16:04 peter
- + added currency support based on int64
- + is_64bit for use in cg units instead of is_64bitint
- * removed cgmessage from n386add, replace with internalerrors
- Revision 1.8 2003/04/22 10:09:35 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.7 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.6 2003/02/19 22:00:14 daniel
- * Code generator converted to new register notation
- - Horribily outdated todo.txt removed
- Revision 1.5 2002/11/25 17:43:18 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.4 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.3 2002/08/23 16:14:48 peter
- * tempgen cleanup
- * tt_noreuse temp type added that will be used in genentrycode
- Revision 1.2 2002/08/15 15:15:55 carl
- * jmpbuf size allocation for exceptions is now cpu specific (as it should)
- * more generic nodes for maths
- * several fixes for better m68k support
- Revision 1.1 2002/08/14 19:26:55 carl
- + generic int_to_real type conversion
- + generic unaryminus node
- }
|