+ searchsystype() and searchsystype() functions in symtable

* changed ninl and nadd to use these functions
  * i386 set comparison functions now return their results in al instead
    of in the flags so that they can be sued as compilerprocs
  - removed all processor specific code from n386add.pas that has to do
    with set handling, it's now all done in nadd.pas
  * fixed fpc_set_contains_sets in genset.inc
  * fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
    helper anymore
  * some small fixes in compproc.inc/set.inc regarding the declaration of
    internal helper types (fpc_small_set and fpc_normal_set)
This commit is contained in:
Jonas Maebe 2001-09-04 11:38:54 +00:00
parent a28c6b5d6a
commit ed449defca
8 changed files with 216 additions and 199 deletions

View File

@ -36,10 +36,8 @@ interface
procedure SetResultLocation(cmpop,unsigned : boolean);
protected
function first_addstring : tnode; override;
function first_addset : tnode; override;
private
procedure second_addstring;
procedure second_addset;
end;
implementation
@ -254,94 +252,6 @@ interface
end;
{*****************************************************************************
Addset
*****************************************************************************}
{ we have to disable the compilerproc handling for all set helpers that }
{ return booleans, because they return their results in the flags }
function ti386addnode.first_addset : tnode;
begin
if is_boolean(resulttype.def) then
begin
result := nil;
exit;
end;
result := inherited first_addset;
end;
procedure ti386addnode.second_addset;
var
cmpop,
pushed : boolean;
href : treference;
pushedregs : tpushed;
regstopush: byte;
begin
cmpop:=false;
{ not commutative }
if nf_swaped in flags then
swapleftright;
secondpass(left);
{ are too few registers free? }
pushed:=maybe_push(right.registers32,left,false);
secondpass(right);
if codegenerror then
exit;
if pushed then
restore(left,false);
set_location(location,left.location);
{ handle operations }
{ (the rest is handled by compilerprocs in pass 1) (JM) }
case nodetype of
equaln,
unequaln
,lten, gten :
begin
cmpop:=true;
del_location(left.location);
del_location(right.location);
pushusedregisters(pushedregs,$ff);
If (nodetype in [equaln, unequaln, lten]) Then
Begin
emitpushreferenceaddr(right.location.reference);
emitpushreferenceaddr(left.location.reference);
End
Else {gten = lten, if the arguments are reversed}
Begin
emitpushreferenceaddr(left.location.reference);
emitpushreferenceaddr(right.location.reference);
End;
saveregvars($ff);
Case nodetype of
equaln, unequaln:
emitcall('FPC_SET_COMP_SETS');
lten, gten:
Begin
emitcall('FPC_SET_CONTAINS_SETS');
{ we need a jne afterwards, not a jnbe/jnae }
nodetype := equaln;
End;
End;
maybe_loadself;
popusedregisters(pushedregs);
ungetiftemp(left.location.reference);
ungetiftemp(right.location.reference);
end;
else
internalerror(200108314);
end;
SetResultLocation(cmpop,true);
end;
{*****************************************************************************
pass_2
*****************************************************************************}
@ -458,8 +368,8 @@ interface
{ normalsets are handled separate }
if not(tsetdef(left.resulttype.def).settype=smallset) then
begin
second_addset;
exit;
{ should be handled in pass 1 (JM) }
internalerror(200109041);
end;
end;
end;
@ -1980,7 +1890,20 @@ begin
end.
{
$Log$
Revision 1.21 2001-09-03 13:27:42 jonas
Revision 1.22 2001-09-04 11:38:55 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.21 2001/09/03 13:27:42 jonas
* compilerproc implementation of set addition/substraction/...
* changed the declaration of some set helpers somewhat to accomodate the
above change

View File

@ -509,13 +509,32 @@ implementation
end
else
begin
pushsetelement(left);
emitpushreferenceaddr(right.location.reference);
if not(left.location.loc in [LOC_REGISTER,LOC_CREGISTER]) then
begin
pleftreg := getexplicitregister32(R_EDI);
opsize := def2def_opsize(left.resulttype.def,u32bittype.def);
if opsize = S_L then
emit_ref_reg(A_MOV,opsize,newreference(left.location.reference),pleftreg)
else
emit_ref_reg(A_MOVZX,opsize,newreference(left.location.reference),pleftreg);
ungetiftemp(left.location.reference);
del_reference(left.location.reference);
end
else
begin
pleftreg := left.location.register;
opsize := def2def_opsize(left.resulttype.def,u32bittype.def);
if opsize <> S_L then
{ this will change left, even if it's a LOC_CREGISTER, but }
{ that doesn't matter: if left is an 8 bit def, then the }
{ upper 24 bits are undefined, so we can zero them without }
{ any problem (JM) }
emit_to_reg32(pleftreg)
end;
emit_reg_ref(A_BT,S_L,pleftreg,newreference(right.location.reference));
ungetregister(pleftreg);
del_reference(right.location.reference);
{ registers need not be save. that happens in SET_IN_BYTE }
{ (EDI is changed) }
emitcall('FPC_SET_IN_BYTE');
{ ungetiftemp(right.location.reference); }
{ ungetiftemp(right.location.reference) happens below }
location.loc:=LOC_FLAGS;
location.resflags:=F_C;
end;
@ -1072,7 +1091,20 @@ begin
end.
{
$Log$
Revision 1.16 2001-08-26 13:37:00 florian
Revision 1.17 2001-09-04 11:38:55 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.16 2001/08/26 13:37:00 florian
* some cg reorganisation
* some PPC updates

View File

@ -1117,16 +1117,10 @@ implementation
tempn: tnode;
paras: tcallparanode;
srsym: ttypesym;
symowner: tsymtable;
createset: boolean;
begin
{ get the sym that represents the fpc_normal_set type }
if not(cs_compilesystem in aktmoduleswitches) then
srsym := ttypesym(searchsymonlyin(systemunit,'FPC_NORMAL_SET'))
else
searchsym('FPC_NORMAL_SET',tsym(srsym),symowner);
if not assigned(srsym) or
(srsym.typ <> typesym) then
if not searchsystype('FPC_NORMAL_SET',srsym) then
internalerror(200108313);
case nodetype of
@ -1137,7 +1131,7 @@ implementation
procname := 'fpc_set_comp_sets';
lten,gten:
begin
procname := 'fpc_set_contains_set';
procname := 'fpc_set_contains_sets';
{ (left >= right) = (right <= left) }
if nodetype = gten then
begin
@ -1149,7 +1143,9 @@ implementation
end;
{ convert the arguments (explicitely) to fpc_normal_set's }
left := ctypeconvnode.create(left,srsym.restype);
left.toggleflag(nf_explizit);
right := ctypeconvnode.create(right,srsym.restype);
right.toggleflag(nf_explizit);
result := ccallnode.createintern(procname,ccallparanode.create(right,
ccallparanode.create(left,nil)));
{ left and right are reused as parameters }
@ -1189,12 +1185,12 @@ implementation
ctypeconvnode.create(tsetelementnode(right).left,
u8bittype);
tsetelementnode(right).left.toggleflag(nf_explizit);
{ convert the original set (explicitely) to an }
{ fpc_normal_set so we can pass it to the helper }
left := ctypeconvnode.create(left,srsym.restype);
left.toggleflag(nf_explizit);
{ add a range or a single element? }
if assigned(tsetelementnode(right).right) then
begin
@ -1202,7 +1198,7 @@ implementation
ctypeconvnode.create(tsetelementnode(right).right,
u8bittype);
tsetelementnode(right).right.toggleflag(nf_explizit);
{ create the call }
result := ccallnode.createinternres('fpc_set_set_range',
ccallparanode.create(tsetelementnode(right).right,
@ -1223,7 +1219,7 @@ implementation
else
begin
{ add two sets }
{ convert the sets to fpc_normal_set's }
left := ctypeconvnode.create(left,srsym.restype);
left.toggleflag(nf_explizit);
@ -1531,7 +1527,20 @@ begin
end.
{
$Log$
Revision 1.37 2001-09-03 13:27:42 jonas
Revision 1.38 2001-09-04 11:38:54 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.37 2001/09/03 13:27:42 jonas
* compilerproc implementation of set addition/substraction/...
* changed the declaration of some set helpers somewhat to accomodate the
above change

View File

@ -272,7 +272,7 @@ implementation
tempref : ttemprefnode;
procprefix,
name : string[31];
srsym : tsym;
srsym : tvarsym;
tempowner : tsymtable;
restype : ^ttype;
is_typed,
@ -344,15 +344,7 @@ implementation
{ however, if we aren't compiling the system unit, another unit could }
{ also have defined the INPUT or OUTPUT symbols. Therefore we need the }
{ separate cases (JM) }
if not (cs_compilesystem in aktmoduleswitches) then
begin
srsym := searchsymonlyin(systemunit,name);
tempowner := systemunit;
end
else
searchsym(name,srsym,tempowner);
if not assigned(srsym) then
if not searchsysvar(name,srsym,tempowner) then
internalerror(200108141);
{ create the file parameter }
@ -2277,7 +2269,20 @@ begin
end.
{
$Log$
Revision 1.55 2001-09-02 21:12:07 peter
Revision 1.56 2001-09-04 11:38:55 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.55 2001/09/02 21:12:07 peter
* move class of definitions into type section for delphi
Revision 1.54 2001/08/28 13:24:46 jonas

View File

@ -215,6 +215,8 @@ interface
{*** Search ***}
function searchsym(const s : stringid;var srsym:tsym;var srsymtable:tsymtable):boolean;
function searchsymonlyin(p : tsymtable;const s : stringid):tsym;
function searchsystype(const s: stringid; var srsym: ttypesym): boolean;
function searchsysvar(const s: stringid; var srsym: tvarsym; var symowner: tsymtable): boolean;
function search_class_member(pd : tobjectdef;const s : string):tsym;
{*** Object Helpers ***}
@ -1827,6 +1829,35 @@ implementation
end;
function searchsystype(const s: stringid; var srsym: ttypesym): boolean;
var
symowner: tsymtable;
begin
if not(cs_compilesystem in aktmoduleswitches) then
srsym := ttypesym(searchsymonlyin(systemunit,s))
else
searchsym(s,srsym,symowner);
searchsystype :=
assigned(srsym) and
(srsym.typ = typesym);
end;
function searchsysvar(const s: stringid; var srsym: tvarsym; var symowner: tsymtable): boolean;
begin
if not(cs_compilesystem in aktmoduleswitches) then
begin
srsym := tvarsym(searchsymonlyin(systemunit,s));
symowner := systemunit;
end
else
searchsym(s,srsym,symowner);
searchsysvar :=
assigned(srsym) and
(srsym.typ = varsym);
end;
function search_class_member(pd : tobjectdef;const s : string):tsym;
{ searches n in symtable of pd and all anchestors }
var
@ -2072,7 +2103,20 @@ implementation
end.
{
$Log$
Revision 1.43 2001-08-30 20:13:56 peter
Revision 1.44 2001-09-04 11:38:55 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.43 2001/08/30 20:13:56 peter
* rtti/init table updates
* rttisym for reusable global rtti/init info
* support published for interfaces

View File

@ -14,11 +14,6 @@
**********************************************************************}
{$ifndef hascompilerproc}
type
fpc_small_set = set of 0..31;
fpc_normal_set = set of byte;
{$endif hascompilerproc}
{$define FPC_SYSTEM_HAS_FPC_SET_LOAD_SMALL}
function fpc_set_load_small(l: fpc_small_set): fpc_normal_set;assembler;[public,alias:'FPC_SET_LOAD_SMALL']; {$ifdef hascompilerproc} compilerproc; {$endif}
@ -52,16 +47,10 @@ asm
movl $8,%ecx
rep
stosl
movb b,%al
movl __RESULT,%edi
movl %eax,%ecx
shrl $3,%eax
andl $7,%ecx
addl %eax,%edi
btsl %ecx,(%edi)
{$ifdef hascompilerproc}
movl __RESULT,%edi
{$else hascompilerproc}
leal -32(%edi),%eax
movzbl b,%edi
btsl %edi,(%eax)
{$ifndef hascompilerproc}
popl %ecx
popl %eax
{$endif hascompilerproc}
@ -78,17 +67,12 @@ asm
movl $8,%ecx
movl source,%esi
movl __RESULT,%edi
movb b,%al
rep
movsl
andl $0xf8,%eax
subl $32,%edi
shrl $3,%eax
addl %eax,%edi
movb b,%al
andl $7,%eax
btsl %eax,(%edi)
end ['EAX','ECX','EDI'];
leal -32(%edi),%eax
movzbl b,%edi
btsl %edi,(%eax)
end ['EAX','ECX','ESI','EDI'];
{$else hascompilerproc}
function fpc_set_set_byte(b : byte): fpc_normal_set;assembler;[public,alias:'FPC_SET_SET_BYTE'];
{
@ -119,17 +103,12 @@ asm
movl $8,%ecx
movl source,%esi
movl __RESULT,%edi
movb b,%al
rep
movsl
andl $0xf8,%eax
subl $32,%edi
shrl $3,%eax
addl %eax,%edi
movb b,%al
andl $7,%eax
btrl %eax,(%edi)
end ['EAX','ECX','EDI'];
leal -32(%edi),%eax
movzbl b,%edi
btrl %edi,(%eax)
end ['EAX','ECX','ESI','EDI'];
{$else hascompilerproc}
function fpc_set_unset_byte(b : byte): fpc_normal_set;assembler;[public,alias:'FPC_SET_UNSET_BYTE']; {$ifdef hascompilerproc} compilerproc; {$endif}
{
@ -249,13 +228,14 @@ asm
end;
{$endif hascompilerproc}
{$define FPC_SYSTEM_HAS_FPC_SET_IN_BYTE}
{$ifdef hascompilerproc}
{ can't use as compilerproc, it returns its results in the flags :/ }
{ it's inlined in the code generator }
function fpc_set_in_byte(const p: fpc_normal_set; b: byte): boolean; compilerproc;
begin
fpc_set_in_byte := false;
{ make sure we won't accidentally call it }
runerror(216);
end;
@ -266,16 +246,14 @@ function fpc_set_in_byte_i386(p: pointer; b : byte): boolean;assembler;[public,a
tests if the element b is in the set p the carryflag is set if it present
}
asm
{ it's inlined in the code generator }
{$ifndef hascompilerproc}
pushl %eax
movl p,%edi
movb b,%al
andl $0xf8,%eax
shrl $3,%eax
addl %eax,%edi
movb b,%al
andl $7,%eax
movl p,%edi
movzbl b,%eax
btl %eax,(%edi)
popl %eax
{$endif not hascompilerproc}
end;
@ -400,17 +378,7 @@ end;
{$define FPC_SYSTEM_HAS_FPC_SET_COMP_SETS}
{$ifdef hascompilerproc}
{ can't use as compilerproc, it returns its results in the flags :/ }
function fpc_set_comp_sets(const set1,set2: fpc_normal_set): boolean; compilerproc;
begin
fpc_set_comp_sets := false;
{ make sure we won't accidentally call it }
runerror(216);
end;
{$endif hascompilerproc}
procedure fpc_set_comp_sets_i386(set1,set2 : pointer);assembler;[public,alias:'FPC_SET_COMP_SETS'];
function fpc_set_comp_sets(const set1,set2: fpc_normal_set): boolean;assembler;[public,alias:'FPC_SET_COMP_SETS']; {$ifdef hascompilerproc} compilerproc; {$endif}
{
compares set1 and set2 zeroflag is set if they are equal
}
@ -430,22 +398,15 @@ asm
{ we are here only if the two sets are equal
we have zero flag set, and that what is expected }
.LMCOMPSETEND:
{$ifdef hascompilerproc}
seteb %al
{$endif hascompilerproc}
end;
{$define FPC_SYSTEM_HAS_FPC_SET_CONTAINS_SET}
{$ifdef hascompilerproc}
{ can't use as compilerproc, it returns its results in the flags :/ }
function fpc_set_contains_sets(const set1,set2: fpc_normal_set): boolean; compilerproc;
begin
fpc_set_contains_sets := false;
{ make sure we won't accidentally call it }
runerror(216);
end;
{$endif hascompilerproc}
procedure fpc_set_contains_sets_i386(set1,set2 : pointer);assembler;[public,alias:'FPC_SET_CONTAINS_SETS'];
function fpc_set_contains_sets(const set1,set2: fpc_normal_set): boolean;assembler;[public,alias:'FPC_SET_CONTAINS_SETS']; {$ifdef hascompilerproc} compilerproc; {$endif}
{
on exit, zero flag is set if set1 <= set2 (set2 contains set1)
}
@ -466,11 +427,15 @@ asm
{ we are here only if set2 contains set1
we have zero flag set, and that what is expected }
.LMCONTAINSSETEND:
{$ifdef hascompilerproc}
seteb %al
{$endif hascompilerproc}
end;
{$ifdef LARGESETS}
procedure fpc_largeset_set_wor(p : pointer;b : word);assembler;[public,alias:'FPC_LARGESET_SET_WORD']; {$ifdef hascompilerproc} compilerproc; {$endif}
procedure fpc_largeset_set_word(p : pointer;b : word);assembler;[public,alias:'FPC_LARGESET_SET_WORD']; {$ifdef hascompilerproc} compilerproc; {$endif}
{
sets the element b in set p works for sets larger than 256 elements
not yet use by the compiler so
@ -631,7 +596,20 @@ end;
{
$Log$
Revision 1.6 2001-09-03 13:27:43 jonas
Revision 1.7 2001-09-04 11:38:55 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.6 2001/09/03 13:27:43 jonas
* compilerproc implementation of set addition/substraction/...
* changed the declaration of some set helpers somewhat to accomodate the
above change

View File

@ -22,13 +22,13 @@
**********************************************************************}
{$ifdef hascompilerproc}
{ some dummy types necessary to have generic resulttypes for certain compilerprocs }
type
fpc_big_chararray = array[0..maxlongint] of char;
fpc_small_set = set of 0..31;
fpc_normal_set = set of byte;
fpc_small_set = longint;
fpc_normal_set = array[0..7] of longint;
{$ifdef hascompilerproc}
procedure fpc_Shortstr_SetLength(var s:shortstring;len:StrLenInt); compilerproc;
function fpc_shortstr_to_shortstr(len:longint; const sstr: shortstring): shortstring; compilerproc;
@ -240,7 +240,20 @@ Procedure fpc_typed_read(TypeSize : Longint;var f : TypedFile;var Buf); compiler
{
$Log$
Revision 1.8 2001-09-03 13:27:43 jonas
Revision 1.9 2001-09-04 11:38:55 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.8 2001/09/03 13:27:43 jonas
* compilerproc implementation of set addition/substraction/...
* changed the declaration of some set helpers somewhat to accomodate the
above change

View File

@ -162,6 +162,7 @@ procedure do_unset_byte(p : pointer;b : byte);[public,alias:'FPC_SET_UNSET_BYTE'
dest: fpc_normal_set absolute fpc_set_add_sets;
{$else hascompilerproc}
procedure do_add_sets(const set1,set2: fpc_normal_Set; var dest : fpc_normal_set);[public,alias:'FPC_SET_ADD_SETS'];
{$endif hascompilerproc}
{
adds set1 and set2 into set dest
}
@ -171,7 +172,6 @@ procedure do_unset_byte(p : pointer;b : byte);[public,alias:'FPC_SET_UNSET_BYTE'
for i:=0 to 7 do
dest[i] := set1[i] or set2[i];
end;
{$endif hascompilerproc}
{$endif}
@ -262,7 +262,7 @@ procedure do_unset_byte(p : pointer;b : byte);[public,alias:'FPC_SET_UNSET_BYTE'
begin
fpc_set_contains_sets:= false;
for i:=0 to 7 do
if (set2[i] and not set1[i]) <> 0 then
if (set1[i] and not set2[i]) <> 0 then
exit;
fpc_set_contains_sets:= true;
end;
@ -270,7 +270,20 @@ procedure do_unset_byte(p : pointer;b : byte);[public,alias:'FPC_SET_UNSET_BYTE'
{
$Log$
Revision 1.5 2001-09-03 13:27:43 jonas
Revision 1.6 2001-09-04 11:38:56 jonas
+ searchsystype() and searchsystype() functions in symtable
* changed ninl and nadd to use these functions
* i386 set comparison functions now return their results in al instead
of in the flags so that they can be sued as compilerprocs
- removed all processor specific code from n386add.pas that has to do
with set handling, it's now all done in nadd.pas
* fixed fpc_set_contains_sets in genset.inc
* fpc_set_in_byte is now coded inline in n386set.pas and doesn't use a
helper anymore
* some small fixes in compproc.inc/set.inc regarding the declaration of
internal helper types (fpc_small_set and fpc_normal_set)
Revision 1.5 2001/09/03 13:27:43 jonas
* compilerproc implementation of set addition/substraction/...
* changed the declaration of some set helpers somewhat to accomodate the
above change