1 {
2     Copyright (c) 2002 by Florian Klaempfl
3 
4     Generates the argument location information for i386
5 
6     This program is free software; you can redistribute it and/or modify
7     it under the terms of the GNU General Public License as published by
8     the Free Software Foundation; either version 2 of the License, or
9     (at your option) any later version.
10 
11     This program is distributed in the hope that it will be useful,
12     but WITHOUT ANY WARRANTY; without even the implied warranty of
13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14     GNU General Public License for more details.
15 
16     You should have received a copy of the GNU General Public License
17     along with this program; if not, write to the Free Software
18     Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
19 
20  ****************************************************************************
21 }
22 unit cpupara;
23 
24 {$i fpcdefs.inc}
25 
26   interface
27 
28     uses
29        globtype,
30        aasmtai,aasmdata,cpubase,cgbase,cgutils,
31        symconst,symtype,symsym,symdef,
32        parabase,paramgr;
33 
34     type
35        tcpuparamanager = class(tparamanager)
param_use_paralocnull36           function param_use_paraloc(const cgpara:tcgpara):boolean;override;
ret_in_paramnull37           function ret_in_param(def:tdef;pd:tabstractprocdef):boolean;override;
push_addr_paramnull38           function push_addr_param(varspez:tvarspez;def : tdef;calloption : tproccalloption) : boolean;override;
get_para_alignnull39           function get_para_align(calloption : tproccalloption):byte;override;
get_volatile_registers_intnull40           function get_volatile_registers_int(calloption : tproccalloption):tcpuregisterset;override;
get_volatile_registers_fpunull41           function get_volatile_registers_fpu(calloption : tproccalloption):tcpuregisterset;override;
get_volatile_registers_mmnull42           function get_volatile_registers_mm(calloption : tproccalloption):tcpuregisterset;override;
get_saved_registers_intnull43           function get_saved_registers_int(calloption : tproccalloption):tcpuregisterarray;override;
create_paraloc_infonull44           function create_paraloc_info(p : tabstractprocdef; side: tcallercallee):longint;override;
create_varargs_paraloc_infonull45           function create_varargs_paraloc_info(p : tabstractprocdef; varargspara:tvarargsparalist):longint;override;
46           procedure createtempparaloc(list: TAsmList;calloption : tproccalloption;parasym : tparavarsym;can_use_final_stack_loc : boolean;var cgpara:TCGPara);override;
get_funcretlocnull47           function get_funcretloc(p : tabstractprocdef; side: tcallercallee; forcetempdef: tdef): TCGPara;override;
48        private
49           procedure create_stdcall_paraloc_info(p : tabstractprocdef; side: tcallercallee;paras:tparalist;var parasize:longint);
50           procedure create_register_paraloc_info(p : tabstractprocdef; side: tcallercallee;paras:tparalist;var parareg,parasize:longint);
51        end;
52 
53 
54   implementation
55 
56     uses
57        cutils,sysutils,
58        systems,verbose,
59        symtable,
60        defutil;
61 
62       const
63         parasupregs : array[0..2] of tsuperregister = (RS_EAX,RS_EDX,RS_ECX);
64 
65 {****************************************************************************
66                                 tcpuparamanager
67 ****************************************************************************}
68 
tcpuparamanager.param_use_paralocnull69     function tcpuparamanager.param_use_paraloc(const cgpara:tcgpara):boolean;
70       var
71         paraloc : pcgparalocation;
72       begin
73         if not assigned(cgpara.location) then
74           internalerror(200410102);
75         result:=true;
76         { All locations are LOC_REFERENCE }
77         paraloc:=cgpara.location;
78         while assigned(paraloc) do
79           begin
80             if (paraloc^.loc<>LOC_REFERENCE) then
81               begin
82                 result:=false;
83                 exit;
84               end;
85             paraloc:=paraloc^.next;
86           end;
87       end;
88 
89 
tcpuparamanager.ret_in_paramnull90     function tcpuparamanager.ret_in_param(def:tdef;pd:tabstractprocdef):boolean;
91       var
92         size: longint;
93       begin
94         if handle_common_ret_in_param(def,pd,result) then
95           exit;
96         case target_info.system of
97           system_i386_win32 :
98             begin
99               case def.typ of
100                 recorddef :
101                   begin
102                     { Win32 GCC returns small records in the FUNCTION_RETURN_REG up to 8 bytes in registers.
103 
104                       For stdcall and register we follow delphi instead of GCC which returns
105                       only records of a size of 1,2 or 4 bytes in FUNCTION_RETURN_REG }
106                     if ((pd.proccalloption in [pocall_stdcall,pocall_register]) and
107                         (def.size in [1,2,4])) or
108                        ((pd.proccalloption in cdecl_pocalls) and
109                         (def.size>0) and
110                         (def.size<=8)) then
111                      begin
112                        result:=false;
113                        exit;
114                      end;
115                   end;
116               end;
117             end;
118           system_i386_os2,
119           system_i386_emx:
120             begin
121               case def.typ of
122                 recorddef :
123                   begin
124                     { EMX port of GCC returns small records in the FUNCTION_RETURN_REG up to 4 bytes in registers. }
125                     if ((pd.proccalloption in cdecl_pocalls) and
126                         (def.size>0) and
127                         (def.size<=4)) then
128                      begin
129                        result:=false;
130                        exit;
131                      end;
132                   end;
133               end;
134             end;
135           system_i386_freebsd,
136           system_i386_openbsd,
137           system_i386_darwin,
138           system_i386_iphonesim :
139             begin
140               if pd.proccalloption in cdecl_pocalls then
141                 begin
142                   case def.typ of
143                     recorddef :
144                       begin
145                         size:=def.size;
146                         if (size>0) and
147                            (size<=8) and
148                            { only if size is a power of 2 }
149                            ((size and (size-1)) = 0) then
150                           begin
151                             result:=false;
152                             exit;
153                           end;
154                       end;
155                     procvardef:
156                       begin
157                         result:=false;
158                         exit;
159                       end;
160                   end;
161               end;
162             end;
163         end;
164         result:=inherited ret_in_param(def,pd);
165       end;
166 
167 
tcpuparamanager.push_addr_paramnull168     function tcpuparamanager.push_addr_param(varspez:tvarspez;def : tdef;calloption : tproccalloption) : boolean;
169       begin
170         result:=false;
171         { var,out,constref always require address }
172         if varspez in [vs_var,vs_out,vs_constref] then
173           begin
174             result:=true;
175             exit;
176           end;
177         { Only vs_const, vs_value here }
178         case def.typ of
179           variantdef :
180             begin
181               { variants are small enough to be passed by value except if
182                 required by the windows api
183 
184                 variants are somethings very delphi/windows specific so do it like
185                 windows/delphi (FK)
186               }
187               if ((target_info.system=system_i386_win32) and
188                  (calloption in [pocall_stdcall,pocall_safecall]) and
189                  (varspez=vs_const)) or
190                  (calloption=pocall_register) then
191                 result:=true
192               else
193                 result:=false;
194             end;
195           formaldef :
196             result:=true;
197           recorddef :
198             begin
199               { Delphi stdcall passes records on the stack for call by value }
200               if (target_info.system=system_i386_win32) and
201                  (calloption=pocall_stdcall) and
202                  (varspez=vs_value) then
203                 result:=false
204               else
205                 result:=
206                   (not(calloption in (cdecl_pocalls)) and
207                    (def.size>sizeof(aint))) or
208                   (((calloption = pocall_mwpascal) or (target_info.system=system_i386_wince)) and
209                    (varspez=vs_const));
210             end;
211           arraydef :
212             begin
213               { array of const values are pushed on the stack as
214                 well as dyn. arrays }
215               if (calloption in cdecl_pocalls) then
216                 result:=not(is_array_of_const(def) or
217                         is_dynamic_array(def))
218               else
219                 begin
220                   result:=(
221                            (tarraydef(def).highrange>=tarraydef(def).lowrange) and
222                            (def.size>sizeof(aint))
223                           ) or
224                           is_open_array(def) or
225                           is_array_of_const(def) or
226                           is_array_constructor(def);
227                 end;
228             end;
229           objectdef :
230             result:=is_object(def);
231           stringdef :
232             result:= (tstringdef(def).stringtype in [st_shortstring,st_longstring]);
233           procvardef :
234             result:=not(calloption in cdecl_pocalls) and not tprocvardef(def).is_addressonly;
235           setdef :
236             result:=not(calloption in cdecl_pocalls) and (not is_smallset(def));
237         end;
238       end;
239 
240 
tcpuparamanager.get_para_alignnull241     function tcpuparamanager.get_para_align(calloption : tproccalloption):byte;
242       begin
243         if calloption=pocall_oldfpccall then
244           begin
245             if target_info.system in [system_i386_go32v2,system_i386_watcom] then
246               result:=2
247             else
248               result:=4;
249           end
250         else
251           result:=std_param_align;
252       end;
253 
254 
tcpuparamanager.get_volatile_registers_intnull255     function tcpuparamanager.get_volatile_registers_int(calloption : tproccalloption):tcpuregisterset;
256       begin
257         case calloption of
258           pocall_internproc :
259             result:=[];
260           pocall_register,
261           pocall_safecall,
262           pocall_stdcall,
263           pocall_cdecl,
264           pocall_syscall,
265           pocall_cppdecl,
266           pocall_mwpascal,
267           pocall_pascal:
268             result:=[RS_EAX,RS_EDX,RS_ECX];
269           pocall_far16,
270           pocall_oldfpccall :
271             result:=[RS_EAX,RS_EDX,RS_ECX,RS_ESI,RS_EDI,RS_EBX];
272           else
273             internalerror(200309071);
274         end;
275       end;
276 
277 
tcpuparamanager.get_volatile_registers_fpunull278     function tcpuparamanager.get_volatile_registers_fpu(calloption : tproccalloption):tcpuregisterset;
279       begin
280         result:=[0..first_fpu_imreg-1];
281       end;
282 
283 
tcpuparamanager.get_volatile_registers_mmnull284     function tcpuparamanager.get_volatile_registers_mm(calloption : tproccalloption):tcpuregisterset;
285       begin
286         result:=[0..first_mm_imreg-1];
287       end;
288 
289 
tcpuparamanager.get_saved_registers_intnull290     function tcpuparamanager.get_saved_registers_int(calloption : tproccalloption):tcpuregisterarray;
291       const
292         saveregs : array[0..3] of tsuperregister = (RS_EBX,RS_ESI,RS_EDI,RS_EBP);
293         saveregs_oldfpccall : array[0..0] of tsuperregister = (RS_EBP);
294       begin
295         case calloption of
296           pocall_internproc,
297           pocall_register,
298           pocall_safecall,
299           pocall_stdcall,
300           pocall_cdecl,
301           pocall_syscall,
302           pocall_cppdecl,
303           pocall_mwpascal,
304           pocall_pascal:
305             result:=saveregs;
306           pocall_far16,
307           pocall_oldfpccall :
308             result:=saveregs_oldfpccall;
309           else
310             internalerror(2018050401);
311         end;
312       end;
313 
314 
tcpuparamanager.get_funcretlocnull315     function  tcpuparamanager.get_funcretloc(p : tabstractprocdef; side: tcallercallee; forcetempdef: tdef): TCGPara;
316       var
317         retcgsize  : tcgsize;
318         paraloc : pcgparalocation;
319         fdef,
320         usedef: tdef;
321         handled: boolean;
322       begin
323         if not assigned(forcetempdef) then
324           usedef:=p.returndef
325         else
326           usedef:=forcetempdef;
327         { on darwin/i386, if a record has only one field and that field is a
328           single or double, it has to be returned like a single/double }
329         if (target_info.system in [system_i386_darwin,system_i386_iphonesim,
330                                    system_i386_freebsd,system_i386_openbsd,
331                                    system_i386_os2,system_i386_emx]) and
332            ((usedef.typ=recorddef) or
333             is_object(usedef)) and
334            tabstractrecordsymtable(tabstractrecorddef(usedef).symtable).has_single_field(fdef) and
335            (fdef.typ=floatdef) and
336            (tfloatdef(fdef).floattype in [s32real,s64real]) then
337           usedef:=fdef;
338 
339         handled:=set_common_funcretloc_info(p,usedef,retcgsize,result);
340         { normally forcetempdef is passed straight through to
341           set_common_funcretloc_info and that one will correctly determine whether
342           the location is a temporary one, but that doesn't work here because we
343           sometimes have to change the type }
344         result.temporary:=assigned(forcetempdef);
345         if handled then
346           exit;
347 
348         { darwin/x86 requires that results < sizeof(aint) are sign/zero
349           extended to sizeof(aint) }
350         if (target_info.system in [system_i386_darwin,system_i386_iphonesim]) and
351            (side=calleeside) and
352            (result.intsize>0) and
353            (result.intsize<sizeof(aint)) then
354           begin
355             result.def:=sinttype;
356             result.intsize:=sizeof(aint);
357             retcgsize:=OS_SINT;
358             result.size:=retcgsize;
359           end;
360 
361         { Return in FPU register? }
362         if result.def.typ=floatdef then
363           begin
364             paraloc:=result.add_location;
365             paraloc^.loc:=LOC_FPUREGISTER;
366             paraloc^.register:=NR_FPU_RESULT_REG;
367             paraloc^.size:=retcgsize;
368             paraloc^.def:=result.def;
369           end
370         else
371          { Return in register }
372           begin
373             paraloc:=result.add_location;
374             paraloc^.loc:=LOC_REGISTER;
375             if retcgsize in [OS_64,OS_S64] then
376              begin
377                { low 32bits }
378                if side=callerside then
379                  paraloc^.register:=NR_FUNCTION_RESULT64_LOW_REG
380                else
381                  paraloc^.register:=NR_FUNCTION_RETURN64_LOW_REG;
382                paraloc^.size:=OS_32;
383                paraloc^.def:=u32inttype;
384 
385                { high 32bits }
386                paraloc:=result.add_location;
387                paraloc^.loc:=LOC_REGISTER;
388                if side=callerside then
389                  paraloc^.register:=NR_FUNCTION_RESULT64_HIGH_REG
390                else
391                  paraloc^.register:=NR_FUNCTION_RETURN64_HIGH_REG;
392                paraloc^.size:=OS_32;
393                paraloc^.def:=u32inttype;
394              end
395             else
396              begin
397                paraloc^.size:=retcgsize;
398                paraloc^.def:=result.def;
399                if side=callerside then
400                  paraloc^.register:=newreg(R_INTREGISTER,RS_FUNCTION_RESULT_REG,cgsize2subreg(R_INTREGISTER,retcgsize))
401                else
402                  paraloc^.register:=newreg(R_INTREGISTER,RS_FUNCTION_RETURN_REG,cgsize2subreg(R_INTREGISTER,retcgsize));
403              end;
404           end;
405       end;
406 
407 
408     procedure tcpuparamanager.create_stdcall_paraloc_info(p : tabstractprocdef; side: tcallercallee;paras:tparalist;var parasize:longint);
409       var
410         i  : integer;
411         hp : tparavarsym;
412         paradef : tdef;
413         paraloc : pcgparalocation;
414         l,
415         paralen,
416         varalign   : longint;
417         paraalign  : shortint;
418         paracgsize : tcgsize;
419         firstparaloc,
420         pushaddr   : boolean;
421       begin
422         paraalign:=get_para_align(p.proccalloption);
423         { we push Flags and CS as long
424           to cope with the IRETD
425           and we save 6 register + 4 selectors }
426         if (po_interrupt in p.procoptions) and (side=calleeside) then
427           inc(parasize,8+6*4+4*2);
428         { Offset is calculated like:
429            sub esp,12
430            mov [esp+8],para3
431            mov [esp+4],para2
432            mov [esp],para1
433            call function
434           That means for pushes the para with the
435           highest offset (see para3) needs to be pushed first
436         }
437         if p.proccalloption in pushleftright_pocalls then
438           i:=paras.count-1
439         else
440           i:=0;
441         while ((p.proccalloption in pushleftright_pocalls) and (i>=0)) or
442               (not(p.proccalloption in pushleftright_pocalls) and (i<=paras.count-1)) do
443           begin
444             hp:=tparavarsym(paras[i]);
445             paradef:=hp.vardef;
446 
447             { syscall for AROS can have already a paraloc set }
448             if (vo_has_explicit_paraloc in hp.varoptions) then
449               begin
450                 if not(vo_is_syscall_lib in hp.varoptions) then
451                   internalerror(2016090105);
452                 if p.proccalloption in pushleftright_pocalls then
453                   dec(i)
454                 else
455                   inc(i);
456                 continue;
457               end;
458 
459             pushaddr:=push_addr_param(hp.varspez,paradef,p.proccalloption);
460             if pushaddr then
461               begin
462                 paralen:=sizeof(aint);
463                 paracgsize:=OS_ADDR;
464                 paradef:=cpointerdef.getreusable_no_free(paradef);
465               end
466             else
467               begin
468                 paralen:=push_size(hp.varspez,paradef,p.proccalloption);
469                 { darwin/x86 requires that parameters < sizeof(aint) are sign/ }
470                 { zero extended to sizeof(aint)                                }
471                 if (target_info.system in [system_i386_darwin,system_i386_iphonesim]) and
472                    (side = callerside) and
473                    (paralen > 0) and
474                    (paralen < sizeof(aint)) then
475                   begin
476                     paralen:=sizeof(aint);
477                     paracgsize:=OS_SINT;
478                     paradef:=sinttype;
479                   end
480                 else
481                   paracgsize:=def_cgsize(paradef);
482               end;
483             hp.paraloc[side].reset;
484             hp.paraloc[side].size:=paracgsize;
485             hp.paraloc[side].intsize:=paralen;
486             hp.paraloc[side].def:=paradef;
487             hp.paraloc[side].Alignment:=paraalign;
488             { Copy to stack? }
489             if (paracgsize=OS_NO) or
490                (use_fixed_stack) then
491               begin
492                 paraloc:=hp.paraloc[side].add_location;
493                 paraloc^.loc:=LOC_REFERENCE;
494                 paraloc^.size:=paracgsize;
495                 paraloc^.def:=paradef;
496                 if side=callerside then
497                   paraloc^.reference.index:=NR_STACK_POINTER_REG
498                 else
499                   paraloc^.reference.index:=NR_FRAME_POINTER_REG;
500                 varalign:=used_align(size_2_align(paralen),paraalign,paraalign);
501 
502                 { don't let push_size return 16, because then we can    }
503                 { read past the end of the heap since the value is only }
504                 { 10 bytes long (JM)                                    }
505                 if (paracgsize = OS_F80) and
506                    (target_info.system in [system_i386_darwin,system_i386_iphonesim]) then
507                   paralen:=16;
508                 paraloc^.reference.offset:=parasize;
509                 if side=calleeside then
510                   inc(paraloc^.reference.offset,target_info.first_parm_offset);
511                 parasize:=align(parasize+paralen,varalign);
512               end
513             else
514               begin
515                 if paralen=0 then
516                   internalerror(200501163);
517                 firstparaloc:=true;
518                 while (paralen>0) do
519                   begin
520                     paraloc:=hp.paraloc[side].add_location;
521                     paraloc^.loc:=LOC_REFERENCE;
522                     { single and double need a single location }
523                     if (paracgsize in [OS_F64,OS_F32]) then
524                       begin
525                         paraloc^.size:=paracgsize;
526                         paraloc^.def:=paradef;
527                         l:=paralen;
528                       end
529                     else
530                       begin
531                         { We can allocate at maximum 32 bits per location }
532                         if paralen>sizeof(aint) then
533                           begin
534                             l:=sizeof(aint);
535                             paraloc^.def:=uinttype;
536                           end
537                         else
538                           begin
539                             l:=paralen;
540                             paraloc^.def:=get_paraloc_def(paradef,l,firstparaloc);
541                           end;
542                         paraloc^.size:=int_cgsize(l);
543                       end;
544                     if (side=callerside) or
545                        (po_nostackframe in p.procoptions) then
546                       paraloc^.reference.index:=NR_STACK_POINTER_REG
547                     else
548                       paraloc^.reference.index:=NR_FRAME_POINTER_REG;
549                     varalign:=used_align(size_2_align(l),paraalign,paraalign);
550                     paraloc^.reference.offset:=parasize;
551                     if side=calleeside then
552                       if not(po_nostackframe in p.procoptions) then
553                         inc(paraloc^.reference.offset,target_info.first_parm_offset)
554                       else
555                         { return addres }
556                         inc(paraloc^.reference.offset,4);
557                     parasize:=align(parasize+l,varalign);
558                     dec(paralen,l);
559                     firstparaloc:=false;
560                   end;
561               end;
562             if p.proccalloption in pushleftright_pocalls then
563               dec(i)
564             else
565               inc(i);
566           end;
567       end;
568 
569 
570     procedure tcpuparamanager.create_register_paraloc_info(p : tabstractprocdef; side: tcallercallee;paras:tparalist;
571                                                             var parareg,parasize:longint);
572       var
573         hp : tparavarsym;
574         paradef : tdef;
575         paraloc : pcgparalocation;
576         paracgsize : tcgsize;
577         i : integer;
578         l,
579         paralen,
580         varalign : longint;
581         paraalign : shortint;
582         pass : byte;
583         firstparaloc,
584         pushaddr : boolean;
585       begin
586         if paras.count=0 then
587           exit;
588         paraalign:=get_para_align(p.proccalloption);
589 
590         { clean up here so we can later detect properly if a parameter has been
591           assigned or not
592         }
593         for i:=0 to paras.count-1 do
594           tparavarsym(paras[i]).paraloc[side].reset;
595         { Register parameters are assigned from left to right,
596           stack parameters from right to left so assign first the
597           register parameters in a first pass, in the second
598           pass all unhandled parameters are done }
599         for pass:=1 to 2 do
600           begin
601             if pass=1 then
602               i:=0
603             else
604               i:=paras.count-1;
605             while true do
606               begin
607                 hp:=tparavarsym(paras[i]);
608                 paradef:=hp.vardef;
609                 if not(assigned(hp.paraloc[side].location)) then
610                   begin
611                     pushaddr:=push_addr_param(hp.varspez,hp.vardef,p.proccalloption);
612                     if pushaddr then
613                       begin
614                         paralen:=sizeof(aint);
615                         paracgsize:=OS_ADDR;
616                         paradef:=cpointerdef.getreusable_no_free(paradef);
617                       end
618                     else
619                       begin
620                         paralen:=push_size(hp.varspez,hp.vardef,p.proccalloption);
621                         paracgsize:=def_cgsize(hp.vardef);
622                       end;
623                     hp.paraloc[side].size:=paracgsize;
624                     hp.paraloc[side].intsize:=paralen;
625                     hp.paraloc[side].Alignment:=paraalign;
626                     hp.paraloc[side].def:=paradef;
627                     {
628                       EAX
629                       EDX
630                       ECX
631                       Stack
632                       Stack
633 
634                       64bit values,floats,arrays and records are always
635                       on the stack.
636 
637                       In case of po_delphi_nested_cc, the parent frame pointer
638                       is also always passed on the stack.
639                     }
640                     if (parareg<=high(parasupregs)) and
641                        (paralen<=sizeof(aint)) and
642                        (not(hp.vardef.typ in [floatdef,recorddef,arraydef]) or
643                         pushaddr or
644                         is_dynamic_array(hp.vardef)) and
645                        (not(vo_is_parentfp in hp.varoptions) or
646                         not(po_delphi_nested_cc in p.procoptions)) then
647                       begin
648                         if pass=1 then
649                           begin
650                             paraloc:=hp.paraloc[side].add_location;
651                             paraloc^.size:=paracgsize;
652                             paraloc^.def:=paradef;
653                             paraloc^.loc:=LOC_REGISTER;
654                             paraloc^.register:=newreg(R_INTREGISTER,parasupregs[parareg],cgsize2subreg(R_INTREGISTER,paracgsize));
655                             inc(parareg);
656                           end;
657                       end
658                     else
659                       if pass=2 then
660                         begin
661                           { Copy to stack? }
662                           if (use_fixed_stack) or
663                              (paracgsize=OS_NO) then
664                             begin
665                               paraloc:=hp.paraloc[side].add_location;
666                               paraloc^.loc:=LOC_REFERENCE;
667                               paraloc^.size:=paracgsize;
668                               paraloc^.def:=paradef;
669                               if side=callerside then
670                                 paraloc^.reference.index:=NR_STACK_POINTER_REG
671                               else
672                                 paraloc^.reference.index:=NR_FRAME_POINTER_REG;
673                               varalign:=used_align(size_2_align(paralen),paraalign,paraalign);
674                               paraloc^.reference.offset:=parasize;
675                               if side=calleeside then
676                                 inc(paraloc^.reference.offset,target_info.first_parm_offset);
677                               parasize:=align(parasize+paralen,varalign);
678                             end
679                           else
680                             begin
681                               if paralen=0 then
682                                 internalerror(200501163);
683                               firstparaloc:=true;
684                               while (paralen>0) do
685                                 begin
686                                   paraloc:=hp.paraloc[side].add_location;
687                                   paraloc^.loc:=LOC_REFERENCE;
688                                   { Extended and double need a single location }
689                                   if (paracgsize in [OS_F64,OS_F32]) then
690                                     begin
691                                       paraloc^.size:=paracgsize;
692                                       paraloc^.def:=paradef;
693                                       l:=paralen;
694                                     end
695                                   else
696                                     begin
697                                       { We can allocate at maximum 32 bits per location }
698                                       if paralen>sizeof(aint) then
699                                         begin
700                                           l:=sizeof(aint);
701                                           paraloc^.def:=uinttype;
702                                         end
703                                       else
704                                         begin
705                                           l:=paralen;
706                                           paraloc^.def:=get_paraloc_def(paradef,l,firstparaloc);
707                                         end;
708                                       paraloc^.size:=int_cgsize(l);
709                                     end;
710                                   if side=callerside then
711                                     paraloc^.reference.index:=NR_STACK_POINTER_REG
712                                   else
713                                     paraloc^.reference.index:=NR_FRAME_POINTER_REG;
714                                   varalign:=used_align(size_2_align(l),paraalign,paraalign);
715                                   paraloc^.reference.offset:=parasize;
716                                   if side=calleeside then
717                                     inc(paraloc^.reference.offset,target_info.first_parm_offset);
718                                   parasize:=align(parasize+l,varalign);
719                                   dec(paralen,l);
720                                   firstparaloc:=false;
721                                 end;
722                             end;
723                         end;
724                   end;
725                 case pass of
726                   1:
727                     begin
728                       if i=paras.count-1 then
729                         break;
730                       inc(i);
731                     end;
732                   2:
733                     begin
734                       if i=0 then
735                         break;
736                       dec(i);
737                     end;
738                 end;
739               end;
740           end;
741       end;
742 
743 
tcpuparamanager.create_paraloc_infonull744     function tcpuparamanager.create_paraloc_info(p : tabstractprocdef; side: tcallercallee):longint;
745       var
746         parasize,
747         parareg : longint;
748       begin
749         parasize:=0;
750         parareg:=0;
751         case p.proccalloption of
752           pocall_register :
753             create_register_paraloc_info(p,side,p.paras,parareg,parasize);
754           pocall_internproc :
755             begin
756               { Use default calling }
757 {$warnings off}
758               if (pocall_default=pocall_register) then
759                 create_register_paraloc_info(p,side,p.paras,parareg,parasize)
760               else
761                 create_stdcall_paraloc_info(p,side,p.paras,parasize);
762 {$warnings on}
763             end;
764           else
765             create_stdcall_paraloc_info(p,side,p.paras,parasize);
766         end;
767         create_funcretloc_info(p,side);
768         result:=parasize;
769       end;
770 
771 
tcpuparamanager.create_varargs_paraloc_infonull772     function tcpuparamanager.create_varargs_paraloc_info(p : tabstractprocdef; varargspara:tvarargsparalist):longint;
773       var
774         parasize : longint;
775       begin
776         parasize:=0;
777         { calculate the registers for the normal parameters }
778         create_stdcall_paraloc_info(p,callerside,p.paras,parasize);
779         { append the varargs }
780         create_stdcall_paraloc_info(p,callerside,varargspara,parasize);
781         result:=parasize;
782       end;
783 
784 
785     procedure tcpuparamanager.createtempparaloc(list: TAsmList;calloption : tproccalloption;parasym : tparavarsym;can_use_final_stack_loc : boolean;var cgpara:TCGPara);
786       begin
787         { Never a need for temps when value is pushed (calls inside parameters
788           will simply allocate even more stack space for their parameters) }
789         if not(use_fixed_stack) then
790           can_use_final_stack_loc:=true;
791         inherited createtempparaloc(list,calloption,parasym,can_use_final_stack_loc,cgpara);
792       end;
793 
794 
795 begin
796    paramanager:=tcpuparamanager.create;
797 end.
798