Quellcode durchsuchen

* current_procdef removed, use current_procinfo.procdef instead

peter vor 22 Jahren
Ursprung
Commit
0dceec9a64

+ 31 - 5
compiler/cgbase.pas

@@ -351,6 +351,8 @@ implementation
 
 
     procedure tprocinfo.handle_body_start;
+      var
+        paramloc : tparalocation;
       begin
          { temporary space is set, while the BEGIN of the procedure }
          if (symtablestack.symtabletype=localsymtable) then
@@ -365,8 +367,29 @@ implementation
            begin
               if not paramanager.ret_in_param(procdef.rettype.def,procdef.proccalloption) then
                 begin
-                   rg.usedinproc := rg.usedinproc +
-                      getfuncretusedregisters(procdef.rettype.def,procdef.proccalloption);
+                  paramloc:=paramanager.getfuncresultloc(procdef,procdef.proccalloption);
+                  case paramloc.loc of
+                    LOC_FPUREGISTER,
+                    LOC_CFPUREGISTER,
+                    LOC_MMREGISTER,
+                    LOC_CMMREGISTER :
+                      begin
+                        include(rg.used_in_proc_other,paramloc.register.enum);
+                      end;
+                    LOC_REGISTER,LOC_CREGISTER :
+                      begin
+                        if ((paramloc.size in [OS_S64,OS_64]) and
+                           (sizeof(aword) < 8)) then
+                          begin
+                            include(rg.used_in_proc_int,paramloc.registerhigh.number shr 8);
+                            include(rg.used_in_proc_int,paramloc.registerlow.number shr 8);
+                          end
+                        else
+                          include(rg.used_in_proc_int,paramloc.register.number shr 8);
+                      end;
+                    else
+                      internalerror(20020816);
+                  end;
                 end;
            end;
       end;
@@ -548,7 +571,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.55  2003-06-12 16:43:07  peter
+  Revision 1.56  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.55  2003/06/12 16:43:07  peter
     * newra compiles for sparc
 
   Revision 1.54  2003/06/09 12:23:29  peter
@@ -593,7 +619,7 @@ end.
     * removed hdisposen,hnewn,selfn
 
   Revision 1.45  2003/04/27 11:21:32  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -602,7 +628,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.44  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 7 - 6
compiler/cgobj.pas

@@ -562,9 +562,7 @@ unit cgobj;
                 break;
              end;
          exclude(unusedscratchregisters,r.number shr 8);
-{$ifndef i386}
-         include(rg.usedintbyproc,r.number shr 8);
-{$endif i386}
+         include(rg.used_in_proc_int,r.number shr 8);
          a_reg_alloc(list,r);
          get_scratch_reg_int:=r;
       end;
@@ -1718,7 +1716,10 @@ finalization
 end.
 {
   $Log$
-  Revision 1.111  2003-06-12 21:11:10  peter
+  Revision 1.112  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.111  2003/06/12 21:11:10  peter
     * ungetregisterfpu gets size parameter
 
   Revision 1.110  2003/06/12 16:43:07  peter
@@ -1799,7 +1800,7 @@ end.
   + Patch from peter to fix wrong pushing of ansistring function results in open array
 
   Revision 1.92  2003/04/27 11:21:32  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1808,7 +1809,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.91  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 8 - 5
compiler/htypechk.pas

@@ -631,8 +631,8 @@ implementation
                           (hsym.varstate=vs_set_but_first_not_passed) then
                         begin
                           if (assigned(hsym.owner) and
-                              assigned(current_procdef) and
-                              (hsym.owner=current_procdef.localst)) then
+                              assigned(current_procinfo) and
+                              (hsym.owner=current_procinfo.procdef.localst)) then
                            begin
                              if (vo_is_funcret in hsym.varoptions) then
                                CGMessage(sym_w_function_result_not_set)
@@ -993,12 +993,15 @@ implementation
 end.
 {
   $Log$
-  Revision 1.63  2003-05-09 17:47:02  peter
+  Revision 1.64  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.63  2003/05/09 17:47:02  peter
     * self moved to hidden parameter
     * removed hdisposen,hnewn,selfn
 
   Revision 1.62  2003/04/27 11:21:32  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1007,7 +1010,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.61  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 6 - 3
compiler/i386/cpupi.pas

@@ -58,7 +58,7 @@ unit cpupi;
           begin
             { Make sure the register allocator won't allocate registers
               into ebp }
-            include(rg.usedintinproc,RS_EBP);
+            include(rg.used_in_proc_int,RS_EBP);
             exclude(rg.unusedregsint,RS_EBP);
           end;
       end;
@@ -69,7 +69,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.7  2003-06-12 18:12:49  jonas
+  Revision 1.8  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.7  2003/06/12 18:12:49  jonas
     * fixed compilation problems
 
   Revision 1.6  2003/06/12 16:43:07  peter
@@ -82,7 +85,7 @@ end.
     * removed some unit dependencies
 
   Revision 1.3  2003/04/27 11:21:35  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 12 - 9
compiler/i386/daopt386.pas

@@ -386,18 +386,18 @@ Procedure RemoveLastDeallocForFuncRes(asmL: TAAsmOutput; p: Tai);
   end;
 
 begin
-    case current_procdef.rettype.def.deftype of
+    case current_procinfo.procdef.rettype.def.deftype of
       arraydef,recorddef,pointerdef,
          stringdef,enumdef,procdef,objectdef,errordef,
          filedef,setdef,procvardef,
          classrefdef,forwarddef:
         DoRemoveLastDeallocForFuncRes(asmL,R_EAX);
       orddef:
-        if current_procdef.rettype.def.size <> 0 then
+        if current_procinfo.procdef.rettype.def.size <> 0 then
           begin
             DoRemoveLastDeallocForFuncRes(asmL,R_EAX);
             { for int64/qword }
-            if current_procdef.rettype.def.size = 8 then
+            if current_procinfo.procdef.rettype.def.size = 8 then
               DoRemoveLastDeallocForFuncRes(asmL,R_EDX);
           end;
     end;
@@ -407,18 +407,18 @@ procedure getNoDeallocRegs(var regs: TRegSet);
 var regCounter: ToldRegister;
 begin
   regs := [];
-    case current_procdef.rettype.def.deftype of
+    case current_procinfo.procdef.rettype.def.deftype of
       arraydef,recorddef,pointerdef,
          stringdef,enumdef,procdef,objectdef,errordef,
          filedef,setdef,procvardef,
          classrefdef,forwarddef:
        regs := [R_EAX];
       orddef:
-        if current_procdef.rettype.def.size <> 0 then
+        if current_procinfo.procdef.rettype.def.size <> 0 then
           begin
             regs := [R_EAX];
             { for int64/qword }
-            if current_procdef.rettype.def.size = 8 then
+            if current_procinfo.procdef.rettype.def.size = 8 then
               regs := regs + [R_EDX];
           end;
     end;
@@ -2018,7 +2018,7 @@ begin
   lolab := 0;
   hilab := 0;
   labdif := 0;
-  labeltable := nil;  
+  labeltable := nil;
 end;
 
 
@@ -2782,7 +2782,10 @@ end.
 
 {
   $Log$
-  Revision 1.52  2003-06-08 18:48:03  jonas
+  Revision 1.53  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.52  2003/06/08 18:48:03  jonas
     * first small steps towards an oop optimizer
 
   Revision 1.51  2003/06/03 21:09:05  peter
@@ -2796,7 +2799,7 @@ end.
     + tcallnode.inlined_pass_2 added
 
   Revision 1.49  2003/04/27 11:21:35  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 6 - 3
compiler/i386/n386mat.pas

@@ -405,8 +405,8 @@ implementation
                { since it was acquired with getregister), the others also }
                { use both EAX and EDX (JM)                                }
                 begin
-                  include(rg.usedintinproc,RS_EAX);
-                  include(rg.usedintinproc,RS_EDX);
+                  include(rg.used_in_proc_int,RS_EAX);
+                  include(rg.used_in_proc_int,RS_EDX);
                 end;
               location_reset(location,LOC_REGISTER,OS_INT);
               location.register:=hreg1;
@@ -1094,7 +1094,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.57  2003-06-03 21:11:09  peter
+  Revision 1.58  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.57  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

+ 10 - 7
compiler/i386/rgcpu.pas

@@ -151,7 +151,7 @@ unit rgcpu;
         begin
           dec(countunusedregsint);
           exclude(unusedregsint,RS_EAX);
-          include(usedintinproc,RS_EAX);
+          include(used_in_proc_int,RS_EAX);
           result.number:=RS_EAX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
           reg_user[R_EAX]:=curptree^;
@@ -162,7 +162,7 @@ unit rgcpu;
         begin
           dec(countunusedregsint);
           exclude(unusedregsint,RS_EDX);
-          include(usedintinproc,RS_EDX);
+          include(used_in_proc_int,RS_EDX);
           result.number:=RS_EDX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
           reg_user[R_EDX]:=curptree^;
@@ -173,7 +173,7 @@ unit rgcpu;
         begin
           dec(countunusedregsint);
           exclude(unusedregsint,RS_EBX);
-          include(usedintinproc,RS_EBX);
+          include(used_in_proc_int,RS_EBX);
           result.number:=RS_EBX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
           reg_user[R_EBX]:=curptree^;
@@ -184,7 +184,7 @@ unit rgcpu;
         begin
           dec(countunusedregsint);
           exclude(unusedregsint,RS_ECX);
-          include(usedintinproc,RS_ECX);
+          include(used_in_proc_int,RS_ECX);
           result.number:=RS_ECX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
           reg_user[R_ECX]:=curptree^;
@@ -305,7 +305,7 @@ unit rgcpu;
         r2:Tregister;
 
     begin
-      usedintinproc:=usedintinproc+s;
+      used_in_proc_int:=used_in_proc_int+s;
       for r:=firstsaveintreg to lastsaveintreg do
         begin
           r2.enum:=R_INTREGISTER;
@@ -341,7 +341,7 @@ unit rgcpu;
         hr:Treference;
 
     begin
-      usedinproc:=usedinproc+s;
+      used_in_proc_other:=used_in_proc_other+s;
       for r:=R_MM0 to R_MM6 do
         begin
           pushed[r].pushed:=false;
@@ -517,7 +517,10 @@ end.
 
 {
   $Log$
-  Revision 1.26  2003-06-12 21:12:20  peter
+  Revision 1.27  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.26  2003/06/12 21:12:20  peter
     * size para for ungetregisterfpu
 
   Revision 1.25  2003/06/03 21:11:09  peter

+ 8 - 5
compiler/nbas.pas

@@ -391,9 +391,9 @@ implementation
                    { concat function result to exit }
                    { this is wrong for string or other complex
                      result types !!! }
-                   if {ret_in_acc(current_procdef.rettype.def) and }
-                      (is_ordinal(current_procdef.rettype.def) or
-                       is_smallset(current_procdef.rettype.def)) and
+                   if {ret_in_acc(current_procinfo.procdef.rettype.def) and }
+                      (is_ordinal(current_procinfo.procdef.rettype.def) or
+                       is_smallset(current_procinfo.procdef.rettype.def)) and
                       assigned(hp.right) and
                       assigned(tstatementnode(hp.right).left) and
                       (tstatementnode(hp.right).left.nodetype=exitn) and
@@ -852,7 +852,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.57  2003-06-10 09:10:47  jonas
+  Revision 1.58  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.57  2003/06/10 09:10:47  jonas
     * patch from Peter to fix tempinfo copying
 
   Revision 1.56  2003/06/09 18:26:46  peter
@@ -898,7 +901,7 @@ end.
     * direct with rewritten to use temprefnode
 
   Revision 1.48  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 31 - 28
compiler/ncal.pas

@@ -91,7 +91,7 @@ interface
           { node that specifies where the result should be put for calls }
           { that return their result in a parameter                      }
           property funcretnode: tnode read _funcretnode write setfuncretnode;
-          
+
 
           { separately specified resulttype for some compilerprocs (e.g. }
           { you can't have a function with an "array of char" resulttype }
@@ -173,8 +173,13 @@ interface
 
 
     var
-       ccallnode : tcallnodeclass;
-       ccallparanode : tcallparanodeclass;
+      ccallnode : tcallnodeclass;
+      ccallparanode : tcallparanodeclass;
+
+      { Current callnode, this is needed for having a link
+       between the callparanodes and the callnode they belong to }
+      aktcallnode : tcallnode;
+
 
 implementation
 
@@ -309,7 +314,7 @@ type
             begin
               if (srsym.typ<>procsym) then
                internalerror(200111022);
-              if srsym.is_visible_for_proc(current_procdef) then
+              if srsym.is_visible_for_proc(current_procinfo.procdef) then
                begin
                  srsym.add_para_match_to(Aprocsym);
                  { we can stop if the overloads were already added
@@ -663,8 +668,8 @@ type
               begin
                 if is_array_of_const(paraitem.paratype.def) then
                  begin
-                   if assigned(aktcallprocdef) and
-                      (aktcallprocdef.proccalloption in [pocall_cppdecl,pocall_cdecl]) then
+                   if assigned(aktcallnode) and
+                      (aktcallnode.procdefinition.proccalloption in [pocall_cppdecl,pocall_cdecl]) then
                      include(left.flags,nf_cargs);
                    { force variant array }
                    include(left.flags,nf_forcevaria);
@@ -688,7 +693,7 @@ type
                 (paraitem.paratype.def.deftype<>formaldef) then
                begin
                   { Process open parameters }
-                  if paramanager.push_high_param(paraitem.paratype.def,aktcallprocdef.proccalloption) then
+                  if paramanager.push_high_param(paraitem.paratype.def,aktcallnode.procdefinition.proccalloption) then
                    begin
                      { insert type conv but hold the ranges of the array }
                      oldtype:=left.resulttype;
@@ -1123,7 +1128,6 @@ type
         parents : tlinkedlist;
         objectinfo : tobjectinfoitem;
         stritem : tstringlistitem;
-        _classname : string;
       begin
         objectdf := nil;
         { verify if trying to create an instance of a class which contains
@@ -1142,10 +1146,6 @@ type
           end;
         if not assigned(objectdf) then
           exit;
-        if assigned(objectdf.symtable.name) then
-          _classname := objectdf.symtable.name^
-        else
-          _classname := '';
 
         parents := tlinkedlist.create;
         AbstractMethodsList := tstringlist.create;
@@ -1239,7 +1239,7 @@ type
               when the callnode is generated by a property }
             if (nf_isproperty in flags) or
                (pd.owner.symtabletype<>objectsymtable) or
-               pd.is_visible_for_proc(current_procdef) then
+               pd.is_visible_for_proc(current_procinfo.procdef) then
              begin
                { only when the # of parameter are supported by the
                  procedure }
@@ -1270,7 +1270,7 @@ type
                   { process only visible procsyms }
                   if assigned(srprocsym) and
                      (srprocsym.typ=procsym) and
-                     srprocsym.is_visible_for_proc(current_procdef) then
+                     srprocsym.is_visible_for_proc(current_procinfo.procdef) then
                    begin
                      { if this procedure doesn't have overload we can stop
                        searching }
@@ -1686,13 +1686,13 @@ type
               then we need to load self with the VMT }
             if (
                 (po_classmethod in procdefinition.procoptions) and
-                not(assigned(current_procdef) and
-                    (po_classmethod in current_procdef.procoptions))
+                not(assigned(current_procinfo.procdef) and
+                    (po_classmethod in current_procinfo.procdef.procoptions))
                ) or
                (
                 (po_staticmethod in procdefinition.procoptions) and
-                 not(assigned(current_procdef) and
-                     (po_staticmethod in current_procdef.procoptions))
+                 not(assigned(current_procinfo.procdef) and
+                     (po_staticmethod in current_procinfo.procdef.procoptions))
                ) then
               begin
                 if (procdefinition.deftype<>procdef) then
@@ -1875,7 +1875,7 @@ type
     function tcallnode.det_resulttype:tnode;
       var
         procs : pcandidate;
-        oldcallprocdef : tabstractprocdef;
+        oldcallnode : tcallnode;
         hpt : tnode;
         pt : tcallparanode;
         lastpara : longint;
@@ -1890,8 +1890,8 @@ type
          result:=nil;
          procs:=nil;
 
-         oldcallprocdef:=aktcallprocdef;
-         aktcallprocdef:=nil;
+         oldcallnode:=aktcallnode;
+         aktcallnode:=nil;
 
          { determine length of parameter list }
          pt:=tcallparanode(left);
@@ -2143,7 +2143,7 @@ type
             if (nf_inherited in flags) and
                (procdefinition.proctypeoption in [potype_constructor,potype_destructor]) and
                is_object(methodpointer.resulttype.def) and
-               not(current_procdef.proctypeoption in [potype_constructor,potype_destructor]) then
+               not(current_procinfo.procdef.proctypeoption in [potype_constructor,potype_destructor]) then
              CGMessage(cg_w_member_cd_call_from_method);
 
             if methodpointer.nodetype<>typen then
@@ -2194,7 +2194,7 @@ type
           end;
 
          { bind paraitems to the callparanodes and insert hidden parameters }
-         aktcallprocdef:=procdefinition;
+         aktcallnode:=self;
          bind_paraitem;
 
          { methodpointer is only needed for virtual calls, and
@@ -2223,7 +2223,7 @@ type
            tcallparanode(left).insert_typeconv(true);
 
       errorexit:
-         aktcallprocdef:=oldcallprocdef;
+         aktcallnode:=oldcallnode;
       end;
 
 
@@ -2346,8 +2346,8 @@ type
 
               { procedure does a call }
               if not (block_type in [bt_const,bt_type]) then
-            {$ifndef newra}
                 include(current_procinfo.flags,pi_do_call);
+            {$ifndef newra}
               rg.incrementintregisterpushed(all_intregisters);
             {$endif}
               rg.incrementotherregisterpushed(all_registers);
@@ -2632,7 +2632,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.168  2003-06-08 20:01:53  jonas
+  Revision 1.169  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.168  2003/06/08 20:01:53  jonas
     * optimized assignments with on the right side a function that returns
       an ansi- or widestring
 
@@ -2720,7 +2723,7 @@ end.
     * vs_hidden replaced by is_hidden boolean
 
   Revision 1.147  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -2733,7 +2736,7 @@ end.
       because some nodes are turned into calls during the firstpass
 
   Revision 1.145  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 8 - 5
compiler/ncgbas.pas

@@ -144,8 +144,8 @@ interface
          if inlining_procedure then
            begin
              objectlibrary.CreateUsedAsmSymbolList;
-             localfixup:=current_procdef.localst.address_fixup;
-             parafixup:=current_procdef.parast.address_fixup;
+             localfixup:=current_procinfo.procdef.localst.address_fixup;
+             parafixup:=current_procinfo.procdef.parast.address_fixup;
              hp:=tai(p_asm.first);
              while assigned(hp) do
               begin
@@ -218,7 +218,7 @@ interface
            begin
              { if the routine is an inline routine, then we must hold a copy
                because it can be necessary for inlining later }
-             if (current_procdef.proccalloption=pocall_inline) then
+             if (current_procinfo.procdef.proccalloption=pocall_inline) then
                exprasmList.concatlistcopy(p_asm)
              else
                exprasmList.concatlist(p_asm);
@@ -316,7 +316,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.36  2003-06-09 18:26:46  peter
+  Revision 1.37  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.36  2003/06/09 18:26:46  peter
     * remove temptype, use tempinfo.temptype instead
 
   Revision 1.35  2003/06/09 12:20:47  peter
@@ -328,7 +331,7 @@ end.
       temps, but a ttemptype, so you can also create ansistring temps etc
 
   Revision 1.33  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 45 - 51
compiler/ncgcal.pas

@@ -96,11 +96,6 @@ implementation
       ncgutil,cgobj,tgobj,regvars,rgobj,rgcpu;
 
 
-    var
-      { Current callnode, this is needed for having a link
-        between the callparanodes and the callnode they belong to }
-      aktcallnode : tcallnode;
-
 {*****************************************************************************
                              TCGCALLPARANODE
 *****************************************************************************}
@@ -378,23 +373,23 @@ implementation
         i : integer;
       begin
         { this routine is itself not nested }
-        if current_procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel) then
+        if current_procinfo.procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel) then
           begin
             reference_reset_base(href,current_procinfo.framepointer,current_procinfo.framepointer_offset);
             cg.a_param_ref(exprasmlist,OS_ADDR,href,paramanager.getintparaloc(exprasmlist,1));
           end
         { one nesting level }
-        else if (current_procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel)-1) then
+        else if (current_procinfo.procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel)-1) then
           begin
             cg.a_param_reg(exprasmlist,OS_ADDR,current_procinfo.framepointer,paramanager.getintparaloc(exprasmlist,1));
           end
         { very complex nesting level ... }
-        else if (current_procdef.parast.symtablelevel>(tprocdef(procdefinition).parast.symtablelevel)) then
+        else if (current_procinfo.procdef.parast.symtablelevel>(tprocdef(procdefinition).parast.symtablelevel)) then
           begin
             hregister:=rg.getaddressregister(exprasmlist);
             reference_reset_base(href,current_procinfo.framepointer,current_procinfo.framepointer_offset);
             cg.a_load_ref_reg(exprasmlist,OS_ADDR,OS_ADDR,href,hregister);
-            i:=current_procdef.parast.symtablelevel;
+            i:=current_procinfo.procdef.parast.symtablelevel;
             while (i>tprocdef(procdefinition).parast.symtablelevel) do
               begin
                 reference_reset_base(href,hregister,current_procinfo.framepointer_offset);
@@ -679,7 +674,7 @@ implementation
            begin
               if (cs_check_io in aktlocalswitches) and
                  (po_iocheck in procdefinition.procoptions) and
-                 not(po_iocheck in current_procdef.procoptions) then
+                 not(po_iocheck in current_procinfo.procdef.procoptions) then
                 begin
                    objectlibrary.getaddrlabel(iolabel);
                    cg.a_label(exprasmlist,iolabel);
@@ -725,10 +720,8 @@ implementation
               { and must make sure it saves its volatile registers before doing a call     }
 {$ifdef i386}
               { give used registers through }
-{$ifndef newra}
-              rg.usedintinproc:=rg.usedintinproc + tprocdef(procdefinition).usedintregisters;
-{$endif}
-              rg.usedinproc:=rg.usedinproc + tprocdef(procdefinition).usedotherregisters;
+              rg.used_in_proc_int:=rg.used_in_proc_int + tprocdef(procdefinition).usedintregisters;
+              rg.used_in_proc_other:=rg.used_in_proc_other + tprocdef(procdefinition).usedotherregisters;
 {$endif i386}
            end
          else
@@ -751,9 +744,8 @@ implementation
 {$endif}
               regs_to_push_other := all_registers;
               rg.saveusedotherregisters(exprasmlist,pushedother,regs_to_push_other);
-{$ifndef newra}
-              rg.usedinproc:=all_registers;
-{$endif}
+              rg.used_in_proc_other:=all_registers;
+
               { no IO check for methods and procedure variables }
               iolabel:=nil;
            end;
@@ -824,7 +816,7 @@ implementation
          if (right=nil) then
            begin
               { push base pointer ?}
-              if (current_procdef.parast.symtablelevel>=normal_function_level) and
+              if (current_procinfo.procdef.parast.symtablelevel>=normal_function_level) and
                  assigned(tprocdef(procdefinition).parast) and
                  ((tprocdef(procdefinition).parast.symtablelevel)>normal_function_level) then
                 push_framepointer;
@@ -1110,15 +1102,15 @@ implementation
            internalerror(200305262);
 
          oldinlining_procedure:=inlining_procedure;
-         oldprocdef:=current_procdef;
+         oldprocdef:=current_procinfo.procdef;
          oldprocinfo:=current_procinfo;
          { we're inlining a procedure }
          inlining_procedure:=true;
 
          { deallocate the registers used for the current procedure's regvars }
-         if assigned(current_procdef.regvarinfo) then
+         if assigned(current_procinfo.procdef.regvarinfo) then
            begin
-             with pregvarinfo(current_procdef.regvarinfo)^ do
+             with pregvarinfo(current_procinfo.procdef.regvarinfo)^ do
                for i := 1 to maxvarregs do
                  if assigned(regvars[i]) then
                    store_regvar(exprasmlist,regvars[i].reg);
@@ -1145,36 +1137,35 @@ implementation
          { create temp procinfo }
          current_procinfo:=cprocinfo.create(nil);
          current_procinfo.procdef:=tprocdef(procdefinition);
-         current_procdef:=current_procinfo.procdef;
 
          { Localsymtable }
-         current_procdef.localst.symtablelevel:=oldprocdef.localst.symtablelevel;
-         if current_procdef.localst.datasize>0 then
+         current_procinfo.procdef.localst.symtablelevel:=oldprocdef.localst.symtablelevel;
+         if current_procinfo.procdef.localst.datasize>0 then
            begin
-             old_local_fixup:=current_procdef.localst.address_fixup;
-             tg.GetTemp(exprasmlist,current_procdef.localst.datasize,tt_persistent,localsref);
+             old_local_fixup:=current_procinfo.procdef.localst.address_fixup;
+             tg.GetTemp(exprasmlist,current_procinfo.procdef.localst.datasize,tt_persistent,localsref);
              if tg.direction>0 then
-               current_procdef.localst.address_fixup:=localsref.offset
+               current_procinfo.procdef.localst.address_fixup:=localsref.offset
              else
-               current_procdef.localst.address_fixup:=localsref.offset+current_procdef.localst.datasize;
+               current_procinfo.procdef.localst.address_fixup:=localsref.offset+current_procinfo.procdef.localst.datasize;
 {$ifdef extdebug}
-             Comment(V_debug,'inlined local symtable ('+tostr(current_procdef.localst.datasize)+' bytes) is at offset '+tostr(current_procdef.localst.address_fixup));
+             Comment(V_debug,'inlined local symtable ('+tostr(current_procinfo.procdef.localst.datasize)+' bytes) is at offset '+tostr(current_procinfo.procdef.localst.address_fixup));
              exprasmList.concat(tai_comment.Create(strpnew(
-               'inlined local symtable ('+tostr(current_procdef.localst.datasize)+' bytes) is at offset '+tostr(current_procdef.localst.address_fixup))));
+               'inlined local symtable ('+tostr(current_procinfo.procdef.localst.datasize)+' bytes) is at offset '+tostr(current_procinfo.procdef.localst.address_fixup))));
 {$endif extdebug}
            end;
 
          { Parasymtable }
-         current_procdef.parast.symtablelevel:=oldprocdef.localst.symtablelevel;
-         if current_procdef.parast.datasize>0 then
+         current_procinfo.procdef.parast.symtablelevel:=oldprocdef.localst.symtablelevel;
+         if current_procinfo.procdef.parast.datasize>0 then
            begin
-             old_para_fixup:=current_procdef.parast.address_fixup;
-             tg.GetTemp(exprasmlist,current_procdef.parast.datasize,tt_persistent,pararef);
-             current_procdef.parast.address_fixup:=pararef.offset;
+             old_para_fixup:=current_procinfo.procdef.parast.address_fixup;
+             tg.GetTemp(exprasmlist,current_procinfo.procdef.parast.datasize,tt_persistent,pararef);
+             current_procinfo.procdef.parast.address_fixup:=pararef.offset;
 {$ifdef extdebug}
-             Comment(V_debug,'inlined para symtable ('+tostr(current_procdef.parast.datasize)+' bytes) is at offset '+tostr(current_procdef.parast.address_fixup));
+             Comment(V_debug,'inlined para symtable ('+tostr(current_procinfo.procdef.parast.datasize)+' bytes) is at offset '+tostr(current_procinfo.procdef.parast.address_fixup));
              exprasmList.concat(tai_comment.Create(strpnew(
-               'inlined para symtable ('+tostr(current_procdef.parast.datasize)+' bytes) is at offset '+tostr(current_procdef.parast.address_fixup))));
+               'inlined para symtable ('+tostr(current_procinfo.procdef.parast.datasize)+' bytes) is at offset '+tostr(current_procinfo.procdef.parast.address_fixup))));
 {$endif extdebug}
            end;
 
@@ -1231,7 +1222,7 @@ implementation
 
          if (cs_check_io in aktlocalswitches) and
             (po_iocheck in procdefinition.procoptions) and
-            not(po_iocheck in current_procdef.procoptions) then
+            not(po_iocheck in current_procinfo.procdef.procoptions) then
            begin
               objectlibrary.getaddrlabel(iolabel);
               cg.a_label(exprasmlist,iolabel);
@@ -1264,8 +1255,8 @@ implementation
 
 {$ifdef i386}
          { give used registers through }
-         rg.usedintinproc:=rg.usedintinproc + tprocdef(procdefinition).usedintregisters;
-         rg.usedinproc:=rg.usedinproc + tprocdef(procdefinition).usedotherregisters;
+         rg.used_in_proc_int:=rg.used_in_proc_int + tprocdef(procdefinition).usedintregisters;
+         rg.used_in_proc_other:=rg.used_in_proc_other + tprocdef(procdefinition).usedotherregisters;
 {$endif i386}
 
          { Initialize for pushing the parameters }
@@ -1311,7 +1302,7 @@ implementation
          inlineexitcode:=TAAsmoutput.Create;
 
          gen_initialize_code(inlineentrycode,true);
-         if po_assembler in current_procdef.procoptions then
+         if po_assembler in current_procinfo.procdef.procoptions then
            inlineentrycode.insert(Tai_marker.Create(asmblockstart));
          exprasmList.concatlist(inlineentrycode);
 
@@ -1333,7 +1324,7 @@ implementation
 
          gen_finalize_code(inlineexitcode,true);
          gen_load_return_value(inlineexitcode,usesacc,usesacchi,usesfpu);
-         if po_assembler in current_procdef.procoptions then
+         if po_assembler in current_procinfo.procdef.procoptions then
            inlineexitcode.concat(Tai_marker.Create(asmblockend));
          exprasmList.concatlist(inlineexitcode);
 
@@ -1345,16 +1336,16 @@ implementation
          exprasmList.concat(Tai_Marker.Create(InlineEnd));
 
          {we can free the local data now, reset also the fixup address }
-         if current_procdef.localst.datasize>0 then
+         if current_procinfo.procdef.localst.datasize>0 then
            begin
              tg.UnGetTemp(exprasmlist,localsref);
-             current_procdef.localst.address_fixup:=old_local_fixup;
+             current_procinfo.procdef.localst.address_fixup:=old_local_fixup;
            end;
          {we can free the para data now, reset also the fixup address }
-         if current_procdef.parast.datasize>0 then
+         if current_procinfo.procdef.parast.datasize>0 then
            begin
              tg.UnGetTemp(exprasmlist,pararef);
-             current_procdef.parast.address_fixup:=old_para_fixup;
+             current_procinfo.procdef.parast.address_fixup:=old_para_fixup;
            end;
          { free return reference }
          if (resulttype.def.size>0) then
@@ -1435,13 +1426,13 @@ implementation
 {$endif GDB}
 
          { restore }
-         current_procdef:=oldprocdef;
+         current_procinfo.procdef:=oldprocdef;
          inlining_procedure:=oldinlining_procedure;
 
          { reallocate the registers used for the current procedure's regvars, }
          { since they may have been used and then deallocated in the inlined  }
          { procedure (JM)                                                     }
-         if assigned(current_procdef.regvarinfo) then
+         if assigned(current_procinfo.procdef.regvarinfo) then
            rg.restoreStateAfterInline(oldregstate);
       end;
 
@@ -1461,7 +1452,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.92  2003-06-12 21:10:50  peter
+  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
@@ -1609,7 +1603,7 @@ end.
   + 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_procdef
+    * 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
@@ -1618,7 +1612,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.54  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * 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

+ 5 - 2
compiler/ncgflw.pas

@@ -1443,7 +1443,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.71  2003-06-09 14:38:52  jonas
+  Revision 1.72  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.71  2003/06/09 14:38:52  jonas
     * fixed for callparatemp
 
   Revision 1.70  2003/06/09 12:23:30  peter
@@ -1509,7 +1512,7 @@ end.
   + Patch from peter to fix wrong pushing of ansistring function results in open array
 
   Revision 1.56  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 6 - 3
compiler/ncginl.pas

@@ -249,7 +249,7 @@ implementation
               LOC_REGISTER :
                 begin
                   if (left.resulttype.def.deftype=classrefdef) or
-                     (po_staticmethod in current_procdef.procoptions) then
+                     (po_staticmethod in current_procinfo.procdef.procoptions) then
                     cg.a_load_reg_reg(exprasmlist,OS_ADDR,OS_ADDR,left.location.register,hregister)
                   else
                    begin
@@ -686,7 +686,10 @@ end.
 
 {
   $Log$
-  Revision 1.36  2003-06-07 18:57:04  jonas
+  Revision 1.37  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.36  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)
@@ -721,7 +724,7 @@ end.
     * fixed include/exclude for normalsets
 
   Revision 1.28  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 8 - 5
compiler/ncgld.pas

@@ -209,14 +209,14 @@ implementation
                                   location.reference.base:=current_procinfo.framepointer;
                                   location.reference.offset:=tvarsym(symtableentry).adjusted_address;
 
-                                  if (current_procdef.parast.symtablelevel>symtable.symtablelevel) then
+                                  if (current_procinfo.procdef.parast.symtablelevel>symtable.symtablelevel) then
                                     begin
                                        hregister:=rg.getaddressregister(exprasmlist);
                                        { make a reference }
                                        reference_reset_base(href,current_procinfo.framepointer,current_procinfo.framepointer_offset);
                                        cg.a_load_ref_reg(exprasmlist,OS_ADDR,OS_ADDR,href,hregister);
                                        { walk parents }
-                                       i:=current_procdef.parast.symtablelevel-1;
+                                       i:=current_procinfo.procdef.parast.symtablelevel-1;
                                        while (i>symtable.symtablelevel) do
                                          begin
                                             { make a reference }
@@ -953,7 +953,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.70  2003-06-12 16:43:07  peter
+  Revision 1.71  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.70  2003/06/12 16:43:07  peter
     * newra compiles for sparc
 
   Revision 1.69  2003/06/09 16:41:52  jonas
@@ -1030,7 +1033,7 @@ end.
   + Patch from peter to fix wrong pushing of ansistring function results in open array
 
   Revision 1.54  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1039,7 +1042,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.53  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 9 - 6
compiler/ncgmem.pas

@@ -367,13 +367,13 @@ implementation
                '"with'+tostr(withlevel)+':'+tostr(symtablestack.getnewtypecount)+
                '=*'+tstoreddef(left.resulttype.def).numberstring+'",'+
                tostr(N_LSYM)+',0,0,'+tostr(withrefnode.location.reference.offset))));
-            mangled_length:=length(current_procdef.mangledname);
+            mangled_length:=length(current_procinfo.procdef.mangledname);
             getmem(pp,mangled_length+50);
             strpcopy(pp,'192,0,0,'+withstartlabel.name);
             if (target_info.use_function_relative_addresses) then
               begin
                 strpcopy(strend(pp),'-');
-                strpcopy(strend(pp),current_procdef.mangledname);
+                strpcopy(strend(pp),current_procinfo.procdef.mangledname);
               end;
             withdebugList.concat(Tai_stabn.Create(strnew(pp)));
           end;
@@ -390,7 +390,7 @@ implementation
            if (target_info.use_function_relative_addresses) then
              begin
                strpcopy(strend(pp),'-');
-               strpcopy(strend(pp),current_procdef.mangledname);
+               strpcopy(strend(pp),current_procinfo.procdef.mangledname);
              end;
             withdebugList.concat(Tai_stabn.Create(strnew(pp)));
             freemem(pp,mangled_length+50);
@@ -470,7 +470,7 @@ implementation
             is_array_of_const(left.resulttype.def) then
           begin
             { cdecl functions don't have high() so we can not check the range }
-            if not(current_procdef.proccalloption in [pocall_cdecl,pocall_cppdecl]) then
+            if not(current_procinfo.procdef.proccalloption in [pocall_cdecl,pocall_cppdecl]) then
              begin
                { Get high value }
                hightree:=load_high_value_node(tvarsym(tloadnode(left).symtableentry));
@@ -955,7 +955,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.61  2003-06-09 16:45:41  jonas
+  Revision 1.62  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.61  2003/06/09 16:45:41  jonas
     * fixed update_reference_reg_mul() so that it won't modify CREGISTERs
       in a reference
     * cache value of get_mul_size()
@@ -1010,7 +1013,7 @@ end.
   - non used units removed from uses clause
 
   Revision 1.49  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 107 - 104
compiler/ncgutil.pas

@@ -1242,22 +1242,22 @@ implementation
       var
         href    : treference;
       begin
-        if not is_void(current_procdef.rettype.def) then
+        if not is_void(current_procinfo.procdef.rettype.def) then
           begin
              { initialize return value }
-             if (current_procdef.rettype.def.needs_inittable) then
+             if (current_procinfo.procdef.rettype.def.needs_inittable) then
                begin
 {$ifdef powerpc}
-                  if (po_assembler in current_procdef.procoptions) then
+                  if (po_assembler in current_procinfo.procdef.procoptions) then
                     internalerror(200304161);
 {$endif powerpc}
                   if (cs_implicit_exceptions in aktmoduleswitches) then
                     include(current_procinfo.flags,pi_needs_implicit_finally);
-                  reference_reset_base(href,current_procinfo.framepointer,tvarsym(current_procdef.funcretsym).adjusted_address);
-                  cg.g_initialize(list,current_procdef.rettype.def,href,paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption));
+                  reference_reset_base(href,current_procinfo.framepointer,tvarsym(current_procinfo.procdef.funcretsym).adjusted_address);
+                  cg.g_initialize(list,current_procinfo.procdef.rettype.def,href,paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption));
                   { load the pointer to the initialized retvalue in te register }
-                  if (tvarsym(current_procdef.funcretsym).reg.enum <> R_NO) then
-                    cg.a_load_ref_reg(list,OS_ADDR,def_cgsize(current_procdef.rettype.def),href,tvarsym(current_procdef.funcretsym).reg);
+                  if (tvarsym(current_procinfo.procdef.funcretsym).reg.enum <> R_NO) then
+                    cg.a_load_ref_reg(list,OS_ADDR,def_cgsize(current_procinfo.procdef.rettype.def),href,tvarsym(current_procinfo.procdef.funcretsym).reg);
                end;
           end;
       end;
@@ -1271,22 +1271,22 @@ implementation
         hreg,r,r2 : tregister;
       begin
         { Is the loading needed? }
-        if is_void(current_procdef.rettype.def) or
+        if is_void(current_procinfo.procdef.rettype.def) or
            (
-            (po_assembler in current_procdef.procoptions) and
-            (not(assigned(current_procdef.funcretsym)) or
-             (tvarsym(current_procdef.funcretsym).refcount=0))
+            (po_assembler in current_procinfo.procdef.procoptions) and
+            (not(assigned(current_procinfo.procdef.funcretsym)) or
+             (tvarsym(current_procinfo.procdef.funcretsym).refcount=0))
            ) then
           exit;
 
         { Constructors need to return self }
-        if (current_procdef.proctypeoption=potype_constructor) then
+        if (current_procinfo.procdef.proctypeoption=potype_constructor) then
           begin
             r.enum:=R_INTREGISTER;
             r.number:=NR_FUNCTION_RETURN_REG;
             cg.a_reg_alloc(list,r);
             { return the self pointer }
-            ressym:=tvarsym(current_procdef.parast.search('self'));
+            ressym:=tvarsym(current_procinfo.procdef.parast.search('self'));
             if not assigned(ressym) then
               internalerror(200305058);
             reference_reset_base(href,current_procinfo.framepointer,tvarsym(ressym).adjusted_address);
@@ -1296,27 +1296,27 @@ implementation
             exit;
           end;
 
-        ressym := tvarsym(current_procdef.funcretsym);
+        ressym := tvarsym(current_procinfo.procdef.funcretsym);
         if ressym.reg.enum <> R_NO then
           begin
-            if paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+            if paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption) then
               location_reset(resloc,LOC_CREGISTER,OS_ADDR)
             else
               if ressym.vartype.def.deftype = floatdef then
-                location_reset(resloc,LOC_CFPUREGISTER,def_cgsize(current_procdef.rettype.def))
+                location_reset(resloc,LOC_CFPUREGISTER,def_cgsize(current_procinfo.procdef.rettype.def))
               else
-                location_reset(resloc,LOC_CREGISTER,def_cgsize(current_procdef.rettype.def));
+                location_reset(resloc,LOC_CREGISTER,def_cgsize(current_procinfo.procdef.rettype.def));
             resloc.register := ressym.reg;
           end
         else
           begin
-            location_reset(resloc,LOC_REFERENCE,def_cgsize(current_procdef.rettype.def));
-            reference_reset_base(resloc.reference,current_procinfo.framepointer,tvarsym(current_procdef.funcretsym).adjusted_address);
+            location_reset(resloc,LOC_REFERENCE,def_cgsize(current_procinfo.procdef.rettype.def));
+            reference_reset_base(resloc.reference,current_procinfo.framepointer,tvarsym(current_procinfo.procdef.funcretsym).adjusted_address);
           end;
         { Here, we return the function result. In most architectures, the value is
           passed into the FUNCTION_RETURN_REG, but in a windowed architecure like sparc a
           function returns in a register and the caller receives it in an other one }
-        case current_procdef.rettype.def.deftype of
+        case current_procinfo.procdef.rettype.def.deftype of
           orddef,
           enumdef :
             begin
@@ -1355,7 +1355,7 @@ implementation
             end;
           else
             begin
-              if not paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+              if not paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption) then
                begin
                  uses_acc:=true;
 {$ifndef cpu64bit}
@@ -1393,7 +1393,7 @@ implementation
           the actual call to the profile code
         }
         if (cs_profile in aktmoduleswitches) and
-           not(po_assembler in current_procdef.procoptions) and
+           not(po_assembler in current_procinfo.procdef.procoptions) and
            not(inlined) then
           begin
             { non-win32 can call mcout even in main }
@@ -1401,7 +1401,7 @@ implementation
               cg.g_profilecode(list)
             else
             { wdosx, and win32 should not call mcount before monstartup has been called }
-            if not (current_procdef.proctypeoption=potype_proginit) then
+            if not (current_procinfo.procdef.proctypeoption=potype_proginit) then
               cg.g_profilecode(list);
           end;
 
@@ -1409,7 +1409,7 @@ implementation
         initretvalue(list);
 
         { initialize local data like ansistrings }
-        case current_procdef.proctypeoption of
+        case current_procinfo.procdef.proctypeoption of
            potype_unitinit:
              begin
                 { this is also used for initialization of variables in a
@@ -1423,7 +1423,7 @@ implementation
            { program init/final is generated in separate procedure }
            potype_proginit: ;
            else
-             current_procdef.localst.foreach_static({$ifndef TP}@{$endif}initialize_data,list);
+             current_procinfo.procdef.localst.foreach_static({$ifndef TP}@{$endif}initialize_data,list);
         end;
 
         { initialisizes temp. ansi/wide string data }
@@ -1432,16 +1432,16 @@ implementation
         { generate copies of call by value parameters, must be done before
           the initialization because the refcounts are incremented using
           the local copies }
-        if not(po_assembler in current_procdef.procoptions) then
-          current_procdef.parast.foreach_static({$ifndef TP}@{$endif}copyvalueparas,list);
+        if not(po_assembler in current_procinfo.procdef.procoptions) then
+          current_procinfo.procdef.parast.foreach_static({$ifndef TP}@{$endif}copyvalueparas,list);
 
         { initialize ansi/widesstring para's }
-        current_procdef.parast.foreach_static({$ifndef TP}@{$endif}init_paras,list);
+        current_procinfo.procdef.parast.foreach_static({$ifndef TP}@{$endif}init_paras,list);
 
         if (not inlined) then
          begin
            { call startup helpers from main program }
-           if (current_procdef.proctypeoption=potype_proginit) then
+           if (current_procinfo.procdef.proctypeoption=potype_proginit) then
             begin
               { initialize profiling for win32 }
               if (target_info.system in [system_i386_win32,system_i386_wdosx]) and
@@ -1480,7 +1480,7 @@ implementation
         finalizetempvariables(list);
 
         { finalize local data like ansistrings}
-        case current_procdef.proctypeoption of
+        case current_procinfo.procdef.proctypeoption of
            potype_unitfinalize:
              begin
                 { this is also used for initialization of variables in a
@@ -1494,17 +1494,17 @@ implementation
            { program init/final is generated in separate procedure }
            potype_proginit: ;
            else
-             current_procdef.localst.foreach_static({$ifndef TP}@{$endif}finalize_data,list);
+             current_procinfo.procdef.localst.foreach_static({$ifndef TP}@{$endif}finalize_data,list);
         end;
 
         { finalize paras data }
-        if assigned(current_procdef.parast) then
-          current_procdef.parast.foreach_static({$ifndef TP}@{$endif}final_paras,list);
+        if assigned(current_procinfo.procdef.parast) then
+          current_procinfo.procdef.parast.foreach_static({$ifndef TP}@{$endif}final_paras,list);
 
         { call __EXIT for main program }
         if (not DLLsource) and
            (not inlined) and
-           (current_procdef.proctypeoption=potype_proginit) then
+           (current_procinfo.procdef.proctypeoption=potype_proginit) then
           cg.a_call_name(list,'FPC_DO_EXIT');
 
         cleanup_regvars(list);
@@ -1526,14 +1526,14 @@ implementation
           code, since temp. allocation might occur before - carl
         }
 
-        if assigned(current_procdef.parast) then
+        if assigned(current_procinfo.procdef.parast) then
           begin
-             if not (po_assembler in current_procdef.procoptions) then
+             if not (po_assembler in current_procinfo.procdef.procoptions) then
                begin
                  { move register parameters which aren't regable into memory                               }
                  { we do this before init_paras because that one calls routines which may overwrite these  }
                  { registers and it also expects the values to be in memory                                }
-                 hp:=tparaitem(current_procdef.para.first);
+                 hp:=tparaitem(current_procinfo.procdef.para.first);
                  while assigned(hp) do
                    begin
                      if Tvarsym(hp.parasym).reg.enum>R_INTREGISTER then
@@ -1585,18 +1585,18 @@ implementation
 
         { for the save all registers we can simply use a pusha,popa which
           push edi,esi,ebp,esp(ignored),ebx,edx,ecx,eax }
-        if (po_saveregisters in current_procdef.procoptions) then
+        if (po_saveregisters in current_procinfo.procdef.procoptions) then
           cg.g_save_all_registers(list)
         else
          { should we save edi,esi,ebx like C ? }
-         if (po_savestdregs in current_procdef.procoptions) then
-           cg.g_save_standard_registers(list,current_procdef.usedintregisters);
+         if (po_savestdregs in current_procinfo.procdef.procoptions) then
+           cg.g_save_standard_registers(list,current_procinfo.procdef.usedintregisters);
 
         { Save stackpointer value }
         if not inlined and
            (current_procinfo.framepointer.number<>NR_STACK_POINTER_REG) and
-           ((po_savestdregs in current_procdef.procoptions) or
-            (po_saveregisters in current_procdef.procoptions)) then
+           ((po_savestdregs in current_procinfo.procdef.procoptions) or
+            (po_saveregisters in current_procinfo.procdef.procoptions)) then
          begin
            tg.GetTemp(list,POINTER_SIZE,tt_noreuse,current_procinfo.save_stackptr_ref);
            rsp.enum:=R_INTREGISTER;
@@ -1624,15 +1624,15 @@ implementation
 {$ifdef GDB}
       if (cs_debuginfo in aktmoduleswitches) then
         begin
-          if (po_public in current_procdef.procoptions) then
-            Tprocsym(current_procdef.procsym).is_global:=true;
-          current_procdef.concatstabto(list);
-          Tprocsym(current_procdef.procsym).isstabwritten:=true;
+          if (po_public in current_procinfo.procdef.procoptions) then
+            Tprocsym(current_procinfo.procdef.procsym).is_global:=true;
+          current_procinfo.procdef.concatstabto(list);
+          Tprocsym(current_procinfo.procdef.procsym).isstabwritten:=true;
         end;
 {$endif GDB}
 
       repeat
-        hs:=current_procdef.aliasnames.getfirst;
+        hs:=current_procinfo.procdef.aliasnames.getfirst;
         if hs='' then
           break;
 {$ifdef GDB}
@@ -1641,7 +1641,7 @@ implementation
         list.concat(Tai_stab_function_name.create(strpnew(hs)));
 {$endif GDB}
         if (cs_profile in aktmoduleswitches) or
-           (po_public in current_procdef.procoptions) then
+           (po_public in current_procinfo.procdef.procoptions) then
           list.concat(Tai_symbol.createname_global(hs,0))
         else
           list.concat(Tai_symbol.createname(hs,0));
@@ -1665,14 +1665,14 @@ implementation
       else
 {$endif powerpc}
         begin
-          if (po_interrupt in current_procdef.procoptions) then
+          if (po_interrupt in current_procinfo.procdef.procoptions) then
             cg.g_interrupt_stackframe_entry(list);
 
           cg.g_stackframe_entry(list,stackframe);
 
           {Never call stack checking before the standard system unit
            has been initialized.}
-           if (cs_check_stack in aktlocalswitches) and (current_procdef.proctypeoption<>potype_proginit) then
+           if (cs_check_stack in aktlocalswitches) and (current_procinfo.procdef.proctypeoption<>potype_proginit) then
              cg.g_stackcheck(list,stackframe);
         end;
     end;
@@ -1710,8 +1710,8 @@ implementation
         { Restore stackpointer if it was saved }
         if not inlined and
            (current_procinfo.framepointer.number<>NR_STACK_POINTER_REG) and
-           ((po_savestdregs in current_procdef.procoptions) or
-            (po_saveregisters in current_procdef.procoptions)) then
+           ((po_savestdregs in current_procinfo.procdef.procoptions) or
+            (po_saveregisters in current_procinfo.procdef.procoptions)) then
          begin
            rsp.enum:=R_INTREGISTER;
            rsp.number:=NR_STACK_POINTER_REG;
@@ -1721,12 +1721,12 @@ implementation
 
         { for the save all registers we can simply use a pusha,popa which
           push edi,esi,ebp,esp(ignored),ebx,edx,ecx,eax }
-        if (po_saveregisters in current_procdef.procoptions) then
+        if (po_saveregisters in current_procinfo.procdef.procoptions) then
           cg.g_restore_all_registers(list,usesacc,usesacchi)
         else
          { should we restore edi ? }
-         if (po_savestdregs in current_procdef.procoptions) then
-           cg.g_restore_standard_registers(list,current_procdef.usedintregisters);
+         if (po_savestdregs in current_procinfo.procdef.procoptions) then
+           cg.g_restore_standard_registers(list,current_procinfo.procdef.usedintregisters);
 
 {$ifndef powerpc}
         { remove stackframe }
@@ -1745,28 +1745,28 @@ implementation
         { at last, the return is generated }
         if not inlined then
          begin
-           if (po_interrupt in current_procdef.procoptions) then
+           if (po_interrupt in current_procinfo.procdef.procoptions) then
             cg.g_interrupt_stackframe_exit(list,usesacc,usesacchi)
            else
             begin
-              if (po_clearstack in current_procdef.procoptions) then
+              if (po_clearstack in current_procinfo.procdef.procoptions) then
                 begin
                   retsize:=0;
-                  if paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+                  if paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption) then
                     inc(retsize,POINTER_SIZE);
                 end
               else
                 begin
-                  retsize:=current_procdef.parast.datasize;
-                  if current_procdef.parast.address_fixup>target_info.first_parm_offset then
-                    inc(retsize,current_procdef.parast.address_fixup-target_info.first_parm_offset);
+                  retsize:=current_procinfo.procdef.parast.datasize;
+                  if current_procinfo.procdef.parast.address_fixup>target_info.first_parm_offset then
+                    inc(retsize,current_procinfo.procdef.parast.address_fixup-target_info.first_parm_offset);
                 end;
               cg.g_return_from_proc(list,retsize);
             end;
          end;
 
         if not inlined then
-          list.concat(Tai_symbol_end.Createname(current_procdef.mangledname));
+          list.concat(Tai_symbol_end.Createname(current_procinfo.procdef.mangledname));
 
 {$ifdef GDB}
         if (cs_debuginfo in aktmoduleswitches) and not inlined  then
@@ -1774,55 +1774,55 @@ implementation
             { define calling EBP as pseudo local var PM }
             { this enables test if the function is a local one !! }
             if  assigned(current_procinfo.parent) and
-                (current_procdef.parast.symtablelevel>normal_function_level) then
+                (current_procinfo.procdef.parast.symtablelevel>normal_function_level) then
               list.concat(Tai_stabs.Create(strpnew(
                '"parent_ebp:'+tstoreddef(voidpointertype.def).numberstring+'",'+
                tostr(N_LSYM)+',0,0,'+tostr(current_procinfo.framepointer_offset))));
 
-            if (not is_void(current_procdef.rettype.def)) then
+            if (not is_void(current_procinfo.procdef.rettype.def)) then
               begin
-                if paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+                if paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption) then
                   list.concat(Tai_stabs.Create(strpnew(
-                   '"'+current_procdef.procsym.name+':X*'+tstoreddef(current_procdef.rettype.def).numberstring+'",'+
-                   tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procdef.funcretsym).adjusted_address))))
+                   '"'+current_procinfo.procdef.procsym.name+':X*'+tstoreddef(current_procinfo.procdef.rettype.def).numberstring+'",'+
+                   tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procinfo.procdef.funcretsym).adjusted_address))))
                 else
                   list.concat(Tai_stabs.Create(strpnew(
-                   '"'+current_procdef.procsym.name+':X'+tstoreddef(current_procdef.rettype.def).numberstring+'",'+
-                   tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procdef.funcretsym).adjusted_address))));
+                   '"'+current_procinfo.procdef.procsym.name+':X'+tstoreddef(current_procinfo.procdef.rettype.def).numberstring+'",'+
+                   tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procinfo.procdef.funcretsym).adjusted_address))));
                 if (m_result in aktmodeswitches) then
-                  if paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+                  if paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption) then
                     list.concat(Tai_stabs.Create(strpnew(
-                     '"RESULT:X*'+tstoreddef(current_procdef.rettype.def).numberstring+'",'+
-                     tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procdef.funcretsym).adjusted_address))))
+                     '"RESULT:X*'+tstoreddef(current_procinfo.procdef.rettype.def).numberstring+'",'+
+                     tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procinfo.procdef.funcretsym).adjusted_address))))
                   else
                     list.concat(Tai_stabs.Create(strpnew(
-                     '"RESULT:X'+tstoreddef(current_procdef.rettype.def).numberstring+'",'+
-                     tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procdef.funcretsym).adjusted_address))));
+                     '"RESULT:X'+tstoreddef(current_procinfo.procdef.rettype.def).numberstring+'",'+
+                     tostr(N_tsym)+',0,0,'+tostr(tvarsym(current_procinfo.procdef.funcretsym).adjusted_address))));
               end;
-            mangled_length:=length(current_procdef.mangledname);
+            mangled_length:=length(current_procinfo.procdef.mangledname);
             getmem(p,2*mangled_length+50);
             strpcopy(p,'192,0,0,');
-            strpcopy(strend(p),current_procdef.mangledname);
+            strpcopy(strend(p),current_procinfo.procdef.mangledname);
             if (target_info.use_function_relative_addresses) then
               begin
                 strpcopy(strend(p),'-');
-                strpcopy(strend(p),current_procdef.mangledname);
+                strpcopy(strend(p),current_procinfo.procdef.mangledname);
               end;
             list.concat(Tai_stabn.Create(strnew(p)));
             {List.concat(Tai_stabn.Create(strpnew('192,0,0,'
-             +current_procdef.mangledname))));
+             +current_procinfo.procdef.mangledname))));
             p[0]:='2';p[1]:='2';p[2]:='4';
             strpcopy(strend(p),'_end');}
             strpcopy(p,'224,0,0,'+stabsendlabel.name);
             if (target_info.use_function_relative_addresses) then
               begin
                 strpcopy(strend(p),'-');
-                strpcopy(strend(p),current_procdef.mangledname);
+                strpcopy(strend(p),current_procinfo.procdef.mangledname);
               end;
             list.concatlist(withdebuglist);
             list.concat(Tai_stabn.Create(strnew(p)));
              { strpnew('224,0,0,'
-             +current_procdef.mangledname+'_end'))));}
+             +current_procinfo.procdef.mangledname+'_end'))));}
             freemem(p,2*mangled_length+50);
           end;
 {$endif GDB}
@@ -1840,29 +1840,29 @@ implementation
         resloc: tlocation;
         r,r2 : tregister;
       begin
-        if not is_void(current_procdef.rettype.def) then
+        if not is_void(current_procinfo.procdef.rettype.def) then
          begin
-           ressym := tvarsym(current_procdef.funcretsym);
+           ressym := tvarsym(current_procinfo.procdef.funcretsym);
            if ressym.reg.enum <> R_NO then
              begin
-               if paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+               if paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption) then
                  location_reset(resloc,LOC_CREGISTER,OS_ADDR)
                else
                  if ressym.vartype.def.deftype = floatdef then
-                   location_reset(resloc,LOC_CFPUREGISTER,def_cgsize(current_procdef.rettype.def))
+                   location_reset(resloc,LOC_CFPUREGISTER,def_cgsize(current_procinfo.procdef.rettype.def))
                  else
-                   location_reset(resloc,LOC_CREGISTER,def_cgsize(current_procdef.rettype.def));
+                   location_reset(resloc,LOC_CREGISTER,def_cgsize(current_procinfo.procdef.rettype.def));
                resloc.register := ressym.reg;
              end
            else
              begin
-               location_reset(resloc,LOC_CREGISTER,def_cgsize(current_procdef.rettype.def));
-               reference_reset_base(resloc.reference,current_procinfo.framepointer,tvarsym(current_procdef.funcretsym).adjusted_address);
+               location_reset(resloc,LOC_CREGISTER,def_cgsize(current_procinfo.procdef.rettype.def));
+               reference_reset_base(resloc.reference,current_procinfo.framepointer,tvarsym(current_procinfo.procdef.funcretsym).adjusted_address);
              end;
            { Here, we return the function result. In most architectures, the value is
              passed into the FUNCTION_RETURN_REG, but in a windowed architecure like sparc a
              function returns in a register and the caller receives it in an other one }
-           case current_procdef.rettype.def.deftype of
+           case current_procinfo.procdef.rettype.def.deftype of
              orddef,
              enumdef :
                begin
@@ -1892,7 +1892,7 @@ implementation
                end;
              else
                begin
-                 if not paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+                 if not paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption) then
                   begin
 {$ifndef cpu64bit}
                     { Win32 can return records in EAX:EDX }
@@ -1920,18 +1920,18 @@ implementation
         { initialize return value }
         initretvalue(list);
 
-        current_procdef.localst.foreach_static({$ifndef TP}@{$endif}initialize_data,list);
+        current_procinfo.procdef.localst.foreach_static({$ifndef TP}@{$endif}initialize_data,list);
 
         { initialisizes temp. ansi/wide string data }
         inittempvariables(list);
 
         { initialize ansi/widesstring para's }
-        if assigned(current_procdef.parast) then
-          current_procdef.parast.foreach_static({$ifndef TP}@{$endif}init_paras,list);
+        if assigned(current_procinfo.procdef.parast) then
+          current_procinfo.procdef.parast.foreach_static({$ifndef TP}@{$endif}init_paras,list);
 
         { generate copies of call by value parameters }
-        if not(po_assembler in current_procdef.procoptions) then
-          current_procdef.parast.foreach_static({$ifndef TP}@{$endif}copyvalueparas,list);
+        if not(po_assembler in current_procinfo.procdef.procoptions) then
+          current_procinfo.procdef.parast.foreach_static({$ifndef TP}@{$endif}copyvalueparas,list);
 
         load_regvars(list,nil);
       end;
@@ -1951,19 +1951,19 @@ implementation
         { finalize temporary data }
         finalizetempvariables(list);
 
-        current_procdef.localst.foreach_static({$ifndef TP}@{$endif}finalize_data,list);
+        current_procinfo.procdef.localst.foreach_static({$ifndef TP}@{$endif}finalize_data,list);
 
         { finalize paras data }
-        if assigned(current_procdef.parast) then
-          current_procdef.parast.foreach_static({$ifndef TP}@{$endif}final_paras,list);
+        if assigned(current_procinfo.procdef.parast) then
+          current_procinfo.procdef.parast.foreach_static({$ifndef TP}@{$endif}final_paras,list);
 
         { handle return value, this is not done for assembler routines when
           they didn't reference the result variable }
-        if not(po_assembler in current_procdef.procoptions) or
-           (assigned(current_procdef.funcretsym) and
-            (tvarsym(current_procdef.funcretsym).refcount>1)) then
+        if not(po_assembler in current_procinfo.procdef.procoptions) or
+           (assigned(current_procinfo.procdef.funcretsym) and
+            (tvarsym(current_procinfo.procdef.funcretsym).refcount>1)) then
           begin
-            if (current_procdef.proctypeoption=potype_constructor) then
+            if (current_procinfo.procdef.proctypeoption=potype_constructor) then
              internalerror(200305263);
 //            load_inlined_return_value(list);
              load_return_value(list,usesacc,usesacchi,usesfpu)
@@ -1976,7 +1976,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.124  2003-06-09 12:23:30  peter
+  Revision 1.125  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.124  2003/06/09 12:23:30  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
@@ -2113,7 +2116,7 @@ end.
       could overwrite those registers)
 
   Revision 1.92  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -2122,7 +2125,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.91  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * 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

+ 9 - 6
compiler/nflw.pas

@@ -724,7 +724,7 @@ implementation
              (hp.nodetype=loadn) and
              (
               (tloadnode(hp).symtable.symtablelevel=main_program_level) or
-              (tloadnode(hp).symtable.symtablelevel=current_procdef.parast.symtablelevel)
+              (tloadnode(hp).symtable.symtablelevel=current_procinfo.procdef.parast.symtablelevel)
              ) and
              not(
                  (tloadnode(hp).symtableentry.typ=varsym) and
@@ -857,9 +857,9 @@ implementation
         if assigned(left) then
           begin
             { add assignment to funcretsym }
-            inserttypeconv(left,current_procdef.rettype);
+            inserttypeconv(left,current_procinfo.procdef.rettype);
             left:=cassignmentnode.create(
-                cloadnode.create(current_procdef.funcretsym,current_procdef.funcretsym.owner),
+                cloadnode.create(current_procinfo.procdef.funcretsym,current_procinfo.procdef.funcretsym.owner),
                 left);
             resulttypepass(left);
             set_varstate(left,true);
@@ -1429,7 +1429,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.77  2003-06-07 20:26:32  peter
+  Revision 1.78  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.77  2003/06/07 20:26:32  peter
     * re-resolving added instead of reloading from ppu
     * tderef object added to store deref info for resolving
 
@@ -1460,7 +1463,7 @@ end.
     * int64s/qwords are allowed as for loop counter on 64 bit CPUs
 
   Revision 1.71  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1469,7 +1472,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.70  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 6 - 3
compiler/ninl.pas

@@ -1388,7 +1388,7 @@ implementation
               in_sizeof_x:
                 begin
                   set_varstate(left,false);
-                  if paramanager.push_high_param(left.resulttype.def,current_procdef.proccalloption) then
+                  if paramanager.push_high_param(left.resulttype.def,current_procinfo.procdef.proccalloption) then
                    begin
                      hightree:=load_high_value_node(tvarsym(tloadnode(left).symtableentry));
                      if assigned(hightree) then
@@ -2351,7 +2351,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.113  2003-05-31 21:29:04  jonas
+  Revision 1.114  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.113  2003/05/31 21:29:04  jonas
     * constant evaluation of trunc() and round() now also gives 64 bit
       results
 
@@ -2369,7 +2372,7 @@ end.
     * removed hdisposen,hnewn,selfn
 
   Revision 1.109  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 8 - 5
compiler/nld.pas

@@ -471,7 +471,7 @@ implementation
             varsym :
               begin
                 if (symtable.symtabletype in [parasymtable,localsymtable]) and
-                   (current_procdef.parast.symtablelevel>symtable.symtablelevel) then
+                   (current_procinfo.procdef.parast.symtablelevel>symtable.symtablelevel) then
                   begin
                     { if the variable is in an other stackframe then we need
                       a register to dereference }
@@ -791,7 +791,7 @@ implementation
          if codegenerror then
            exit;
 
-         
+
         if (is_shortstring(left.resulttype.def)) then
           begin
            if right.resulttype.def.deftype=stringdef then
@@ -1286,7 +1286,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.101  2003-06-08 20:01:53  jonas
+  Revision 1.102  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.101  2003/06/08 20:01:53  jonas
     * optimized assignments with on the right side a function that returns
       an ansi- or widestring
 
@@ -1341,7 +1344,7 @@ end.
     * removed hdisposen,hnewn,selfn
 
   Revision 1.90  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1350,7 +1353,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.89  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 9 - 5
compiler/nutils.pas

@@ -61,6 +61,7 @@ implementation
       verbose,
       symconst,symsym,symtype,symdef,symtable,
       nbas,ncon,ncnv,nld,nflw,nset,ncal,nadd,nmem,
+      cgbase,
       pass_1;
 
   function foreachnode(var n: tnode; f: foreachnodefunction): boolean;
@@ -165,9 +166,9 @@ implementation
         result:=internalstatements(newstatement,true);
 
         { call fail helper and exit normal }
-        if is_class(current_procdef._class) then
+        if is_class(current_procinfo.procdef._class) then
           begin
-            srsym:=search_class_member(current_procdef._class,'FREEINSTANCE');
+            srsym:=search_class_member(current_procinfo.procdef._class,'FREEINSTANCE');
             if assigned(srsym) and
                (srsym.typ=procsym) then
               begin
@@ -189,13 +190,13 @@ implementation
               internalerror(200305108);
           end
         else
-          if is_object(current_procdef._class) then
+          if is_object(current_procinfo.procdef._class) then
             begin
               { parameter 3 : vmt_offset }
               { parameter 2 : pointer to vmt }
               { parameter 1 : self pointer }
               para:=ccallparanode.create(
-                        cordconstnode.create(current_procdef._class.vmt_offset,s32bittype,false),
+                        cordconstnode.create(current_procinfo.procdef._class.vmt_offset,s32bittype,false),
                     ccallparanode.create(
                         ctypeconvnode.create_explicit(
                             load_vmt_pointer_node,
@@ -253,7 +254,10 @@ end.
 
 {
   $Log$
-  Revision 1.5  2003-05-26 21:17:17  peter
+  Revision 1.6  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.5  2003/05/26 21:17:17  peter
     * procinlinenode removed
     * aktexit2label removed, fast exit removed
     + tcallnode.inlined_pass_2 added

+ 8 - 50
compiler/paramgr.pas

@@ -137,15 +137,12 @@ unit paramgr;
        end;
 
 
-
-    procedure setparalocs(p : tprocdef);
-    function getfuncretusedregisters(def : tdef;calloption:tproccalloption): tregisterset;
-
     var
        paralocdummy : tparalocation;
        paramanager : tparamanager;
 
-  implementation
+
+implementation
 
     uses
        cpuinfo,globals,systems,
@@ -408,48 +405,6 @@ unit paramgr;
       end;
 
 
-    function getfuncretusedregisters(def : tdef;calloption:tproccalloption): tregisterset;
-      var
-        paramloc : tparalocation;
-        regset : tregisterset;
-      begin
-        regset:=[];
-        getfuncretusedregisters:=[];
-        { if nothing is returned in registers,
-          its useless to continue on in this
-          routine
-        }
-        if paramanager.ret_in_param(def,calloption) then
-          exit;
-        paramloc := paramanager.getfuncresultloc(def,calloption);
-        case paramloc.loc of
-          LOC_FPUREGISTER,
-          LOC_CFPUREGISTER,
-          LOC_MMREGISTER,
-          LOC_CMMREGISTER,
-          LOC_REGISTER,LOC_CREGISTER :
-              begin
-                regset := regset + [paramloc.register.enum];
-                if ((paramloc.size in [OS_S64,OS_64]) and
-                   (sizeof(aword) < 8))
-                then
-                  begin
-                     regset := regset + [paramloc.registerhigh.enum];
-                  end;
-              end;
-          else
-            internalerror(20020816);
-        end;
-        getfuncretusedregisters:=regset;
-      end;
-
-    procedure setparalocs(p : tprocdef);
-
-      var
-         hp : tparaitem;
-
-      begin
-      end;
 
 initialization
   ;
@@ -459,7 +414,10 @@ end.
 
 {
    $Log$
-   Revision 1.44  2003-06-12 21:11:10  peter
+   Revision 1.45  2003-06-13 21:19:30  peter
+     * current_procdef removed, use current_procinfo.procdef instead
+
+   Revision 1.44  2003/06/12 21:11:10  peter
      * ungetregisterfpu gets size parameter
 
    Revision 1.43  2003/06/09 14:54:26  jonas
@@ -498,7 +456,7 @@ end.
      * tparamanager.ret_in_acc doesn't return true anymore for a void-def
 
    Revision 1.36  2003/04/27 11:21:33  peter
-     * aktprocdef renamed to current_procdef
+     * 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
@@ -507,7 +465,7 @@ end.
      * fixed unit implicit initfinal
 
    Revision 1.35  2003/04/27 07:29:50  peter
-     * current_procdef cleanup, current_procdef is now always nil when parsing
+     * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
        a new procdef declaration
      * aktprocsym removed
      * lexlevel removed, use symtable.symtablelevel instead

+ 10 - 9
compiler/parser.pas

@@ -67,9 +67,7 @@ implementation
          { and no function header                        }
          testcurobject:=0;
 
-         { Symtable }
-         current_procdef:=nil;
-
+         { Current compiled module/proc }
          objectlibrary:=nil;
          current_module:=nil;
          compiled_module:=nil;
@@ -255,7 +253,6 @@ implementation
           olddefaultsymtablestack,
           oldsymtablestack : tsymtable;
           oldaktprocsym    : tprocsym;
-          oldcurrent_procdef    : tprocdef;
           oldoverloaded_operators : toverloaded_operators;
         { cg }
           oldparse_only  : boolean;
@@ -288,6 +285,7 @@ implementation
           oldaktinterfacetype: tinterfacetypes;
           oldaktmodeswitches : tmodeswitches;
           old_compiled_module : tmodule;
+          oldcurrent_procinfo : tprocinfo;
           oldaktdefproccall : tproccalloption;
           oldsourcecodepage : tcodepagestring;
 {$ifdef GDB}
@@ -317,7 +315,7 @@ implementation
             oldsymtablestack:=symtablestack;
             olddefaultsymtablestack:=defaultsymtablestack;
             oldrefsymtable:=refsymtable;
-            oldcurrent_procdef:=current_procdef;
+            oldcurrent_procinfo:=current_procinfo;
             oldaktdefproccall:=aktdefproccall;
             move(overloaded_operators,oldoverloaded_operators,sizeof(toverloaded_operators));
           { save scanner state }
@@ -532,7 +530,7 @@ implementation
                  symtablestack:=oldsymtablestack;
                  defaultsymtablestack:=olddefaultsymtablestack;
                  aktdefproccall:=oldaktdefproccall;
-                 current_procdef:=oldcurrent_procdef;
+                 current_procinfo:=oldcurrent_procinfo;
                  move(oldoverloaded_operators,overloaded_operators,sizeof(toverloaded_operators));
                  aktsourcecodepage:=oldsourcecodepage;
                  aktlocalswitches:=oldaktlocalswitches;
@@ -621,7 +619,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.54  2003-06-12 16:41:51  peter
+  Revision 1.55  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.54  2003/06/12 16:41:51  peter
     * add inputfile prefix to ppas/link.res
 
   Revision 1.53  2003/05/15 18:58:53  peter
@@ -631,7 +632,7 @@ end.
     * removed some obsolete globals
 
   Revision 1.52  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -640,7 +641,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.51  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 6 - 7
compiler/pass_2.pas

@@ -273,10 +273,6 @@ implementation
          if ErrorCount=0 then
            begin
               { assign parameter locations }
-{$ifndef i386}
-              setparalocs(current_procinfo.procdef);
-{$endif i386}
-
               current_procinfo.after_pass1;
 
               { process register variable stuff (JM) }
@@ -304,7 +300,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.56  2003-06-12 16:43:07  peter
+  Revision 1.57  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.56  2003/06/12 16:43:07  peter
     * newra compiles for sparc
 
   Revision 1.55  2003/06/09 12:23:30  peter
@@ -335,7 +334,7 @@ end.
     * removed hdisposen,hnewn,selfn
 
   Revision 1.49  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -344,7 +343,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.48  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 7 - 4
compiler/pdecobj.pas

@@ -52,7 +52,7 @@ implementation
       { Please leave this here, this module should NOT use
         these variables.
         Declaring it as string here results in an error when compiling (PFV) }
-      current_procdef = 'error';
+      current_procinfo = 'error';
 
 
     function object_dec(const n : stringid;fd : tobjectdef) : tdef;
@@ -1138,7 +1138,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.66  2003-05-23 14:27:35  peter
+  Revision 1.67  2003-06-13 21:19:30  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.66  2003/05/23 14:27:35  peter
     * remove some unit dependencies
     * current_procinfo changes to store more info
 
@@ -1150,7 +1153,7 @@ end.
     * vs_hidden replaced by is_hidden boolean
 
   Revision 1.63  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1159,7 +1162,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.62  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 7 - 4
compiler/pdecsub.pas

@@ -93,7 +93,7 @@ implementation
       { Please leave this here, this module should NOT use
         these variables.
         Declaring it as string here results in an error when compiling (PFV) }
-      current_procdef = 'error';
+      current_procinfo = 'error';
 
 
     procedure insert_funcret_para(pd:tabstractprocdef);
@@ -2171,7 +2171,10 @@ const
 end.
 {
   $Log$
-  Revision 1.127  2003-06-05 20:04:43  peter
+  Revision 1.128  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.127  2003/06/05 20:04:43  peter
     * set po_public also when parsing the object declaration
 
   Revision 1.126  2003/06/02 21:42:05  jonas
@@ -2202,7 +2205,7 @@ end.
     + first changes to make self a hidden parameter
 
   Revision 1.119  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -2211,7 +2214,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.118  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 26 - 21
compiler/pexpr.pas

@@ -287,7 +287,8 @@ implementation
                     consume(_RKLAMMER);
                     if (block_type=bt_except) then
                       Message(parser_e_exit_with_argument_not__possible);
-                    if is_void(current_procdef.rettype.def) then
+                    if (not assigned(current_procinfo) or
+                        is_void(current_procinfo.procdef.rettype.def)) then
                       Message(parser_e_void_function);
                  end
                else
@@ -719,9 +720,9 @@ implementation
              para:=nil;
              if anon_inherited then
               begin
-                if not assigned(current_procdef) then
+                if not assigned(current_procinfo) then
                   internalerror(200305054);
-                currpara:=tparaitem(current_procdef.para.first);
+                currpara:=tparaitem(current_procinfo.procdef.para.first);
                 while assigned(currpara) do
                  begin
                    if not currpara.is_hidden then
@@ -1168,8 +1169,8 @@ implementation
                          also has objectsymtable. And withsymtable is
                          not possible for self in class methods (PFV) }
                        if (srsymtable.symtabletype=objectsymtable) and
-                          assigned(current_procdef) and
-                          (po_classmethod in current_procdef.procoptions) then
+                          assigned(current_procinfo) and
+                          (po_classmethod in current_procinfo.procdef.procoptions) then
                          Message(parser_e_only_class_methods);
                      end;
 
@@ -1221,11 +1222,11 @@ implementation
                            is_object(htype.def) then
                          begin
                            consume(_POINT);
-                           if assigned(current_procdef) and
-                              assigned(current_procdef._class) and
+                           if assigned(current_procinfo) and
+                              assigned(current_procinfo.procdef._class) and
                               not(getaddr) then
                             begin
-                              if current_procdef._class.is_related(tobjectdef(htype.def)) then
+                              if current_procinfo.procdef._class.is_related(tobjectdef(htype.def)) then
                                begin
                                  p1:=ctypenode.create(htype);
                                  { search also in inherited methods }
@@ -1359,8 +1360,8 @@ implementation
                     { are we in a class method ? }
                     possible_error:=(srsym.owner.symtabletype=objectsymtable) and
                                     not(is_interface(tdef(srsym.owner.defowner))) and
-                                    assigned(current_procdef) and
-                                    (po_classmethod in current_procdef.procoptions);
+                                    assigned(current_procinfo) and
+                                    (po_classmethod in current_procinfo.procdef.procoptions);
                     do_proc_call(srsym,srsymtable,
                                  (getaddr and not(token in [_CARET,_POINT])),
                                  again,p1);
@@ -1378,8 +1379,8 @@ implementation
                     { access to property in a method }
                     { are we in a class method ? }
                     if (srsym.owner.symtabletype=objectsymtable) and
-                       assigned(current_procdef) and
-                       (po_classmethod in current_procdef.procoptions) then
+                       assigned(current_procinfo) and
+                       (po_classmethod in current_procinfo.procdef.procoptions) then
                      Message(parser_e_only_class_methods);
                     { no method pointer }
                     p1:=nil;
@@ -1825,8 +1826,8 @@ implementation
              begin
                again:=true;
                consume(_SELF);
-               if not(assigned(current_procdef) and
-                      assigned(current_procdef._class)) then
+               if not(assigned(current_procinfo) and
+                      assigned(current_procinfo.procdef._class)) then
                 begin
                   p1:=cerrornode.create;
                   again:=false;
@@ -1843,18 +1844,19 @@ implementation
              begin
                again:=true;
                consume(_INHERITED);
-               if assigned(current_procdef._class) then
+               if assigned(current_procinfo) and
+                  assigned(current_procinfo.procdef._class) then
                 begin
-                  classh:=current_procdef._class.childof;
+                  classh:=current_procinfo.procdef._class.childof;
                   { if inherited; only then we need the method with
                     the same name }
                   if token in endtokens then
                    begin
-                     hs:=current_procdef.procsym.name;
+                     hs:=current_procinfo.procdef.procsym.name;
                      anon_inherited:=true;
                      { For message methods we need to search using the message
                        number or string }
-                     pd:=tprocsym(current_procdef.procsym).first_procdef;
+                     pd:=tprocsym(current_procinfo.procdef.procsym).first_procdef;
                      if (po_msgint in pd.procoptions) then
                       sym:=searchsym_in_class_by_msgint(classh,pd.messageinf.i)
                      else
@@ -2410,7 +2412,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.122  2003-06-03 21:02:57  peter
+  Revision 1.123  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.122  2003/06/03 21:02:57  peter
     * don't set nf_member when loaded from with symtable
     * allow static variables in class methods
 
@@ -2450,7 +2455,7 @@ end.
     * int64s/qwords are allowed as for loop counter on 64 bit CPUs
 
   Revision 1.113  2003/04/27 11:21:33  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -2459,7 +2464,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.112  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 12 - 13
compiler/pmodules.pas

@@ -465,15 +465,13 @@ implementation
 
     procedure loadunits;
       var
-         s,sorg : stringid;
-         fn     : string;
-         pu     : tused_unit;
-         hp2    : tmodule;
-         hp3    : tsymtable;
-         oldprocdef : tprocdef;
+         s,sorg  : stringid;
+         fn      : string;
+         pu      : tused_unit;
+         hp2     : tmodule;
+         hp3     : tsymtable;
          unitsym : tunitsym;
       begin
-         oldprocdef:=current_procdef;
          consume(_USES);
 {$ifdef DEBUG}
          test_symtablestack;
@@ -596,7 +594,6 @@ implementation
                 end;
               pu:=tused_unit(pu.next);
            end;
-          current_procdef:=oldprocdef;
       end;
 
 
@@ -724,11 +721,10 @@ implementation
           symtable }
         pd.localst.free;
         pd.localst:=st;
-        { set procinfo and current_procdef }
+        { set procinfo and current_procinfo.procdef }
         current_procinfo:=cprocinfo.create(nil);
         current_module.procinfo:=current_procinfo;
         current_procinfo.procdef:=pd;
-        current_procdef:=pd;
         { return procdef }
         create_main_proc:=pd;
       end;
@@ -1456,7 +1452,10 @@ So, all parameters are passerd into registers in sparc architecture.}
 end.
 {
   $Log$
-  Revision 1.113  2003-06-09 12:23:30  peter
+  Revision 1.114  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.113  2003/06/09 12:23:30  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
@@ -1496,7 +1495,7 @@ end.
     * fix stabs generation for implicit initfinal
 
   Revision 1.103  2003/04/27 11:21:34  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1505,7 +1504,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.102  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 35 - 32
compiler/powerpc/cgcpu.pas

@@ -987,7 +987,7 @@ const
         r.number:=NR_R0;
         a_reg_alloc(list,r);
 
-        if current_procdef.parast.symtablelevel>1 then
+        if current_procinfo.procdef.parast.symtablelevel>1 then
           begin
              r.enum:=R_INTREGISTER;
              r.number:=NR_R11;
@@ -996,9 +996,9 @@ const
 
 
         usesfpr:=false;
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
           for regcounter.enum:=R_F14 to R_F31 do
-            if regcounter.enum in rg.usedbyproc then
+            if regcounter.enum in rg.used_in_proc_other then
               begin
                 usesfpr:= true;
                 firstregfpu:=regcounter;
@@ -1006,10 +1006,10 @@ const
               end;
 
         usesgpr:=false;
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
           for regcounter2:=firstsaveintreg to RS_R31 do
             begin
-              if regcounter2 in rg.usedintbyproc then
+              if regcounter2 in rg.used_in_proc_int then
                 begin
                    usesgpr:=true;
                    firstreggpr.enum := R_INTREGISTER;
@@ -1019,7 +1019,7 @@ const
             end;
 
         { save link register? }
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
           if (pi_do_call in current_procinfo.flags) then
             begin
                { save return address... }
@@ -1033,7 +1033,7 @@ const
             end;
 
         { !!! always allocate space for all registers for now !!! }
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
 {        if usesfpr or usesgpr then }
           begin
              r.enum:=R_INTREGISTER;
@@ -1051,7 +1051,7 @@ const
           inc(localsize,(ord(R_F31)-ord(firstregfpu.enum)+1)*8);
 }
         { !!! always allocate space for all registers for now !!! }
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
           inc(localsize,(31-13+1)*4+(31-14+1)*8);
 
         { align to 16 bytes }
@@ -1099,7 +1099,7 @@ const
              }
              reference_reset_base(href,r,-8);
              for regcounter.enum:=firstregfpu.enum to R_F31 do
-               if regcounter.enum in rg.usedbyproc then
+               if regcounter.enum in rg.used_in_proc_other then
                  begin
                     a_loadfpu_reg_ref(list,OS_F64,regcounter,href);
                     dec(href.offset,8);
@@ -1124,7 +1124,7 @@ const
             reference_reset_base(href,r,-4);
             for regcounter2:=firstsaveintreg to RS_R31 do
               begin
-                if regcounter2 in rg.usedintbyproc then
+                if regcounter2 in rg.used_in_proc_int then
                   begin
                      usesgpr:=true;
                      r.enum := R_INTREGISTER;
@@ -1141,14 +1141,14 @@ const
 }
           end;
 
-        if assigned(current_procdef.parast) then
+        if assigned(current_procinfo.procdef.parast) then
           begin
-            if not (po_assembler in current_procdef.procoptions) then
+            if not (po_assembler in current_procinfo.procdef.procoptions) then
               begin
                 { copy memory parameters to local parast }
                 r.enum:=R_INTREGISTER;
                 r.number:=NR_R12;
-                hp:=tparaitem(current_procdef.para.first);
+                hp:=tparaitem(current_procinfo.procdef.para.first);
                 while assigned(hp) do
                   begin
                     if (hp.paraloc.loc in [LOC_REFERENCE,LOC_CREFERENCE]) then
@@ -1192,7 +1192,7 @@ const
         { now comes the AltiVec context save, not yet implemented !!! }
 
         { if we're in a nested procedure, we've to save R11 }
-        if current_procdef.parast.symtablelevel>2 then
+        if current_procinfo.procdef.parast.symtablelevel>2 then
           begin
              r.enum:=R_INTREGISTER;
              r.number:=NR_R11;
@@ -1223,9 +1223,9 @@ const
         { AltiVec context restore, not yet implemented !!! }
 
         usesfpr:=false;
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
           for regcounter.enum:=R_F14 to R_F31 do
-            if regcounter.enum in rg.usedbyproc then
+            if regcounter.enum in rg.used_in_proc_other then
               begin
                  usesfpr:=true;
                  firstregfpu:=regcounter;
@@ -1233,10 +1233,10 @@ const
               end;
 
         usesgpr:=false;
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
           for regcounter2:=firstsaveintreg to RS_R31 do
             begin
-              if regcounter2 in rg.usedintbyproc then
+              if regcounter2 in rg.used_in_proc_int then
                 begin
                   usesgpr:=true;
                   firstreggpr.enum:=R_INTREGISTER;
@@ -1245,7 +1245,7 @@ const
                 end;
             end;
 
-        if not (po_assembler in current_procdef.procoptions) then
+        if not (po_assembler in current_procinfo.procdef.procoptions) then
           inc(localsize,(31-13+1)*4+(31-14+1)*8);
 
         { align to 16 bytes }
@@ -1272,7 +1272,7 @@ const
                begin
                  reference_reset_base(href,r2,-8);
                  for regcounter.enum := firstregfpu.enum to R_F31 do
-                   if (regcounter.enum in rg.usedbyproc) then
+                   if (regcounter.enum in rg.used_in_proc_other) then
                      begin
                        a_loadfpu_ref_reg(list,OS_F64,href,regcounter);
                        dec(href.offset,8);
@@ -1284,7 +1284,7 @@ const
 
             for regcounter2:=firstsaveintreg to RS_R31 do
               begin
-                if regcounter2 in rg.usedintbyproc then
+                if regcounter2 in rg.used_in_proc_int then
                   begin
                      usesgpr:=true;
                      r.enum := R_INTREGISTER;
@@ -1329,7 +1329,7 @@ const
              r.number:=NR_R1;
              a_op_const_reg(list,OP_ADD,OS_ADDR,tppcprocinfo(current_procinfo).localsize,r);
              { load link register? }
-             if not (po_assembler in current_procdef.procoptions) then
+             if not (po_assembler in current_procinfo.procdef.procoptions) then
                if (pi_do_call in current_procinfo.flags) then
                  begin
                     r.enum:=R_INTREGISTER;
@@ -1358,9 +1358,9 @@ const
 
     begin
       usesfpr:=false;
-      if not (po_assembler in current_procdef.procoptions) then
+      if not (po_assembler in current_procinfo.procdef.procoptions) then
         for regcounter.enum:=R_F14 to R_F31 do
-          if regcounter.enum in rg.usedbyproc then
+          if regcounter.enum in rg.used_in_proc_other then
             begin
                usesfpr:=true;
                firstregfpu:=regcounter;
@@ -1368,10 +1368,10 @@ const
             end;
 
       usesgpr:=false;
-      if not (po_assembler in current_procdef.procoptions) then
+      if not (po_assembler in current_procinfo.procdef.procoptions) then
         for regcounter2:=firstsaveintreg to RS_R31 do
           begin
-            if regcounter2 in rg.usedintbyproc then
+            if regcounter2 in rg.used_in_proc_int then
               begin
                  usesgpr:=true;
                  firstreggpr.enum:=R_INTREGISTER;
@@ -1437,9 +1437,9 @@ const
 
     begin
       usesfpr:=false;
-      if not (po_assembler in current_procdef.procoptions) then
+      if not (po_assembler in current_procinfo.procdef.procoptions) then
         for regcounter.enum:=R_F14 to R_F31 do
-          if regcounter.enum in rg.usedbyproc then
+          if regcounter.enum in rg.used_in_proc_other then
             begin
                usesfpr:=true;
                firstregfpu:=regcounter;
@@ -1447,10 +1447,10 @@ const
             end;
 
       usesgpr:=false;
-      if not (po_assembler in current_procdef.procoptions) then
+      if not (po_assembler in current_procinfo.procdef.procoptions) then
         for regcounter2:=RS_R13 to RS_R31 do
           begin
-            if regcounter2 in rg.usedintbyproc then
+            if regcounter2 in rg.used_in_proc_int then
               begin
                  usesgpr:=true;
                  firstreggpr.enum:=R_INTREGISTER;
@@ -2532,7 +2532,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.107  2003-06-09 14:54:26  jonas
+  Revision 1.108  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.107  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
@@ -2618,7 +2621,7 @@ end.
     * fixed optimizations in a_op_const_reg_reg()
 
   Revision 1.86  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 5 - 2
compiler/powerpc/cpupi.pas

@@ -98,7 +98,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.22  2003-06-02 21:42:05  jonas
+  Revision 1.23  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.22  2003/06/02 21:42:05  jonas
     * function results can now also be regvars
     - removed tprocinfo.return_offset, never use it again since it's invalid
       if the result is a regvar
@@ -137,7 +140,7 @@ end.
     * call inherited after_header as well
 
   Revision 1.12  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 9 - 6
compiler/powerpc/nppccal.pas

@@ -77,7 +77,7 @@ implementation
        hregister1,hregister2 : tregister;
        i : longint;
     begin
-       if current_procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel) then
+       if current_procinfo.procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel) then
          begin
             { pass the same framepointer as the current procedure got }
             hregister2.enum:=R_INTREGISTER;
@@ -88,7 +88,7 @@ implementation
          end
          { this is only true if the difference is one !!
            but it cannot be more !! }
-       else if (current_procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel)-1) then
+       else if (current_procinfo.procdef.parast.symtablelevel=(tprocdef(procdefinition).parast.symtablelevel)-1) then
          begin
             { pass the same framepointer as the current procedure got }
             hregister1.enum:=R_INTREGISTER;
@@ -97,7 +97,7 @@ implementation
             hregister2.number:=NR_R11;
             cg.a_load_reg_reg(exprasmlist,OS_32,OS_32,hregister1,hregister2);
          end
-       else if (current_procdef.parast.symtablelevel>(tprocdef(procdefinition).parast.symtablelevel)) then
+       else if (current_procinfo.procdef.parast.symtablelevel>(tprocdef(procdefinition).parast.symtablelevel)) then
          begin
             hregister1:=rg.getregisterint(exprasmlist,OS_ADDR);
             reference_reset_base(href,current_procinfo.framepointer,current_procinfo.framepointer_offset);
@@ -105,7 +105,7 @@ implementation
             { the previous frame pointer is always saved at }
             { previous_framepointer+12 (in the link area)   }
             reference_reset_base(href,hregister1,12);
-            i:=current_procdef.parast.symtablelevel-1;
+            i:=current_procinfo.procdef.parast.symtablelevel-1;
             while (i>tprocdef(procdefinition).parast.symtablelevel) do
               begin
                  cg.a_load_ref_reg(exprasmlist,OS_ADDR,OS_ADDR,href,hregister1);
@@ -125,7 +125,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.17  2003-06-04 11:58:58  jonas
+  Revision 1.18  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.17  2003/06/04 11:58:58  jonas
     * calculate localsize also in g_return_from_proc since it's now called
       before g_stackframe_entry (still have to fix macos)
     * compilation fixes (cycle doesn't work yet though)
@@ -154,7 +157,7 @@ end.
       nested procedures are declared
 
   Revision 1.10  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 23 - 20
compiler/powerpc/radirect.pas

@@ -97,9 +97,9 @@ interface
            if s<>'' then
             code.concat(Tai_direct.Create(strpnew(s)));
             { consider it set function set if the offset was loaded }
-           if assigned(current_procdef.funcretsym) and
+           if assigned(current_procinfo.procdef.funcretsym) and
               (pos(retstr,upper(s))>0) then
-             tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+             tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
            s:='';
          end;
 
@@ -109,12 +109,12 @@ interface
        framereg.number:=NR_STACK_POINTER_REG;
        convert_register_to_enum(framereg);
        s:='';
-       if assigned(current_procdef.funcretsym) and
-          is_fpu(current_procdef.rettype.def) then
-         tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+       if assigned(current_procinfo.procdef.funcretsym) and
+          is_fpu(current_procinfo.procdef.rettype.def) then
+         tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
        { !!!!!
-       if (not is_void(current_procdef.rettype.def)) then
-         retstr:=upper(tostr(tvarsym(current_procdef.funcretsym).adjusted_address)+'('+gas_reg2str[procinfo^.framepointer]+')')
+       if (not is_void(current_procinfo.procdef.rettype.def)) then
+         retstr:=upper(tostr(tvarsym(current_procinfo.procdef.funcretsym).adjusted_address)+'('+gas_reg2str[procinfo^.framepointer]+')')
        else
        }
          retstr:='';
@@ -159,7 +159,7 @@ interface
                            end
                          else
                            { access to local variables }
-                           if assigned(current_procdef) then
+                           if assigned(current_procinfo.procdef) then
                              begin
                                 { I don't know yet, what the ppc port requires }
                                 { we'll see how things settle down             }
@@ -168,16 +168,16 @@ interface
                                 { char ?                                   }
                                 { !!!
                                 if (s[length(s)]='%') and
-                                   ret_in_acc(current_procdef.rettype.def) and
+                                   ret_in_acc(current_procinfo.procdef.rettype.def) and
                                    ((pos('AX',upper(hs))>0) or
                                    (pos('AL',upper(hs))>0)) then
-                                  tfuncretsym(current_procdef.funcretsym).funcretstate:=vs_assigned;
+                                  tfuncretsym(current_procinfo.procdef.funcretsym).funcretstate:=vs_assigned;
                                 }
                                 if ((s[length(s)]<>'0') or (hs[1]<>'x')) and not(is_register(hs)) then
                                   begin
-                                     if assigned(current_procdef.localst) and
-                                        (current_procdef.localst.symtablelevel >= normal_function_level) then
-                                       sym:=tsym(current_procdef.localst.search(upper(hs)))
+                                     if assigned(current_procinfo.procdef.localst) and
+                                        (current_procinfo.procdef.localst.symtablelevel >= normal_function_level) then
+                                       sym:=tsym(current_procinfo.procdef.localst.search(upper(hs)))
                                      else
                                        sym:=nil;
                                      if assigned(sym) then
@@ -209,8 +209,8 @@ interface
                                        end
                                      else
                                        begin
-                                          if assigned(current_procdef.parast) then
-                                            sym:=tsym(current_procdef.parast.search(upper(hs)))
+                                          if assigned(current_procinfo.procdef.parast) then
+                                            sym:=tsym(current_procinfo.procdef.parast.search(upper(hs)))
                                           else
                                             sym:=nil;
                                           if assigned(sym) then
@@ -219,7 +219,7 @@ interface
                                                  begin
                                                     l:=tvarsym(sym).address;
                                                     { set offset }
-                                                    inc(l,current_procdef.parast.address_fixup);
+                                                    inc(l,current_procinfo.procdef.parast.address_fixup);
 //                                                    hs:=tostr(l)+'('+gas_reg2str[procinfo.framepointer.enum]+')';
                                                     hs:=tostr(l)+'('+gas_reg2str[framereg.enum]+')';
                                                     if pos(',',s) > 0 then
@@ -285,7 +285,7 @@ interface
                                                  end
                                                else if upper(hs)='__RESULT' then
                                                  begin
-                                                    if (not is_void(current_procdef.rettype.def)) then
+                                                    if (not is_void(current_procinfo.procdef.rettype.def)) then
                                                       hs:=retstr
                                                     else
                                                       Message(asmr_e_void_function);
@@ -315,7 +315,7 @@ interface
               '{',';',#10,#13:
                 begin
                    if pos(retstr,s) > 0 then
-                     tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+                     tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
                    writeasmline;
                    c:=current_scanner.asmgetchar;
                 end;
@@ -351,7 +351,10 @@ initialization
 end.
 {
   $Log$
-  Revision 1.15  2003-06-02 21:42:05  jonas
+  Revision 1.16  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.15  2003/06/02 21:42:05  jonas
     * function results can now also be regvars
     - removed tprocinfo.return_offset, never use it again since it's invalid
       if the result is a regvar
@@ -362,7 +365,7 @@ end.
       function_result_reg (caller)
 
   Revision 1.13  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 34 - 31
compiler/pstatmnt.pas

@@ -416,8 +416,8 @@ implementation
               hp:=tunarynode(hp).left;
             if (hp.nodetype=loadn) and
                (
-                (tloadnode(hp).symtable=current_procdef.localst) or
-                (tloadnode(hp).symtable=current_procdef.parast) or
+                (tloadnode(hp).symtable=current_procinfo.procdef.localst) or
+                (tloadnode(hp).symtable=current_procinfo.procdef.parast) or
                 (tloadnode(hp).symtable.symtabletype in [staticsymtable,globalsymtable])
                ) then
              begin
@@ -776,7 +776,7 @@ implementation
       var
         asmstat : tasmnode;
         Marker  : tai;
-        r       : tregister;
+        reg     : tsuperregister;
         found   : boolean;
         hs      : string;
       begin
@@ -801,11 +801,11 @@ implementation
              begin
                if not target_asm.allowdirect then
                  Message(parser_f_direct_assembler_not_allowed);
-               if (current_procdef.proccalloption=pocall_inline) then
+               if (current_procinfo.procdef.proccalloption=pocall_inline) then
                  Begin
                     Message1(parser_w_not_supported_for_inline,'direct asm');
                     Message(parser_w_inlining_disabled);
-                    current_procdef.proccalloption:=pocall_fpccall;
+                    current_procinfo.procdef.proccalloption:=pocall_fpccall;
                  End;
                asmstat:=tasmnode(radirect.assemble);
              end;
@@ -816,20 +816,20 @@ implementation
          { Read first the _ASM statement }
          consume(_ASM);
 
-         { END is read }
+         { END is read, got a list of changed registers? }
          if try_to_consume(_LECKKLAMMER) then
            begin
+             rg.used_in_proc_other:=ALL_OTHERREGISTERS;
              if token<>_RECKKLAMMER then
               begin
                 repeat
                   { it's possible to specify the modified registers }
                   hs:=upper(pattern);
                   found:=false;
-                  for r.enum:=firstreg to lastreg do
-                   if hs=upper(std_reg2str[r.enum]) then
+                  for reg:=first_supreg to last_supreg do
+                   if hs=upper(supreg_name(reg)) then
                     begin
-                      include(rg.usedinproc,r.enum);
-                      include(rg.usedbyproc,r.enum);
+                      include(rg.used_in_proc_int,reg);
                       found:=true;
                       break;
                     end;
@@ -844,8 +844,8 @@ implementation
            end
          else
            begin
-              rg.usedbyproc := ALL_REGISTERS;
-              rg.usedinproc := ALL_REGISTERS;
+              rg.used_in_proc_int:=ALL_INTREGISTERS;
+              rg.used_in_proc_other:=ALL_OTHERREGISTERS;
            end;
 
          { mark the start and the end of the assembler block
@@ -939,7 +939,7 @@ implementation
              code:=cnothingnode.create;
            _FAIL :
              begin
-                if (current_procdef.proctypeoption<>potype_constructor) then
+                if (current_procinfo.procdef.proctypeoption<>potype_constructor) then
                   Message(parser_e_fail_only_in_constructor);
                 consume(_FAIL);
                 code:=call_fail_node;
@@ -1075,12 +1075,12 @@ implementation
         current_procinfo.framepointer.enum:=R_INTREGISTER;
         current_procinfo.framepointer.number:=NR_STACK_POINTER_REG;
         { set the right value for parameters }
-        dec(current_procdef.parast.address_fixup,pointer_size);
+        dec(current_procinfo.procdef.parast.address_fixup,pointer_size);
         { replace all references to parameters in the instructions,
           the parameters can be identified by the parafixup option
           that is set. For normal user coded [ebp+4] this field is not
           set }
-        parafixup:=current_procdef.parast.address_fixup;
+        parafixup:=current_procinfo.procdef.parast.address_fixup;
         hp:=tai(p.p_asm.first);
         while assigned(hp) do
          begin
@@ -1131,8 +1131,8 @@ implementation
         p : tnode;
       begin
          { Rename the funcret so that recursive calls are possible }
-         if not is_void(current_procdef.rettype.def) then
-           symtablestack.rename(current_procdef.resultname,'$hiddenresult');
+         if not is_void(current_procinfo.procdef.rettype.def) then
+           symtablestack.rename(current_procinfo.procdef.resultname,'$hiddenresult');
 
          { force the asm statement }
          if token<>_ASM then
@@ -1149,19 +1149,19 @@ implementation
            - target processor has optional frame pointer save
              (vm, i386, vm only currently)
          }
-         if (po_assembler in current_procdef.procoptions) and
+         if (po_assembler in current_procinfo.procdef.procoptions) and
 {$ifndef powerpc}
             { is this really necessary??? }
-            (current_procdef.parast.datasize=0) and
+            (current_procinfo.procdef.parast.datasize=0) and
 {$endif powerpc}
-            (current_procdef.localst.datasize=current_procdef.rettype.def.size) and
-            (current_procdef.owner.symtabletype<>objectsymtable) and
-            (not assigned(current_procdef.funcretsym) or
-             (tvarsym(current_procdef.funcretsym).refcount<=1)) and
-            not(paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption)) then
+            (current_procinfo.procdef.localst.datasize=current_procinfo.procdef.rettype.def.size) and
+            (current_procinfo.procdef.owner.symtabletype<>objectsymtable) and
+            (not assigned(current_procinfo.procdef.funcretsym) or
+             (tvarsym(current_procinfo.procdef.funcretsym).refcount<=1)) and
+            not(paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption)) then
             begin
                { we don't need to allocate space for the locals }
-               current_procdef.localst.datasize:=0;
+               current_procinfo.procdef.localst.datasize:=0;
                current_procinfo.firsttemp_offset:=0;
                { only for cpus with different frame- and stack pointer the code must be changed }
                if (NR_STACK_POINTER_REG<>NR_FRAME_POINTER_REG)
@@ -1175,9 +1175,9 @@ implementation
         { Flag the result as assigned when it is returned in a
           register.
         }
-        if assigned(current_procdef.funcretsym) and
-           (not paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption)) then
-          tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+        if assigned(current_procinfo.procdef.funcretsym) and
+           (not paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption)) then
+          tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
 
         { because the END is already read we need to get the
           last_endtoken_filepos here (PFV) }
@@ -1189,7 +1189,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.103  2003-06-09 18:27:14  peter
+  Revision 1.104  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.103  2003/06/09 18:27:14  peter
     * load calln in temprefn in with statement
 
   Revision 1.102  2003/05/23 22:33:48  florian
@@ -1229,7 +1232,7 @@ end.
     * tparamanager.ret_in_acc doesn't return true anymore for a void-def
 
   Revision 1.94  2003/04/27 11:21:34  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1238,7 +1241,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.93  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * 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

+ 54 - 68
compiler/psub.pas

@@ -133,10 +133,10 @@ implementation
          { do we have an assembler block without the po_assembler?
            we should allow this for Delphi compatibility (PFV) }
          if (token=_ASM) and (m_delphi in aktmodeswitches) then
-          include(current_procdef.procoptions,po_assembler);
+          include(current_procinfo.procdef.procoptions,po_assembler);
 
          { Handle assembler block different }
-         if (po_assembler in current_procdef.procoptions) then
+         if (po_assembler in current_procinfo.procdef.procoptions) then
           begin
             block:=assembler_block;
             exit;
@@ -144,8 +144,8 @@ implementation
 
          {Unit initialization?.}
          if (
-             assigned(current_procdef.localst) and
-             (current_procdef.localst.symtablelevel=main_program_level) and
+             assigned(current_procinfo.procdef.localst) and
+             (current_procinfo.procdef.localst.symtablelevel=main_program_level) and
              (current_module.is_unit)
             ) or
             islibrary then
@@ -198,7 +198,7 @@ implementation
                if symtablestack.symtabletype=localsymtable then
                  symtablestack.foreach_static({$ifdef FPCPROCVAR}@{$endif}initializevars,block);
             end;
-         if (current_procdef.localst.symtablelevel=main_program_level) and
+         if (current_procinfo.procdef.localst.symtablelevel=main_program_level) and
              (not current_module.is_unit) then
            begin
              { there's always a call to FPC_DO_EXIT in the main program }
@@ -241,7 +241,7 @@ implementation
          end;
         writeln(printnodefile);
         writeln(printnodefile,'*******************************************************************************');
-        writeln(printnodefile,current_procdef.fullprocname(false));
+        writeln(printnodefile,current_procinfo.procdef.fullprocname(false));
         writeln(printnodefile,'*******************************************************************************');
         printnode(printnodefile,pd.code);
         close(printnodefile);
@@ -261,16 +261,16 @@ implementation
         tcgprocinfo(current_procinfo).initasmnode:=casmnode.create_get_position;
         addstatement(newstatement,tcgprocinfo(current_procinfo).initasmnode);
 
-        if assigned(current_procdef._class) then
+        if assigned(current_procinfo.procdef._class) then
           begin
             { a constructor needs a help procedure }
-            if (current_procdef.proctypeoption=potype_constructor) then
+            if (current_procinfo.procdef.proctypeoption=potype_constructor) then
               begin
-                if is_class(current_procdef._class) then
+                if is_class(current_procinfo.procdef._class) then
                   begin
                     if (cs_implicit_exceptions in aktmoduleswitches) then
                       include(current_procinfo.flags,pi_needs_implicit_finally);
-                    srsym:=search_class_member(current_procdef._class,'NEWINSTANCE');
+                    srsym:=search_class_member(current_procinfo.procdef._class,'NEWINSTANCE');
                     if assigned(srsym) and
                        (srsym.typ=procsym) then
                       begin
@@ -290,9 +290,9 @@ implementation
                       internalerror(200305108);
                   end
                 else
-                  if is_object(current_procdef._class) then
+                  if is_object(current_procinfo.procdef._class) then
                     begin
-                      htype.setdef(current_procdef._class);
+                      htype.setdef(current_procinfo.procdef._class);
                       htype.setdef(tpointerdef.create(htype));
                       { parameter 3 : vmt_offset }
                       { parameter 2 : address of pointer to vmt,
@@ -300,7 +300,7 @@ implementation
                         that memory was allocated }
                       { parameter 1 : self pointer }
                       para:=ccallparanode.create(
-                                cordconstnode.create(current_procdef._class.vmt_offset,s32bittype,false),
+                                cordconstnode.create(current_procinfo.procdef._class.vmt_offset,s32bittype,false),
                             ccallparanode.create(
                                 ctypeconvnode.create_explicit(
                                     load_vmt_pointer_node,
@@ -330,10 +330,10 @@ implementation
               end;
 
             { maybe call BeforeDestruction for classes }
-            if (current_procdef.proctypeoption=potype_destructor) and
-               is_class(current_procdef._class) then
+            if (current_procinfo.procdef.proctypeoption=potype_destructor) and
+               is_class(current_procinfo.procdef._class) then
               begin
-                srsym:=search_class_member(current_procdef._class,'BEFOREDESTRUCTION');
+                srsym:=search_class_member(current_procinfo.procdef._class,'BEFOREDESTRUCTION');
                 if assigned(srsym) and
                    (srsym.typ=procsym) then
                   begin
@@ -374,13 +374,13 @@ implementation
       begin
         generate_exit_block:=internalstatements(newstatement,true);
 
-        if assigned(current_procdef._class) then
+        if assigned(current_procinfo.procdef._class) then
           begin
             { maybe call AfterConstruction for classes }
-            if (current_procdef.proctypeoption=potype_constructor) and
-               is_class(current_procdef._class) then
+            if (current_procinfo.procdef.proctypeoption=potype_constructor) and
+               is_class(current_procinfo.procdef._class) then
               begin
-                srsym:=search_class_member(current_procdef._class,'AFTERCONSTRUCTION');
+                srsym:=search_class_member(current_procinfo.procdef._class,'AFTERCONSTRUCTION');
                 if assigned(srsym) and
                    (srsym.typ=procsym) then
                   begin
@@ -397,11 +397,11 @@ implementation
               end;
 
             { a destructor needs a help procedure }
-            if (current_procdef.proctypeoption=potype_destructor) then
+            if (current_procinfo.procdef.proctypeoption=potype_destructor) then
               begin
-                if is_class(current_procdef._class) then
+                if is_class(current_procinfo.procdef._class) then
                   begin
-                    srsym:=search_class_member(current_procdef._class,'FREEINSTANCE');
+                    srsym:=search_class_member(current_procinfo.procdef._class,'FREEINSTANCE');
                     if assigned(srsym) and
                        (srsym.typ=procsym) then
                       begin
@@ -423,16 +423,16 @@ implementation
                       internalerror(200305108);
                   end
                 else
-                  if is_object(current_procdef._class) then
+                  if is_object(current_procinfo.procdef._class) then
                     begin
                       { finalize object data }
-                      if current_procdef._class.needs_inittable then
+                      if current_procinfo.procdef._class.needs_inittable then
                         addstatement(newstatement,finalize_data_node(load_self_node));
                       { parameter 3 : vmt_offset }
                       { parameter 2 : pointer to vmt }
                       { parameter 1 : self pointer }
                       para:=ccallparanode.create(
-                                cordconstnode.create(current_procdef._class.vmt_offset,s32bittype,false),
+                                cordconstnode.create(current_procinfo.procdef._class.vmt_offset,s32bittype,false),
                             ccallparanode.create(
                                 ctypeconvnode.create_explicit(
                                     load_vmt_pointer_node,
@@ -461,10 +461,10 @@ implementation
 
         { a constructor needs call destructor (if available) when it
           is not inherited }
-        if assigned(current_procdef._class) and
-           (current_procdef.proctypeoption=potype_constructor) then
+        if assigned(current_procinfo.procdef._class) and
+           (current_procinfo.procdef.proctypeoption=potype_constructor) then
           begin
-            pd:=current_procdef._class.searchdestructor;
+            pd:=current_procinfo.procdef._class.searchdestructor;
             if assigned(pd) then
               begin
                 { if vmt<>0 then call destructor }
@@ -480,9 +480,9 @@ implementation
           begin
             { no constructor }
             { must be the return value finalized before reraising the exception? }
-            if (not is_void(current_procdef.rettype.def)) and
-               (current_procdef.rettype.def.needs_inittable) and
-               (not is_class(current_procdef.rettype.def)) then
+            if (not is_void(current_procinfo.procdef.rettype.def)) and
+               (current_procinfo.procdef.rettype.def.needs_inittable) and
+               (not is_class(current_procinfo.procdef.rettype.def)) then
               finalize_data_node(load_result_node);
           end;
       end;
@@ -523,7 +523,7 @@ implementation
         newblock:=internalstatements(newstatement,true);
         if (pi_needs_implicit_finally in current_procinfo.flags) and
            { but it's useless in init/final code of units }
-           not(current_procdef.proctypeoption in [potype_unitfinalize,potype_unitinit]) then
+           not(current_procinfo.procdef.proctypeoption in [potype_unitfinalize,potype_unitinit]) then
           begin
             addstatement(newstatement,initializecode);
             aktfilepos:=entrypos;
@@ -564,7 +564,6 @@ implementation
 
     procedure tcgprocinfo.generate_code;
       var
-        oldprocdef : tprocdef;
         oldprocinfo : tprocinfo;
         oldaktmaxfpuregisters : longint;
         oldfilepos : tfileposinfo;
@@ -579,12 +578,10 @@ implementation
           exit;
 
         oldprocinfo:=current_procinfo;
-        oldprocdef:=current_procdef;
         oldfilepos:=aktfilepos;
         oldaktmaxfpuregisters:=aktmaxfpuregisters;
 
         current_procinfo:=self;
-        current_procdef:=procdef;
 
         { get new labels }
         aktbreaklabel:=nil;
@@ -596,12 +593,8 @@ implementation
 
         { reset the temporary memory }
         rg.cleartempgen;
-        rg.usedinproc:=[];
-        rg.usedintinproc:=[];
-        rg.usedbyproc:=[];
-      {$ifndef newra}
-        rg.usedintbyproc:=[];
-      {$endif}
+        rg.used_in_proc_int:=[];
+        rg.used_in_proc_other:=[];
 
         { set the start offset to the start of the temp area in the stack }
         tg.setfirsttemp(firsttemp_offset);
@@ -666,11 +659,11 @@ implementation
         { now all the registers used are known }
         { Remove all imaginary registers from the used list.}
 {$ifdef newra}
-        procdef.usedintregisters:=rg.usedintinproc*ALL_INTREGISTERS-rg.savedbyproc;
+        procdef.usedintregisters:=rg.used_in_proc_int*ALL_INTREGISTERS-rg.saved_by_proc_int;
 {$else}
-        procdef.usedintregisters:=rg.usedintinproc;
+        procdef.usedintregisters:=rg.used_in_proc_int;
 {$endif}
-        procdef.usedotherregisters:=rg.usedinproc;
+        procdef.usedotherregisters:=rg.used_in_proc_other;
 
         { save local data (casetable) also in the same file }
         if assigned(aktlocaldata) and
@@ -698,7 +691,6 @@ implementation
         templist.free;
         aktmaxfpuregisters:=oldaktmaxfpuregisters;
         aktfilepos:=oldfilepos;
-        current_procdef:=oldprocdef;
         current_procinfo:=oldprocinfo;
       end;
 
@@ -773,7 +765,7 @@ implementation
          if assigned(code) then
           begin
             { the inline procedure has already got a copy of the tree
-              stored in current_procdef.code }
+              stored in current_procinfo.procdef.code }
             code.free;
             if (procdef.proccalloption<>pocall_inline) then
               procdef.code:=nil;
@@ -783,14 +775,11 @@ implementation
 
     procedure tcgprocinfo.parse_body;
       var
-         oldprocdef : tprocdef;
          oldprocinfo : tprocinfo;
       begin
-         oldprocdef:=current_procdef;
          oldprocinfo:=current_procinfo;
 
          current_procinfo:=self;
-         current_procdef:=procdef;
 
          { calculate the lexical level }
          if procdef.parast.symtablelevel>maxnesting then
@@ -820,9 +809,8 @@ implementation
 
          { reset the temporary memory }
          rg.cleartempgen;
-         rg.usedintinproc:=[];
-         rg.usedinproc:=[];
-         rg.usedbyproc:=[];
+         rg.used_in_proc_int:=[];
+         rg.used_in_proc_other:=[];
 
          { save entry info }
          entrypos:=aktfilepos;
@@ -890,10 +878,9 @@ implementation
     {$endif state_tracking}
 
          { reset to normal non static function }
-         if (current_procdef.parast.symtablelevel=normal_function_level) then
+         if (current_procinfo.procdef.parast.symtablelevel=normal_function_level) then
            allow_only_static:=false;
 
-         current_procdef:=oldprocdef;
          current_procinfo:=oldprocinfo;
       end;
 
@@ -969,7 +956,6 @@ implementation
         end;
 
       var
-        oldprocdef       : tprocdef;
         old_current_procinfo : tprocinfo;
         oldconstsymtable : tsymtable;
         oldselftokenmode,
@@ -979,13 +965,11 @@ implementation
         isnestedproc     : boolean;
       begin
          { save old state }
-         oldprocdef:=current_procdef;
          oldconstsymtable:=constsymtable;
          old_current_procinfo:=current_procinfo;
 
-         { reset current_procdef to nil to be sure that nothing is writing
+         { reset current_procinfo.procdef to nil to be sure that nothing is writing
            to an other procdef }
-         current_procdef:=nil;
          current_procinfo:=nil;
 
          { parse procedure declaration }
@@ -1142,7 +1126,6 @@ implementation
          { Restore old state }
          constsymtable:=oldconstsymtable;
 
-         current_procdef:=oldprocdef;
          current_procinfo:=old_current_procinfo;
       end;
 
@@ -1165,17 +1148,17 @@ implementation
 
         procedure Not_supported_for_inline(t : ttoken);
         begin
-           if (current_procdef.proccalloption=pocall_inline) then
+           if (current_procinfo.procdef.proccalloption=pocall_inline) then
              Begin
                 Message1(parser_w_not_supported_for_inline,tokenstring(t));
                 Message(parser_w_inlining_disabled);
-                current_procdef.proccalloption:=pocall_fpccall;
+                current_procinfo.procdef.proccalloption:=pocall_fpccall;
              End;
         end;
 
       begin
          repeat
-           if not assigned(current_procdef) then
+           if not assigned(current_procinfo) then
              internalerror(200304251);
            case token of
               _LABEL:
@@ -1208,8 +1191,8 @@ implementation
               _EXPORTS:
                 begin
                    Not_supported_for_inline(token);
-                   if not(assigned(current_procdef.localst)) or
-                      (current_procdef.localst.symtablelevel>main_program_level) or
+                   if not(assigned(current_procinfo.procdef.localst)) or
+                      (current_procinfo.procdef.localst.symtablelevel>main_program_level) or
                       (current_module.is_unit) then
                      begin
                         Message(parser_e_syntax_error);
@@ -1268,7 +1251,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.126  2003-06-12 16:43:07  peter
+  Revision 1.127  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.126  2003/06/12 16:43:07  peter
     * newra compiles for sparc
 
   Revision 1.125  2003/06/09 12:23:30  peter
@@ -1349,7 +1335,7 @@ end.
     * removed hdisposen,hnewn,selfn
 
   Revision 1.107  2003/04/27 11:21:34  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1358,7 +1344,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.106  2003/04/27 07:29:50  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 24 - 21
compiler/rautils.pas

@@ -732,10 +732,10 @@ Function TOperand.SetupResult:boolean;
 Begin
   SetupResult:=false;
   { replace by correct offset. }
-  if (not is_void(current_procdef.rettype.def)) then
+  if (not is_void(current_procinfo.procdef.rettype.def)) then
    begin
      if (m_tp7 in aktmodeswitches) and
-        (not paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption)) then
+        (not paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption)) then
        begin
          Message(asmr_e_cannot_use_RESULT_here);
          exit;
@@ -750,7 +750,7 @@ end;
 Function TOperand.SetupSelf:boolean;
 Begin
   SetupSelf:=false;
-  if assigned(current_procdef._class) then
+  if assigned(current_procinfo.procdef._class) then
     SetupSelf:=setupvar('self',false)
   else
     Message(asmr_e_cannot_use_SELF_outside_a_method);
@@ -760,7 +760,7 @@ end;
 Function TOperand.SetupOldEBP:boolean;
 Begin
   SetupOldEBP:=false;
-  if current_procdef.parast.symtablelevel>normal_function_level then
+  if current_procinfo.procdef.parast.symtablelevel>normal_function_level then
     SetupOldEBP:=setupvar('parentframe',false)
   else
     Message(asmr_e_cannot_use_OLDEBP_outside_nested_procedure);
@@ -812,25 +812,25 @@ Begin
             begin
               { if we only want the offset we don't have to care
                 the base will be zeroed after ! }
-              if (tvarsym(sym).owner=current_procdef.parast) or
+              if (tvarsym(sym).owner=current_procinfo.procdef.parast) or
                 GetOffset then
                 begin
                   opr.ref.base:=current_procinfo.framepointer;
                 end
               else
                 begin
-                  if (current_procdef.localst.datasize=0) and
+                  if (current_procinfo.procdef.localst.datasize=0) and
                      assigned(current_procinfo.parent) and
-                     (tvarsym(sym).owner=current_procdef.parast) and
-                     (current_procdef.parast.symtablelevel>normal_function_level) then
+                     (tvarsym(sym).owner=current_procinfo.procdef.parast) and
+                     (current_procinfo.procdef.parast.symtablelevel>normal_function_level) then
                     opr.ref.base:=current_procinfo.parent.framepointer
                   else
                     message1(asmr_e_local_para_unreachable,s);
                 end;
               opr.ref.offset:=tvarsym(sym).address;
-              if (current_procdef.parast.symtablelevel=tvarsym(sym).owner.symtablelevel) then
+              if (current_procinfo.procdef.parast.symtablelevel=tvarsym(sym).owner.symtablelevel) then
                 begin
-                  opr.ref.offsetfixup:=current_procdef.parast.address_fixup;
+                  opr.ref.offsetfixup:=current_procinfo.procdef.parast.address_fixup;
                   opr.ref.options:=ref_parafixup;
                 end
               else
@@ -840,7 +840,7 @@ Begin
                 end;
               if (tvarsym(sym).varspez=vs_var) or
                  ((tvarsym(sym).varspez=vs_const) and
-                  paramanager.push_addr_param(tvarsym(sym).vartype.def,current_procdef.proccalloption)) then
+                  paramanager.push_addr_param(tvarsym(sym).vartype.def,current_procinfo.procdef.proccalloption)) then
                 SetSize(pointer_size,false);
             end;
           localsymtable :
@@ -851,23 +851,23 @@ Begin
                 begin
                   { if we only want the offset we don't have to care
                     the base will be zeroed after ! }
-                  if (tvarsym(sym).owner=current_procdef.localst) or
+                  if (tvarsym(sym).owner=current_procinfo.procdef.localst) or
                      GetOffset then
                     opr.ref.base:=current_procinfo.framepointer
                   else
                     begin
-                      if (current_procdef.localst.datasize=0) and
+                      if (current_procinfo.procdef.localst.datasize=0) and
                          assigned(current_procinfo.parent) and
                          (tvarsym(sym).owner=current_procinfo.parent.procdef.localst) and
-                         (current_procdef.parast.symtablelevel>normal_function_level) then
+                         (current_procinfo.procdef.parast.symtablelevel>normal_function_level) then
                         opr.ref.base:=current_procinfo.parent.framepointer
                       else
                         message1(asmr_e_local_para_unreachable,s);
                     end;
                   opr.ref.offset:=tvarsym(sym).address;
-                  if (current_procdef.localst.symtablelevel=tvarsym(sym).owner.symtablelevel) then
+                  if (current_procinfo.procdef.localst.symtablelevel=tvarsym(sym).owner.symtablelevel) then
                     begin
-                      opr.ref.offsetfixup:=current_procdef.localst.address_fixup;
+                      opr.ref.offsetfixup:=current_procinfo.procdef.localst.address_fixup;
                       opr.ref.options:=ref_localfixup;
                     end
                   else
@@ -878,7 +878,7 @@ Begin
                 end;
               if (tvarsym(sym).varspez in [vs_var,vs_out]) or
                  ((tvarsym(sym).varspez=vs_const) and
-                  paramanager.push_addr_param(tvarsym(sym).vartype.def,current_procdef.proccalloption)) then
+                  paramanager.push_addr_param(tvarsym(sym).vartype.def,current_procinfo.procdef.proccalloption)) then
                 SetSize(pointer_size,false);
             end;
         end;
@@ -1284,7 +1284,7 @@ Begin
   base:=Copy(s,1,i-1);
   delete(s,1,i);
   if base='SELF' then
-   st:=current_procdef._class.symtable
+   st:=current_procinfo.procdef._class.symtable
   else
    begin
      asmsearchsym(base,sym,srsymtable);
@@ -1560,7 +1560,10 @@ end;
 end.
 {
   $Log$
-  Revision 1.63  2003-06-06 14:43:29  peter
+  Revision 1.64  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.63  2003/06/06 14:43:29  peter
     * absolutesym support
 
   Revision 1.62  2003/05/30 23:57:08  peter
@@ -1582,7 +1585,7 @@ end.
       tg.direction*tvarsym(X).address...
 
   Revision 1.58  2003/04/27 11:21:34  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -1591,7 +1594,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.57  2003/04/27 07:29:51  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * 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

+ 19 - 16
compiler/regvars.pas

@@ -77,7 +77,7 @@ implementation
               { walk through all momentary register variables }
               for i:=1 to maxvarregs do
                 begin
-                  with pregvarinfo(current_procdef.regvarinfo)^ do
+                  with pregvarinfo(current_procinfo.procdef.regvarinfo)^ do
                    if ((regvars[i]=nil) or (j>regvars_refs[i])) and (j>0) then
                      begin
                         for k:=maxvarregs-1 downto i do
@@ -118,7 +118,7 @@ implementation
               { walk through all momentary register variables }
               for i:=1 to maxfpuvarregs do
                 begin
-                  with pregvarinfo(current_procdef.regvarinfo)^ do
+                  with pregvarinfo(current_procinfo.procdef.regvarinfo)^ do
                    if ((fpuregvars[i]=nil) or (j>fpuregvars_refs[i])) and (j>0) then
                      begin
                         for k:=maxfpuvarregs-1 downto i do
@@ -164,7 +164,7 @@ implementation
         begin
           new(regvarinfo);
           fillchar(regvarinfo^,sizeof(regvarinfo^),0);
-          current_procdef.regvarinfo := regvarinfo;
+          current_procinfo.procdef.regvarinfo := regvarinfo;
           if (p.registers32<maxvarregs) then
             begin
               parasym:=false;
@@ -180,7 +180,7 @@ implementation
 {$ifndef i386}
               else
                 begin
-                  hp:=tparaitem(current_procdef.para.first);
+                  hp:=tparaitem(current_procinfo.procdef.para.first);
                   while assigned(hp) do
                     begin
                       if (hp.paraloc.loc in [LOC_REGISTER,LOC_FPUREGISTER,
@@ -224,7 +224,7 @@ implementation
                       { call by reference/const ? }
                       if (regvarinfo^.regvars[i].varspez in [vs_var,vs_out]) or
                          ((regvarinfo^.regvars[i].varspez=vs_const) and
-                           paramanager.push_addr_param(regvarinfo^.regvars[i].vartype.def,current_procdef.proccalloption)) then
+                           paramanager.push_addr_param(regvarinfo^.regvars[i].vartype.def,current_procinfo.procdef.proccalloption)) then
                         siz:=OS_32
                       else
                        if (regvarinfo^.regvars[i].vartype.def.deftype in [orddef,enumdef]) and
@@ -241,7 +241,7 @@ implementation
                       regvarinfo^.regvars[i].reg.number:=(varregs[i] shl 8) or cgsize2subreg(siz);
 {$ifdef i386}
                       { procedure uses this register }
-                      include(rg.usedintinproc,varregs[i]);
+                      include(rg.used_in_proc_int,varregs[i]);
 {$endif i386}
                     end
                   else
@@ -319,7 +319,7 @@ implementation
       vsym: tvarsym;
     begin
 {$ifdef i386}
-      regvarinfo := pregvarinfo(current_procdef.regvarinfo);
+      regvarinfo := pregvarinfo(current_procinfo.procdef.regvarinfo);
       if not assigned(regvarinfo) then
         exit;
       if reg.enum=R_INTREGISTER then
@@ -393,7 +393,7 @@ implementation
               reference_reset_base(hr,current_procinfo.framepointer,vsym.adjusted_address);
               if (vsym.varspez in [vs_var,vs_out]) or
                  ((vsym.varspez=vs_const) and
-                   paramanager.push_addr_param(vsym.vartype.def,current_procdef.proccalloption)) then
+                   paramanager.push_addr_param(vsym.vartype.def,current_procinfo.procdef.proccalloption)) then
                 opsize := OS_ADDR
               else
                 opsize := def_cgsize(vsym.vartype.def);
@@ -410,7 +410,7 @@ implementation
               reference_reset_base(hr,current_procinfo.framepointer,vsym.adjusted_address);
               if (vsym.varspez in [vs_var,vs_out]) or
                  ((vsym.varspez=vs_const) and
-                   paramanager.push_addr_param(vsym.vartype.def,current_procdef.proccalloption)) then
+                   paramanager.push_addr_param(vsym.vartype.def,current_procinfo.procdef.proccalloption)) then
                 opsize := OS_ADDR
               else
                 opsize := def_cgsize(vsym.vartype.def);
@@ -426,7 +426,7 @@ implementation
       regvarinfo: pregvarinfo;
       reg_spare : tregister;
     begin
-      regvarinfo := pregvarinfo(current_procdef.regvarinfo);
+      regvarinfo := pregvarinfo(current_procinfo.procdef.regvarinfo);
       if not assigned(regvarinfo) then
         exit;
       if reg.enum=R_INTREGISTER then
@@ -453,7 +453,7 @@ implementation
       i: longint;
       regvarinfo: pregvarinfo;
     begin
-      regvarinfo := pregvarinfo(current_procdef.regvarinfo);
+      regvarinfo := pregvarinfo(current_procinfo.procdef.regvarinfo);
       if not assigned(regvarinfo) then
         exit;
       for i := 1 to maxvarregs do
@@ -472,7 +472,7 @@ implementation
          not(pi_uses_asm in current_procinfo.flags) and
          not(pi_uses_exceptions in current_procinfo.flags) then
         begin
-          regvarinfo := pregvarinfo(current_procdef.regvarinfo);
+          regvarinfo := pregvarinfo(current_procinfo.procdef.regvarinfo);
           { can happen when inlining assembler procedures (JM) }
           if not assigned(regvarinfo) then
             exit;
@@ -573,12 +573,12 @@ implementation
       r,reg : tregister;
     begin
       { can happen when inlining assembler procedures (JM) }
-      if not assigned(current_procdef.regvarinfo) then
+      if not assigned(current_procinfo.procdef.regvarinfo) then
         exit;
       if (cs_regalloc in aktglobalswitches) and
          not(pi_uses_asm in current_procinfo.flags) and
          not(pi_uses_exceptions in current_procinfo.flags) then
-        with pregvarinfo(current_procdef.regvarinfo)^ do
+        with pregvarinfo(current_procinfo.procdef.regvarinfo)^ do
           begin
 {$ifdef i386}
             r.enum:=R_ST0;
@@ -616,7 +616,10 @@ end.
 
 {
   $Log$
-  Revision 1.56  2003-06-07 18:57:04  jonas
+  Revision 1.57  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.56  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)
@@ -660,7 +663,7 @@ end.
       tg.direction*tvarsym(X).address...
 
   Revision 1.47  2003/04/27 11:21:34  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 55 - 67
compiler/rgobj.pas

@@ -87,12 +87,11 @@ unit rgobj;
       ;
 
 
-    const ALL_REGISTERS=[firstreg..lastreg];
-          ALL_INTREGISTERS=[first_supreg..last_supreg]-[RS_STACK_POINTER_REG];
+    const
+      ALL_INTREGISTERS=[first_supreg..last_supreg]-[RS_STACK_POINTER_REG];
+      ALL_OTHERREGISTERS=[firstreg..lastreg];
 
     type
-
-
        regvarother_longintarray = array[firstreg..lastreg] of longint;
        regvarother_booleanarray = array[firstreg..lastreg] of boolean;
        regvarint_longintarray = array[first_supreg..last_supreg] of longint;
@@ -104,9 +103,9 @@ unit rgobj;
            1: (ofs: longint);
        end;
 
-       tpushedsavedother = array[firstreg..lastreg] of tpushedsavedloc;
+      tpushedsavedother = array[firstreg..lastreg] of tpushedsavedloc;
 {$ifndef newra}
-       Tpushedsavedint = array[first_supreg..last_supreg] of Tpushedsavedloc;
+      Tpushedsavedint = array[first_supreg..last_supreg] of Tpushedsavedloc;
 {$endif}
 
       Tinterferencebitmap=array[Tsuperregister] of set of Tsuperregister;
@@ -152,7 +151,7 @@ unit rgobj;
        trgobj = class
           { The "usableregsxxx" contain all registers of type "xxx" that }
           { aren't currently allocated to a regvar. The "unusedregsxxx"  }
-          { contain all registers of type "xxx" that aren't currenly     }
+          { contain all registers of type "xxx" that aren't currently    }
           { allocated                                                    }
           lastintreg,maxintreg:Tsuperregister;
           unusedregsint,usableregsint:Tsupregset;
@@ -175,28 +174,24 @@ unit rgobj;
           { Contains the registers which are really used by the proc itself.
             It doesn't take care of registers used by called procedures
           }
-          usedbyproc,
-          usedinproc : tregisterset;
 {$ifdef newra}
-          savedbyproc,
-{$else}
-          usedintbyproc,
+          savedintbyproc,
 {$endif}
-          usedaddrbyproc,
-          usedintinproc,
-          usedaddrinproc:Tsupregset;
+          used_in_proc_int,
+          usedaddrinproc : tsupregset;
+          used_in_proc_other : tregisterset;
 
           reg_pushes_other : regvarother_longintarray;
 {$ifndef newra}
           reg_pushes_int : regvarint_longintarray;
 {$endif}
           is_reg_var_other : regvarother_booleanarray;
-          is_reg_var_int:Tsupregset;
-          regvar_loaded_other: regvarother_booleanarray;
-          regvar_loaded_int: Tsupregset;
+          is_reg_var_int   : Tsupregset;
+          regvar_loaded_other : regvarother_booleanarray;
+          regvar_loaded_int   : Tsupregset;
 {$ifdef newra}
-          colour:array[Tsuperregister] of Tsuperregister;
-          spillednodes:string;
+          colour : array[Tsuperregister] of Tsuperregister;
+          spillednodes : string;
 {$endif}
 
           { tries to hold the amount of times which the current tree is processed  }
@@ -386,11 +381,11 @@ unit rgobj;
 {$endif}
           { the following two contain the common (generic) code for all }
           { get- and ungetregisterxxx functions/procedures              }
-          function getregistergen(list: taasmoutput; const lowreg, highreg: Toldregister;
+          function getregistergenother(list: taasmoutput; const lowreg, highreg: Toldregister;
               var unusedregs:Tregisterset;var countunusedregs:byte): tregister;
           function getregistergenint(list:Taasmoutput;subreg:Tsubregister;
                                      const lowreg,highreg:Tsuperregister;
-                                     var fusedinproc,{$ifndef newra}fusedbyproc,{$endif}unusedregs:Tsupregset
+                                     var fusedinproc,unusedregs:Tsupregset
                                      {$ifndef newra};var countunusedregs:byte{$endif}):Tregister;
           procedure ungetregistergen(list: taasmoutput; const r: tregister;
               const usableregs:tregisterset;var unusedregs: tregisterset; var countunusedregs: byte);
@@ -484,8 +479,8 @@ unit rgobj;
         countusableregsfpu,
         countusableregsmm : byte;
         { contains the registers which are really used by the proc itself }
-        usedbyproc,
-        usedinproc : tregisterset;
+        used_in_proc_int   : tsupregset;
+        used_in_proc_other : tregisterset;
         reg_pushes_other : regvarother_longintarray;
         reg_pushes_int : regvarint_longintarray;
         is_reg_var_other : regvarother_booleanarray;
@@ -522,8 +517,8 @@ unit rgobj;
     constructor Trgobj.create(Acpu_registers:byte);
 
      begin
-       usedinproc := [];
-       usedbyproc:=[];
+       used_in_proc_int := [];
+       used_in_proc_other:=[];
        t_times := 0;
        resetusableregisters;
        lastintreg:=0;
@@ -543,7 +538,7 @@ unit rgobj;
      end;
 
 
-    function trgobj.getregistergen(list: taasmoutput; const lowreg, highreg: Toldregister;
+    function trgobj.getregistergenother(list: taasmoutput; const lowreg, highreg: Toldregister;
         var unusedregs: tregisterset; var countunusedregs: byte): tregister;
       var
         i: Toldregister;
@@ -554,8 +549,7 @@ unit rgobj;
               if i in unusedregs then
                 begin
                    exclude(unusedregs,i);
-                   include(usedinproc,i);
-                   include(usedbyproc,i);
+                   include(used_in_proc_other,i);
                    dec(countunusedregs);
                    r.enum:=i;
                    list.concat(tai_regalloc.alloc(r));
@@ -569,7 +563,7 @@ unit rgobj;
     function Trgobj.getregistergenint(list:Taasmoutput;
                                       subreg:Tsubregister;
                                       const lowreg,highreg:Tsuperregister;
-                                      var fusedinproc,{$ifndef newra}fusedbyproc,{$endif}unusedregs:Tsupregset
+                                      var fusedinproc,unusedregs:Tsupregset
                                       {$ifndef newra};var countunusedregs:byte{$endif}):Tregister;
 
 {$ifdef powerpc}
@@ -600,7 +594,6 @@ unit rgobj;
             exclude(unusedregs,i);
             include(fusedinproc,i);
           {$ifndef newra}
-            include(fusedbyproc,i);
             dec(countunusedregs);
           {$endif}
             r.enum:=R_INTREGISTER;
@@ -710,9 +703,8 @@ unit rgobj;
 {$else}
                                 first_supreg,
                                 last_supreg,
-                                usedintbyproc,
 {$endif}
-                                usedintinproc,
+                                used_in_proc_int,
                                 unusedregsint{$ifndef newra},
                                 countunusedregsint{$endif});
 {$ifdef TEMPREGDEBUG}
@@ -760,10 +752,7 @@ unit rgobj;
 {$endif TEMPREGDEBUG}
 {$endif newra}
           exclude(unusedregsint,r shr 8);
-          include(usedintinproc,r shr 8);
-        {$ifndef newra}
-          include(usedintbyproc,r shr 8);
-        {$endif}
+          include(used_in_proc_int,r shr 8);
           r2.enum:=R_INTREGISTER;
           r2.number:=r;
           list.concat(tai_regalloc.alloc(r2));
@@ -792,8 +781,7 @@ unit rgobj;
               reg_user[r]:=curptree^;
 {$endif TEMPREGDEBUG}
               exclude(unusedregsfpu,r);
-              include(usedinproc,r);
-              include(usedbyproc,r);
+              include(used_in_proc_other,r);
               r2.enum:=r;
               list.concat(tai_regalloc.alloc(r2));
               getexplicitregisterfpu:=r2;
@@ -811,7 +799,7 @@ unit rgobj;
       begin
         if countunusedregsfpu=0 then
           internalerror(10);
-        result := getregistergen(list,firstsavefpureg,lastsavefpureg,
+        result := getregistergenother(list,firstsavefpureg,lastsavefpureg,
           unusedregsfpu,countunusedregsfpu);
       end;
 
@@ -828,7 +816,7 @@ unit rgobj;
       begin
         if countunusedregsmm=0 then
            internalerror(10);
-       result := getregistergen(list,firstsavemmreg,lastsavemmreg,
+       result := getregistergenother(list,firstsavemmreg,lastsavemmreg,
                    unusedregsmm,countunusedregsmm);
       end;
 
@@ -901,7 +889,7 @@ unit rgobj;
       unusedregsfpu:=usableregsfpu;
       unusedregsmm:=usableregsmm;
    {$ifdef newra}
-      savedbyproc:=[];
+      saved_by_proc_int:=[];
       for i:=low(Tsuperregister) to high(Tsuperregister) do
         begin
           if igraph.adjlist[i]<>nil then
@@ -974,7 +962,7 @@ unit rgobj;
         hr : treference;
 
     begin
-      usedintinproc:=usedintinproc+s;
+      used_in_proc_int:=used_in_proc_int+s;
       for r:=firstsaveintreg to lastsaveintreg do
         begin
           saved[r].ofs:=reg_not_saved;
@@ -1010,7 +998,7 @@ unit rgobj;
          hr : treference;
 
       begin
-        usedinproc:=usedinproc + s;
+        used_in_proc_other:=used_in_proc_other + s;
 
         { don't try to save the fpu registers if not desired (e.g. for }
         { the 80x86)                                                   }
@@ -1163,7 +1151,10 @@ unit rgobj;
 {$ifndef newra}
     procedure trgobj.incrementintregisterpushed(const s:Tsupregset);
 
-    var regi:Tsuperregister;
+{$ifdef i386}
+    var
+      regi:Tsuperregister;
+{$endif i386}
 
     begin
 {$ifdef i386}
@@ -1178,8 +1169,10 @@ unit rgobj;
 
     procedure trgobj.incrementotherregisterpushed(const s:Tregisterset);
 
+{$ifdef i386}
       var
          regi : Toldregister;
+{$endif i386}
 
       begin
 {$ifdef i386}
@@ -1246,11 +1239,7 @@ unit rgobj;
         exclude(usableregsint,reg);
         exclude(unusedregsint,reg);
         include(is_reg_var_int,reg);
-{$ifndef newra}
-  {$ifndef i386}
-        include(usedintbyproc,reg);
-  {$endif not i386}
-{$endif newra}
+        include(used_in_proc_int,reg);
       end;
 
     procedure trgobj.makeregvarother(reg: tregister);
@@ -1265,9 +1254,7 @@ unit rgobj;
              dec(countunusedregsfpu);
              exclude(usableregsfpu,reg.enum);
              exclude(unusedregsfpu,reg.enum);
-{$ifndef i386}
-             include(usedbyproc,reg.enum);
-{$endif not i386}
+             include(used_in_proc_other,reg.enum);
           end
         else if reg.enum in mmregs then
           begin
@@ -1275,9 +1262,7 @@ unit rgobj;
              dec(countunusedregsmm);
              exclude(usableregsmm,reg.enum);
              exclude(unusedregsmm,reg.enum);
-{$ifndef i386}
-             include(usedbyproc,reg.enum);
-{$endif not i386}
+             include(used_in_proc_other,reg.enum);
           end;
         is_reg_var_other[reg.enum]:=true;
       end;
@@ -1315,8 +1300,8 @@ unit rgobj;
         psavedstate(state)^.countusableregsint := countusableregsint;
         psavedstate(state)^.countusableregsfpu := countusableregsfpu;
         psavedstate(state)^.countusableregsmm := countusableregsmm;
-        psavedstate(state)^.usedinproc := usedinproc;
-        psavedstate(state)^.usedbyproc := usedbyproc;
+        psavedstate(state)^.used_in_proc_int := used_in_proc_int;
+        psavedstate(state)^.used_in_proc_other := used_in_proc_other;
       {$ifndef newra}
         psavedstate(state)^.reg_pushes_int := reg_pushes_int;
       {$endif}
@@ -1348,8 +1333,8 @@ unit rgobj;
         countusableregsint := psavedstate(state)^.countusableregsint;
         countusableregsfpu := psavedstate(state)^.countusableregsfpu;
         countusableregsmm := psavedstate(state)^.countusableregsmm;
-        usedinproc := psavedstate(state)^.usedinproc;
-        usedbyproc := psavedstate(state)^.usedbyproc;
+        used_in_proc_int := psavedstate(state)^.used_in_proc_int;
+        used_in_proc_other := psavedstate(state)^.used_in_proc_other;
       {$ifndef newra}
         reg_pushes_int := psavedstate(state)^.reg_pushes_int;
       {$endif}
@@ -1962,8 +1947,8 @@ unit rgobj;
                 colour[n]:=k;
                 dec(spillednodes[0]);  {Colour found: no spill.}
                 include(colourednodes,n);
-                if n in usedintinproc then
-                  include(usedintinproc,k);
+                if n in used_in_proc_int then
+                  include(used_in_proc_int,k);
                 break;
               end;
         end;
@@ -1973,8 +1958,8 @@ unit rgobj;
           n:=Tsuperregister(coalescednodes[i]);
           k:=get_alias(n);
           colour[n]:=colour[k];
-          if n in usedintinproc then
-            include(usedintinproc,colour[k]);
+          if n in used_in_proc_int then
+            include(used_in_proc_int,colour[k]);
         end;
     {$ifdef ra_debug}
       for i:=first_imreg to maxintreg do
@@ -2158,7 +2143,7 @@ unit rgobj;
         if (i in unusedregsint) and (pos(char(i),abtlist)=0) then
           begin
             exclude(unusedregsint,i);
-            include(usedintinproc,i);
+            include(used_in_proc_int,i);
             r.enum:=R_INTREGISTER;
             r.number:=i shl 8 or subreg;
             if position=nil then
@@ -2230,7 +2215,7 @@ unit rgobj;
       if found then
         begin
           exclude(unusedregsint,i);
-          include(usedintinproc,i);
+          include(used_in_proc_int,i);
           r.enum:=R_INTREGISTER;
           r.number:=i shl 8 or cgsize2subreg(size);
           list.concat(Tai_regalloc.alloc(r));
@@ -2468,7 +2453,10 @@ end.
 
 {
   $Log$
-  Revision 1.53  2003-06-12 21:11:10  peter
+  Revision 1.54  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.53  2003/06/12 21:11:10  peter
     * ungetregisterfpu gets size parameter
 
   Revision 1.52  2003/06/12 16:43:07  peter

+ 5 - 2
compiler/sparc/cgcpu.pas

@@ -1092,7 +1092,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.58  2003-06-12 16:43:07  peter
+  Revision 1.59  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.58  2003/06/12 16:43:07  peter
     * newra compiles for sparc
 
   Revision 1.57  2003/06/04 20:59:37  mazen
@@ -1146,7 +1149,7 @@ end.
   + NOP after conditional jump instruction to prevent delay slot execution
 
   Revision 1.43  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 5 - 2
compiler/sparc/cpupi.pas

@@ -101,7 +101,10 @@ begin
 end.
 {
   $Log$
-  Revision 1.16  2003-05-30 23:57:08  peter
+  Revision 1.17  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.16  2003/05/30 23:57:08  peter
     * more sparc cleanup
     * accumulator removed, splitted in function_return_reg (called) and
       function_result_reg (caller)
@@ -111,7 +114,7 @@ end.
     * some reformatting done
 
   Revision 1.14  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 5 - 2
compiler/sparc/ncpucall.pas

@@ -62,11 +62,14 @@ begin
 end.
 {
   $Log$
-  Revision 1.11  2003-04-28 09:49:58  mazen
+  Revision 1.12  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.11  2003/04/28 09:49:58  mazen
   - InternalError removed from TSparcCallNode.push_framepointer as it is called by common coplier code.
 
   Revision 1.10  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 25 - 22
compiler/sparc/radirect.pas

@@ -84,22 +84,22 @@ interface
            if s<>'' then
             code.concat(Tai_direct.Create(strpnew(s)));
             { consider it set function set if the offset was loaded }
-           if assigned(current_procdef.funcretsym) and
+           if assigned(current_procinfo.procdef.funcretsym) and
               (pos(retstr,upper(s))>0) then
-             tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+             tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
            s:='';
          end;
 
      begin
        ende:=false;
        s:='';
-       if assigned(current_procdef.funcretsym) and
-          is_fpu(current_procdef.rettype.def) then
-         tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+       if assigned(current_procinfo.procdef.funcretsym) and
+          is_fpu(current_procinfo.procdef.rettype.def) then
+         tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
        framereg:=current_procinfo.framepointer;
        convert_register_to_enum(framereg);
-       if (not is_void(current_procdef.rettype.def)) then
-         retstr:=upper(tostr(tvarsym(current_procdef.funcretsym).adjusted_address)+'('+std_reg2str[framereg.enum]+')')
+       if (not is_void(current_procinfo.procdef.rettype.def)) then
+         retstr:=upper(tostr(tvarsym(current_procinfo.procdef.funcretsym).adjusted_address)+'('+std_reg2str[framereg.enum]+')')
        else
          retstr:='';
 
@@ -144,22 +144,22 @@ interface
                            end
                          else
                          { access to local variables }
-                         if assigned(current_procdef) then
+                         if assigned(current_procinfo.procdef) then
                            begin
                               { is the last written character an special }
                               { char ?                                   }
                               if (s[length(s)]='%') and
-                                 (not paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption)) and
+                                 (not paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption)) and
                                  ((pos('AX',upper(hs))>0) or
                                  (pos('AL',upper(hs))>0)) then
-                                tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+                                tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
                               if (s[length(s)]<>'%') and
                                 (s[length(s)]<>'$') and
                                 ((s[length(s)]<>'0') or (hs[1]<>'x')) then
                                 begin
-                                   if assigned(current_procdef.localst) and
-                                      (current_procdef.localst.symtablelevel >= normal_function_level) then
-                                     sym:=tsym(current_procdef.localst.search(upper(hs)))
+                                   if assigned(current_procinfo.procdef.localst) and
+                                      (current_procinfo.procdef.localst.symtablelevel >= normal_function_level) then
+                                     sym:=tsym(current_procinfo.procdef.localst.search(upper(hs)))
                                    else
                                      sym:=nil;
                                    if assigned(sym) then
@@ -193,8 +193,8 @@ interface
                                      end
                                    else
                                      begin
-                                        if assigned(current_procdef.parast) then
-                                          sym:=tsym(current_procdef.parast.search(upper(hs)))
+                                        if assigned(current_procinfo.procdef.parast) then
+                                          sym:=tsym(current_procinfo.procdef.parast.search(upper(hs)))
                                         else
                                           sym:=nil;
                                         if assigned(sym) then
@@ -203,7 +203,7 @@ interface
                                                begin
                                                   l:=tvarsym(sym).address;
                                                   { set offset }
-                                                  inc(l,current_procdef.parast.address_fixup);
+                                                  inc(l,current_procinfo.procdef.parast.address_fixup);
                                                   hs:=tostr(l)+'('+std_reg2str[current_procinfo.framepointer.enum]+')';
                                                   if pos(',',s) > 0 then
                                                     tvarsym(sym).varstate:=vs_used;
@@ -216,7 +216,7 @@ interface
                                    uhs:=upper(hs);
                                    if (uhs='__SELF') then
                                      begin
-                                       if assigned(current_procdef._class) then
+                                       if assigned(current_procinfo.procdef._class) then
                                         uhs:='self'
                                        else
                                         begin
@@ -227,7 +227,7 @@ interface
                                    else
                                     if (uhs='__OLDEBP') then
                                       begin
-                                        if current_procdef.parast.symtablelevel>normal_function_level then
+                                        if current_procinfo.procdef.parast.symtablelevel>normal_function_level then
                                          uhs:='parentframe'
                                         else
                                          begin
@@ -238,7 +238,7 @@ interface
                                     else
                                       if uhs='__RESULT' then
                                         begin
-                                          if (not is_void(current_procdef.rettype.def)) then
+                                          if (not is_void(current_procinfo.procdef.rettype.def)) then
                                            uhs:='result'
                                           else
                                            begin
@@ -314,7 +314,7 @@ interface
                '{',';',#10,#13:
                  begin
                     if pos(retstr,s) > 0 then
-                      tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+                      tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
                     writeasmline;
                     c:=current_scanner.asmgetchar;
                  end;
@@ -349,7 +349,10 @@ initialization
 end.
 {
   $Log$
-  Revision 1.11  2003-06-02 21:42:05  jonas
+  Revision 1.12  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.11  2003/06/02 21:42:05  jonas
     * function results can now also be regvars
     - removed tprocinfo.return_offset, never use it again since it's invalid
       if the result is a regvar
@@ -365,7 +368,7 @@ end.
     * fixed sparc compilation partially
 
   Revision 1.7  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 10 - 13
compiler/symsym.pas

@@ -348,12 +348,6 @@ interface
 
 
     var
-       current_procdef : tprocdef;
-
-       aktcallprocdef : tabstractprocdef;  { pointer to the definition of the
-                                             currently called procedure,
-                                             only set/unset in ncal }
-
        generrorsym : tsym;
 
     const
@@ -1891,8 +1885,8 @@ implementation
            exit;
          if (vo_is_self in varoptions) then
            begin
-             if (po_classmethod in current_procdef.procoptions) or
-                (po_staticmethod in current_procdef.procoptions) then
+             if (po_classmethod in current_procinfo.procdef.procoptions) or
+                (po_staticmethod in current_procinfo.procdef.procoptions) then
                begin
                  asmlist.concat(Tai_stabs.Create(strpnew(
                     '"pvmt:p'+tstoreddef(pvmttype.def).numberstring+'",'+
@@ -1900,12 +1894,12 @@ implementation
                end
              else
                begin
-                 if not(is_class(current_procdef._class)) then
+                 if not(is_class(current_procinfo.procdef._class)) then
                    c:='v'
                  else
                    c:='p';
                  asmlist.concat(Tai_stabs.Create(strpnew(
-                    '"$t:'+c+current_procdef._class.numberstring+'",'+
+                    '"$t:'+c+current_procinfo.procdef._class.numberstring+'",'+
                     tostr(N_tsym)+',0,0,'+tostr(adjusted_address))));
                end;
            end
@@ -2662,7 +2656,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.109  2003-06-07 20:26:32  peter
+  Revision 1.110  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.109  2003/06/07 20:26:32  peter
     * re-resolving added instead of reloading from ppu
     * tderef object added to store deref info for resolving
 
@@ -2700,7 +2697,7 @@ end.
     * vs_hidden replaced by is_hidden boolean
 
   Revision 1.100  2003/04/27 11:21:34  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -2713,7 +2710,7 @@ end.
       a positive offset relative to the stack/framepointer
 
   Revision 1.98  2003/04/27 07:29:51  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 14 - 7
compiler/symtable.pas

@@ -2028,7 +2028,8 @@ implementation
            begin
               srsym:=tsym(srsymtable.speedsearch(s,speedvalue));
               if assigned(srsym) and
-                 tstoredsym(srsym).is_visible_for_proc(current_procdef) then
+                 (not assigned(current_procinfo) or
+                  tstoredsym(srsym).is_visible_for_proc(current_procinfo.procdef)) then
                begin
                  searchsym:=true;
                  exit;
@@ -2098,7 +2099,8 @@ implementation
                 end
                else
                 begin
-                  if tstoredsym(sym).is_visible_for_proc(current_procdef) then
+                  if (not assigned(current_procinfo) or
+                      tstoredsym(sym).is_visible_for_proc(current_procinfo.procdef)) then
                    break;
                 end;
              end;
@@ -2143,7 +2145,8 @@ implementation
                    end
                   else
                    begin
-                     if tprocdef(def).is_visible_for_proc(current_procdef) then
+                     if (not assigned(current_procinfo) or
+                         tprocdef(def).is_visible_for_proc(current_procinfo.procdef)) then
                       break;
                    end;
                 end;
@@ -2192,7 +2195,8 @@ implementation
                    end
                   else
                    begin
-                     if tprocdef(def).is_visible_for_proc(current_procdef) then
+                     if (not assigned(current_procinfo) or
+                         tprocdef(def).is_visible_for_proc(current_procinfo.procdef)) then
                       break;
                    end;
                 end;
@@ -2470,7 +2474,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.106  2003-06-09 18:26:27  peter
+  Revision 1.107  2003-06-13 21:19:31  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.106  2003/06/09 18:26:27  peter
     * para can be the same as function name in delphi
 
   Revision 1.105  2003/06/08 11:40:00  peter
@@ -2509,7 +2516,7 @@ end.
     * direct with rewritten to use temprefnode
 
   Revision 1.97  2003/04/27 11:21:34  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -2518,7 +2525,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.96  2003/04/27 07:29:51  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * current_procinfo.procdef cleanup, current_procdef is now always nil when parsing
       a new procdef declaration
     * aktprocsym removed
     * lexlevel removed, use symtable.symtablelevel instead

+ 15 - 9
compiler/x86/cgx86.pas

@@ -1710,7 +1710,7 @@ unit cgx86;
                 r.number:=NR_EDX;
                 list.concat(Taicpu.Op_sym_ofs_reg(A_MOV,S_L,pl,0,r));
                 a_call_name(list,target_info.Cprefix+'mcount');
-                include(rg.usedinproc,R_EDX);
+                include(rg.used_in_proc_int,RS_EDX);
              end;
 
            system_i386_go32v2:
@@ -1783,7 +1783,7 @@ unit cgx86;
       r.number:=NR_EBP;
     {$ifdef newra}
       list.concat(tai_regalloc.alloc(r));
-      include(rg.savedbyproc,RS_EBP);
+      include(rg.saved_by_proc_int,RS_EBP);
     {$endif}
       rsp.enum:=R_INTREGISTER;
       rsp.number:=NR_ESP;
@@ -1796,7 +1796,9 @@ unit cgx86;
 
     procedure tcgx86.g_restore_frame_pointer(list : taasmoutput);
 
+    {$ifdef newra}
     var r:Tregister;
+    {$endif}
 
     begin
     {$ifdef newra}
@@ -1812,10 +1814,11 @@ unit cgx86;
       begin
         { Routines with the poclearstack flag set use only a ret }
         { also routines with parasize=0     }
-        if (po_clearstack in current_procdef.procoptions) then
+        if (po_clearstack in current_procinfo.procdef.procoptions) then
          begin
            { complex return values are removed from stack in C code PM }
-           if paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption) then
+           if paramanager.ret_in_param(current_procinfo.procdef.rettype.def,
+                                       current_procinfo.procdef.proccalloption) then
              list.concat(Taicpu.Op_const(A_RET,S_NO,4))
            else
              list.concat(Taicpu.Op_none(A_RET,S_NO));
@@ -1847,9 +1850,9 @@ unit cgx86;
       r.number:=NR_EDI;
       list.concat(Taicpu.op_reg(A_PUSH,S_L,r));
     {$ifdef newra}
-      include(rg.savedbyproc,RS_EBX);
-      include(rg.savedbyproc,RS_ESI);
-      include(rg.savedbyproc,RS_EDI);
+      include(rg.saved_by_proc_int,RS_EBX);
+      include(rg.saved_by_proc_int,RS_ESI);
+      include(rg.saved_by_proc_int,RS_EDI);
     {$endif}
     end;
 
@@ -1932,7 +1935,10 @@ unit cgx86;
 end.
 {
   $Log$
-  Revision 1.54  2003-06-12 18:31:18  peter
+  Revision 1.55  2003-06-13 21:19:32  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.54  2003/06/12 18:31:18  peter
     * fix newra cycle for i386
 
   Revision 1.53  2003/06/07 10:24:10  peter
@@ -1977,7 +1983,7 @@ end.
     * merged some more x86-64 and i386 code
 
   Revision 1.43  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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

+ 24 - 18
compiler/x86/cpubase.pas

@@ -544,6 +544,7 @@ uses
     function is_calljmp(o:tasmop):boolean;
     procedure inverse_flags(var f: TResFlags);
     function flags_to_cond(const f: TResFlags) : TAsmCond;
+    function supreg_name(r:Tsuperregister):string;
 
 
 implementation
@@ -663,26 +664,28 @@ implementation
          end;
       end;
 
-{$ifdef unused}
-    function supreg_name(r:Tsuperregister):string;
-
-    var s:string[4];
 
-    const supreg_names:array[0..last_supreg] of string[4]=
+    function supreg_name(r:Tsuperregister):string;
+      const
+        supreg_names:array[0..last_supreg] of string[4]=
           ('INV',
-           'eax','ebx','ecx','edx','esi','edi','ebp','esp',
-           'r8' ,'r9', 'r10','r11','r12','r13','r14','r15');
+           'eax','ebx','ecx','edx','esi','edi','ebp','esp'
+{$ifdef x86_64}
+           ,'r8' ,'r9', 'r10','r11','r12','r13','r14','r15'
+{$endif x86_64}
+           );
+      var
+        s : string[4];
+      begin
+        if r in [0..last_supreg] then
+          supreg_name:=supreg_names[r]
+        else
+          begin
+            str(r,s);
+            supreg_name:='reg'+s;
+          end;
+      end;
 
-    begin
-      if r in [0..last_supreg] then
-        supreg_name:=supreg_names[r]
-      else
-        begin
-          str(r,s);
-          supreg_name:='reg'+s;
-        end;
-    end;
-{$endif unused}
 
     function is_calljmp(o:tasmop):boolean;
       begin
@@ -725,7 +728,10 @@ implementation
 end.
 {
   $Log$
-  Revision 1.8  2003-06-12 19:11:34  jonas
+  Revision 1.9  2003-06-13 21:19:33  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.8  2003/06/12 19:11:34  jonas
     - removed ALL_INTREGISTERS (only the one in rgobj is valid)
 
   Revision 1.7  2003/06/03 21:11:09  peter

+ 26 - 23
compiler/x86/radirect.pas

@@ -79,22 +79,22 @@ interface
            if s<>'' then
             code.concat(Tai_direct.Create(strpnew(s)));
             { consider it set function set if the offset was loaded }
-           if assigned(current_procdef.funcretsym) and
+           if assigned(current_procinfo.procdef.funcretsym) and
               (pos(retstr,upper(s))>0) then
-             tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+             tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
            s:='';
          end;
 
      begin
        ende:=false;
        s:='';
-       if assigned(current_procdef.funcretsym) and
-          is_fpu(current_procdef.rettype.def) then
-         tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+       if assigned(current_procinfo.procdef.funcretsym) and
+          is_fpu(current_procinfo.procdef.rettype.def) then
+         tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
        framereg:=current_procinfo.framepointer;
        convert_register_to_enum(framereg);
-       if (not is_void(current_procdef.rettype.def)) then
-         retstr:=upper(tostr(tvarsym(current_procdef.funcretsym).adjusted_address)+'('+gas_reg2str[framereg.enum]+')')
+       if (not is_void(current_procinfo.procdef.rettype.def)) then
+         retstr:=upper(tostr(tvarsym(current_procinfo.procdef.funcretsym).adjusted_address)+'('+gas_reg2str[framereg.enum]+')')
        else
          retstr:='';
        c:=current_scanner.asmgetchar;
@@ -138,23 +138,23 @@ interface
                            FwaitWarning
                           else
                           { access to local variables }
-                          if assigned(current_procdef) then
+                          if assigned(current_procinfo.procdef) then
                             begin
                                { is the last written character an special }
                                { char ?                                   }
                                if (s[length(s)]='%') and
-                                  (not paramanager.ret_in_param(current_procdef.rettype.def,current_procdef.proccalloption)) and
+                                  (not paramanager.ret_in_param(current_procinfo.procdef.rettype.def,current_procinfo.procdef.proccalloption)) and
                                   ((pos('AX',upper(hs))>0) or
                                   (pos('AL',upper(hs))>0)) then
-                                 tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+                                 tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
                                if (s[length(s)]<>'%') and
                                  (s[length(s)]<>'$') and
                                  (s[length(s)]<>'.') and
                                  ((s[length(s)]<>'0') or (hs[1]<>'x')) then
                                  begin
-                                    if assigned(current_procdef.localst) and
-                                       (current_procdef.localst.symtablelevel>=normal_function_level) then
-                                      sym:=tsym(current_procdef.localst.search(upper(hs)))
+                                    if assigned(current_procinfo.procdef.localst) and
+                                       (current_procinfo.procdef.localst.symtablelevel>=normal_function_level) then
+                                      sym:=tsym(current_procinfo.procdef.localst.search(upper(hs)))
                                     else
                                       sym:=nil;
                                     if assigned(sym) then
@@ -188,8 +188,8 @@ interface
                                       end
                                     else
                                       begin
-                                         if assigned(current_procdef.parast) then
-                                           sym:=tsym(current_procdef.parast.search(upper(hs)))
+                                         if assigned(current_procinfo.procdef.parast) then
+                                           sym:=tsym(current_procinfo.procdef.parast.search(upper(hs)))
                                          else
                                            sym:=nil;
                                          if assigned(sym) then
@@ -198,7 +198,7 @@ interface
                                                 begin
                                                    l:=tvarsym(sym).address;
                                                    { set offset }
-                                                   inc(l,current_procdef.parast.address_fixup);
+                                                   inc(l,current_procinfo.procdef.parast.address_fixup);
                                                    hs:=tostr(l)+'('+gas_reg2str[framereg.enum]+')';
                                                    if pos(',',s) > 0 then
                                                      tvarsym(sym).varstate:=vs_used;
@@ -214,7 +214,7 @@ interface
                                          uhs:=upper(hs);
                                          if (uhs='__SELF') then
                                            begin
-                                             if assigned(current_procdef._class) then
+                                             if assigned(current_procinfo.procdef._class) then
                                               uhs:='self'
                                              else
                                               begin
@@ -225,7 +225,7 @@ interface
                                          else
                                           if (uhs='__OLDEBP') then
                                            begin
-                                             if current_procdef.parast.symtablelevel>normal_function_level then
+                                             if current_procinfo.procdef.parast.symtablelevel>normal_function_level then
                                               uhs:='parentframe'
                                              else
                                               begin
@@ -236,7 +236,7 @@ interface
                                          else
                                           if uhs='__RESULT' then
                                            begin
-                                             if (not is_void(current_procdef.rettype.def)) then
+                                             if (not is_void(current_procinfo.procdef.rettype.def)) then
                                               uhs:='result'
                                              else
                                               begin
@@ -313,7 +313,7 @@ interface
               '{',';',#10,#13 :
                 begin
                   if pos(retstr,s) > 0 then
-                    tvarsym(current_procdef.funcretsym).varstate:=vs_assigned;
+                    tvarsym(current_procinfo.procdef.funcretsym).varstate:=vs_assigned;
                   writeasmline;
                   c:=current_scanner.asmgetchar;
                 end;
@@ -361,7 +361,10 @@ initialization
 end.
 {
   $Log$
-  Revision 1.6  2003-06-02 21:42:05  jonas
+  Revision 1.7  2003-06-13 21:19:33  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.6  2003/06/02 21:42:05  jonas
     * function results can now also be regvars
     - removed tprocinfo.return_offset, never use it again since it's invalid
       if the result is a regvar
@@ -388,7 +391,7 @@ end.
     * merged more x86-64/i386 code
 
   Revision 1.11  2003/04/27 11:21:36  peter
-    * aktprocdef renamed to current_procdef
+    * 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
@@ -397,7 +400,7 @@ end.
     * fixed unit implicit initfinal
 
   Revision 1.10  2003/04/27 07:29:52  peter
-    * current_procdef cleanup, current_procdef is now always nil when parsing
+    * 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

+ 101 - 206
compiler/x86_64/rgcpu.pas

@@ -38,9 +38,11 @@ unit rgcpu;
        trgcpu = class(trgobj)
 
           { to keep the same allocation order as with the old routines }
-          function getregisterint(list: taasmoutput): tregister; override;
-          procedure ungetregisterint(list: taasmoutput; r : tregister); override;
-          function getexplicitregisterint(list: taasmoutput; r : tregister) : tregister; override;
+          function getregisterint(list:Taasmoutput;size:Tcgsize):Tregister;override;
+{$ifndef newra}
+          procedure ungetregisterint(list:Taasmoutput;r:Tregister); override;
+          function getexplicitregisterint(list:Taasmoutput;r:Tnewregister):Tregister;override;
+{$endif newra}
 
           function getregisterfpu(list: taasmoutput) : tregister; override;
           procedure ungetregisterfpu(list: taasmoutput; r : tregister); override;
@@ -54,17 +56,6 @@ unit rgcpu;
           }
           function makeregsize(reg: tregister; size: tcgsize): tregister; override;
 
-          { pushes and restores registers }
-          procedure pushusedregisters(list: taasmoutput;
-            var pushed : tpushedsaved;const s: tregisterset);
-          procedure popusedregisters(list: taasmoutput;
-            const pushed : tpushedsaved);
-
-          procedure saveusedregisters(list: taasmoutput;
-            var saved : tpushedsaved;const s: tregisterset);override;
-          procedure restoreusedregisters(list: taasmoutput;
-            const saved : tpushedsaved);override;
-
           procedure resetusableregisters;override;
 
          { corrects the fpu stack register by ofs }
@@ -86,7 +77,7 @@ unit rgcpu;
 {************************************************************************}
 
   const
-    reg2reg64 : array[tregister] of tregister = (R_NO,
+    reg2reg64 : array[firstreg..lastreg] of toldregister = (R_NO,
       R_RAX,R_RCX,R_RDX,R_RBX,R_RSP,R_RBP,R_RSI,R_RDI,
       R_R8,R_R9,R_R10,R_R11,R_R12,R_R13,R_R14,R_R15,R_RIP,
       R_RAX,R_RCX,R_RDX,R_RBX,R_RSP,R_RBP,R_RSI,R_RDI,
@@ -106,7 +97,7 @@ unit rgcpu;
       R_NO,R_NO,R_NO,R_NO,R_NO,R_NO,R_NO,R_NO
     );
 
-    reg2reg32 : array[tregister] of tregister = (R_NO,
+    reg2reg32 : array[firstreg..lastreg] of toldregister = (R_NO,
       R_EAX,R_ECX,R_EDX,R_EBX,R_ESP,R_EBP,R_ESI,R_EDI,
       R_R8D,R_R9D,R_R10D,R_R11D,R_R12D,R_R13D,R_R14D,R_R15D,R_NO,
       R_EAX,R_ECX,R_EDX,R_EBX,R_ESP,R_EBP,R_ESI,R_EDI,
@@ -126,7 +117,7 @@ unit rgcpu;
       R_NO,R_NO,R_NO,R_NO,R_NO,R_NO,R_NO,R_NO
     );
 
-    reg2reg16 : array[tregister] of tregister = (R_NO,
+    reg2reg16 : array[firstreg..lastreg] of toldregister = (R_NO,
       R_AX,R_CX,R_DX,R_BX,R_SP,R_BP,R_SI,R_DI,
       R_R8W,R_R9W,R_R10W,R_R11W,R_R12W,R_R13W,R_R14W,R_R15W,R_NO,
       R_AX,R_CX,R_DX,R_BX,R_SP,R_BP,R_SI,R_DI,
@@ -146,7 +137,7 @@ unit rgcpu;
       R_NO,R_NO,R_NO,R_NO,R_NO,R_NO,R_NO,R_NO
     );
 
-    reg2reg8 : array[tregister] of tregister = (R_NO,
+    reg2reg8 : array[firstreg..lastreg] of toldregister = (R_NO,
       R_AL,R_CL,R_DL,R_BL,R_SPL,R_BPL,R_SIL,R_DIL,
       R_R8B,R_R9B,R_R10B,R_R11B,R_R12B,R_R13B,R_R14B,R_R15B,R_NO,
       R_AL,R_CL,R_DL,R_BL,R_SPL,R_BPL,R_SIL,R_DIL,
@@ -173,17 +164,17 @@ unit rgcpu;
       begin
         case size of
           S_B :
-            reg:=reg2reg8[r];
+            reg.enum:=reg2reg8[r.enum];
           S_W :
-            reg:=reg2reg16[r];
+            reg.enum:=reg2reg16[r.enum];
           S_L :
-            reg:=reg2reg32[r];
+            reg.enum:=reg2reg32[r.enum];
           S_Q :
-            reg:=reg2reg64[r];
+            reg.enum:=reg2reg64[r.enum];
           else
             internalerror(200204101);
         end;
-        if reg=R_NO then
+        if reg.enum=R_NO then
          internalerror(200204102);
         changeregsize:=reg;
       end;
@@ -193,91 +184,109 @@ unit rgcpu;
 {                               trgcpu                                   }
 {************************************************************************}
 
-    function trgcpu.getregisterint(list: taasmoutput): tregister;
-      begin
-         if countunusedregsint=0 then
-           internalerror(10);
+    function trgcpu.getregisterint(list: taasmoutput;size:Tcgsize): tregister;
+    var subreg:Tsubregister;
+
+    begin
+      subreg:=cgsize2subreg(size);
+
+      if countunusedregsint=0 then
+        internalerror(10);
+      result.enum:=R_INTREGISTER;
 {$ifdef TEMPREGDEBUG}
-         if curptree^.usableregsint-countunusedregsint>curptree^.registers32 then
-           internalerror(10);
+      if curptree^.usableregsint-countunusedregsint>curptree^.registers32 then
+        internalerror(10);
 {$endif TEMPREGDEBUG}
 {$ifdef EXTTEMPREGDEBUG}
-         if curptree^.usableregs-countunusedregistersint>curptree^^.reallyusedregs then
-           curptree^.reallyusedregs:=curptree^^.usableregs-countunusedregistersint;
+      if curptree^.usableregs-countunusedregistersint>curptree^^.reallyusedregs then
+        curptree^.reallyusedregs:=curptree^^.usableregs-countunusedregistersint;
 {$endif EXTTEMPREGDEBUG}
-         dec(countunusedregsint);
-         if R_EAX in unusedregsint then
-           begin
-              exclude(unusedregsint,R_EAX);
-              include(usedinproc,R_EAX);
-              getregisterint:=R_EAX;
+      if RS_RAX in unusedregsint then
+        begin
+          dec(countunusedregsint);
+          exclude(unusedregsint,RS_RAX);
+          include(used_in_proc_int,RS_RAX);
+          result.number:=RS_RAX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
-              reg_user[R_EAX]:=curptree^;
+          reg_user[R_RAX]:=curptree^;
 {$endif TEMPREGDEBUG}
-              exprasmlist.concat(tai_regalloc.alloc(R_EAX));
-           end
-         else if R_EDX in unusedregsint then
-           begin
-              exclude(unusedregsint,R_EDX);
-              include(usedinproc,R_EDX);
-              getregisterint:=R_EDX;
+          exprasmlist.concat(tai_regalloc.alloc(result));
+        end
+      else if RS_RDX in unusedregsint then
+        begin
+          dec(countunusedregsint);
+          exclude(unusedregsint,RS_RDX);
+          include(used_in_proc_int,RS_RDX);
+          result.number:=RS_RDX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
-              reg_user[R_EDX]:=curptree^;
+          reg_user[R_RDX]:=curptree^;
 {$endif TEMPREGDEBUG}
-              exprasmlist.concat(tai_regalloc.alloc(R_EDX));
-           end
-         else if R_EBX in unusedregsint then
-           begin
-              exclude(unusedregsint,R_EBX);
-              include(usedinproc,R_EBX);
-              getregisterint:=R_EBX;
+          exprasmlist.concat(tai_regalloc.alloc(result));
+        end
+      else if RS_RBX in unusedregsint then
+        begin
+          dec(countunusedregsint);
+          exclude(unusedregsint,RS_RBX);
+          include(used_in_proc_int,RS_RBX);
+          result.number:=RS_RBX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
-              reg_user[R_EBX]:=curptree^;
+          reg_user[R_RBX]:=curptree^;
 {$endif TEMPREGDEBUG}
-              exprasmlist.concat(tai_regalloc.alloc(R_EBX));
-           end
-         else if R_ECX in unusedregsint then
-           begin
-              exclude(unusedregsint,R_ECX);
-              include(usedinproc,R_ECX);
-              getregisterint:=R_ECX;
+          exprasmlist.concat(tai_regalloc.alloc(result));
+        end
+      else if RS_RCX in unusedregsint then
+        begin
+          dec(countunusedregsint);
+          exclude(unusedregsint,RS_RCX);
+          include(used_in_proc_int,RS_RCX);
+          result.number:=RS_RCX shl 8 or subreg;
 {$ifdef TEMPREGDEBUG}
-              reg_user[R_ECX]:=curptree^;
+          reg_user[R_RCX]:=curptree^;
 {$endif TEMPREGDEBUG}
-              exprasmlist.concat(tai_regalloc.alloc(R_ECX));
-           end
-         else internalerror(10);
+          exprasmlist.concat(tai_regalloc.alloc(result));
+        end
+      else
+        internalerror(10);
 {$ifdef TEMPREGDEBUG}
-         testregisters;
+      testregisters;
 {$endif TEMPREGDEBUG}
-      end;
+    end;
+
+
 
     procedure trgcpu.ungetregisterint(list: taasmoutput; r : tregister);
+      var supreg:Tsuperregister;
       begin
-         if r=R_NO then
+         if r.enum=R_NO then
           exit;
-         r := makeregsize(r,OS_INT);
-         if (r = R_EDI) or
-            ((not assigned(procinfo._class)) and (r = R_ESI)) then
+         if r.enum<>R_INTREGISTER then
+            internalerror(200301234);
+         supreg:=r.number shr 8;
+         if (supreg in [RS_RDI]) then
            begin
              list.concat(tai_regalloc.DeAlloc(r));
              exit;
            end;
-         if not(r in [R_EAX,R_EBX,R_ECX,R_EDX]) then
+         if not(supreg in [RS_RAX,RS_RBX,RS_RCX,RS_RDX,RS_RSI]) then
            exit;
          inherited ungetregisterint(list,r);
       end;
 
 
-   function trgcpu.getexplicitregisterint(list: taasmoutput; r : tregister) : tregister;
-     begin
-       if r in [R_ESI,R_EDI] then
-         begin
-           list.concat(tai_regalloc.Alloc(r));
-           getexplicitregisterint := r;
-           exit;
-         end;
-       result := inherited getexplicitregisterint(list,r);
+   function trgcpu.getexplicitregisterint(list: taasmoutput; r : tnewregister) : tregister;
+
+   var r2:Tregister;
+
+    begin
+      if (r shr 8) in [RS_RDI] then
+        begin
+          r2.enum:=R_INTREGISTER;
+          r2.number:=r;
+          list.concat(Tai_regalloc.alloc(r2));
+          getexplicitregisterint:=r2;
+          exit;
+        end;
+      result:=inherited getexplicitregisterint(list,r);
     end;
 
 
@@ -286,7 +295,7 @@ unit rgcpu;
       begin
         { note: don't return R_ST0, see comments above implementation of }
         { a_loadfpu_* methods in cgcpu (JM)                              }
-        result := R_ST;
+        result.enum := R_ST;
       end;
 
 
@@ -305,127 +314,6 @@ unit rgcpu;
          ungetregisterint(list,ref.index);
       end;
 
-
-    procedure trgcpu.pushusedregisters(list: taasmoutput;
-        var pushed : tpushedsaved; const s: tregisterset);
-
-      var
-        r: tregister;
-{$ifdef SUPPORT_MMX}
-        hr : treference;
-{$endif SUPPORT_MMX}
-      begin
-        usedinproc:=usedinproc + s;
-        for r:=R_EAX to R_EBX do
-          begin
-            pushed[r].pushed:=false;
-            { if the register is used by the calling subroutine    }
-            if not is_reg_var[r] and
-               (r in s) and
-               { and is present in use }
-               not(r in unusedregsint) then
-              begin
-                { then save it }
-                list.concat(Taicpu.Op_reg(A_PUSH,S_L,r));
-                include(unusedregsint,r);
-                inc(countunusedregsint);
-                pushed[r].pushed:=true;
-              end;
-          end;
-{$ifdef SUPPORT_MMX}
-        for r:=R_MM0 to R_MM6 do
-          begin
-            pushed[r].pushed:=false;
-            { if the register is used by the calling subroutine    }
-            if not is_reg_var[r] and
-               (r in s) and
-               { and is present in use }
-               not(r in unusedregsmm) then
-              begin
-                list.concat(Taicpu.Op_const_reg(A_SUB,S_L,8,R_ESP));
-                reference_reset_base(hr,R_ESP,0);
-                list.concat(Taicpu.Op_reg_ref(A_MOVQ,S_NO,r,hr));
-                include(unusedregsmm,r);
-                inc(countunusedregsmm);
-                pushed[r].pushed:=true;
-              end;
-          end;
-{$endif SUPPORT_MMX}
-{$ifdef TEMPREGDEBUG}
-        testregisters;
-{$endif TEMPREGDEBUG}
-      end;
-
-
-    procedure trgcpu.popusedregisters(list: taasmoutput;
-        const pushed : tpushedsaved);
-
-      var
-        r : tregister;
-{$ifdef SUPPORT_MMX}
-        hr : treference;
-{$endif SUPPORT_MMX}
-      begin
-        { restore in reverse order: }
-{$ifdef SUPPORT_MMX}
-        for r:=R_MM6 downto R_MM0 do
-          if pushed[r].pushed then
-            begin
-              reference_reset_base(hr,R_ESP,0);
-              list.concat(Taicpu.Op_ref_reg(
-                A_MOVQ,S_NO,hr,r));
-              list.concat(Taicpu.Op_const_reg(
-                A_ADD,S_L,8,R_ESP));
-              if not (r in unusedregsmm) then
-                { internalerror(10)
-                  in cg386cal we always restore regs
-                  that appear as used
-                  due to a unused tmep storage PM }
-              else
-                dec(countunusedregsmm);
-              exclude(unusedregsmm,r);
-            end;
-{$endif SUPPORT_MMX}
-        for r:=R_EBX downto R_EAX do
-          if pushed[r].pushed then
-            begin
-              list.concat(Taicpu.Op_reg(A_POP,S_L,r));
-              if not (r in unusedregsint) then
-                { internalerror(10)
-                  in cg386cal we always restore regs
-                  that appear as used
-                  due to a unused tmep storage PM }
-              else
-                dec(countunusedregsint);
-              exclude(unusedregsint,r);
-            end;
-{$ifdef TEMPREGDEBUG}
-        testregisters;
-{$endif TEMPREGDEBUG}
-      end;
-
-    procedure trgcpu.saveusedregisters(list: taasmoutput;var saved : tpushedsaved;
-      const s: tregisterset);
-
-      begin
-        if (CS_LittleSize in aktglobalswitches) then
-          pushusedregisters(list,saved,s)
-        else
-          inherited saveusedregisters(list,saved,s);
-      end;
-
-
-    procedure trgcpu.restoreusedregisters(list: taasmoutput;
-      const saved : tpushedsaved);
-
-      begin
-        if (CS_LittleSize in aktglobalswitches) then
-          popusedregisters(list,saved)
-        else
-          inherited restoreusedregisters(list,saved);
-      end;
-
-
    procedure trgcpu.resetusableregisters;
 
      begin
@@ -437,7 +325,7 @@ unit rgcpu;
    function trgcpu.correct_fpuregister(r : tregister;ofs : byte) : tregister;
 
      begin
-        correct_fpuregister:=tregister(longint(r)+ofs);
+        correct_fpuregister.enum:=toldregister(longint(r.enum)+ofs);
      end;
 
 
@@ -468,12 +356,19 @@ unit rgcpu;
 
 
 initialization
-  rg := trgcpu.create;
+  rg := trgcpu.create(15);
 end.
 
 {
   $Log$
-  Revision 1.3  2003-01-05 13:36:54  florian
+  Revision 1.5  2003-06-13 21:19:33  peter
+    * current_procdef removed, use current_procinfo.procdef instead
+
+  Revision 1.4  2002/04/25 20:15:40  florian
+    * block nodes within expressions shouldn't release the used registers,
+      fixed using a flag till the new rg is ready
+
+  Revision 1.3  2003/01/05 13:36:54  florian
     * x86-64 compiles
     + very basic support for float128 type (x86-64 only)