1 {
2     Copyright (c) 2013-2014 by Jonas Maebe, Florian Klaempfl and others
3 
4     AArch64 specific calling conventions
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 { AArch64 specific calling conventions are handled by this unit
22 }
23 unit cpupara;
24 
25 {$i fpcdefs.inc}
26 
27   interface
28 
29     uses
30        globtype,globals,
31        aasmtai,aasmdata,
32        cpuinfo,cpubase,cgbase,cgutils,
33        symconst,symbase,symtype,symdef,parabase,paramgr;
34 
35     type
36        tcpuparamanager = class(tparamanager)
get_volatile_registers_intnull37           function get_volatile_registers_int(calloption: tproccalloption): tcpuregisterset; override;
get_volatile_registers_fpunull38           function get_volatile_registers_fpu(calloption: tproccalloption): tcpuregisterset; override;
get_volatile_registers_mmnull39           function get_volatile_registers_mm(calloption: tproccalloption): tcpuregisterset; override;
get_saved_registers_intnull40           function get_saved_registers_int(calloption: tproccalloption): tcpuregisterarray; override;
get_saved_registers_mmnull41           function get_saved_registers_mm(calloption: tproccalloption): tcpuregisterarray; override;
push_addr_paramnull42           function push_addr_param(varspez: tvarspez; def: tdef; calloption: tproccalloption): boolean; override;
ret_in_paramnull43           function ret_in_param(def: tdef; pd: tabstractprocdef):boolean;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;
get_funcretlocnull46           function get_funcretloc(p: tabstractprocdef; side: tcallercallee; forcetempdef: tdef): tcgpara;override;
param_use_paralocnull47           function param_use_paraloc(const cgpara: tcgpara): boolean; override;
48          private
49           curintreg,
50           curmmreg: tsuperregister;
51           curstackoffset: aword;
52 
53           procedure init_para_alloc_values;
54           procedure alloc_para(out result: tcgpara; p: tabstractprocdef; varspez: tvarspez; side: tcallercallee; paradef: tdef; isvariadic, isdelphinestedcc: boolean);
55 
56           procedure create_paraloc_info_intern(p: tabstractprocdef; side: tcallercallee; paras: tparalist; isvariadic: boolean);
57        end;
58 
59   implementation
60 
61     uses
62        verbose,systems,cutils,
63        rgobj,
64        defutil,symsym,symtable;
65 
66     const
67       RS_FIRST_INT_PARAM_SUPREG = RS_X0;
68       RS_LAST_INT_PARAM_SUPREG = RS_X7;
69       { Q0/D0/S0/H0/B0 all have the same superregister number }
70       RS_FIRST_MM_PARAM_SUPREG = RS_D0;
71       RS_LAST_MM_PARAM_SUPREG = RS_D7;
72 
73 
tcpuparamanager.get_volatile_registers_intnull74     function tcpuparamanager.get_volatile_registers_int(calloption : tproccalloption):tcpuregisterset;
75       begin
76         result:=VOLATILE_INTREGISTERS
77       end;
78 
79 
tcpuparamanager.get_volatile_registers_fpunull80     function tcpuparamanager.get_volatile_registers_fpu(calloption : tproccalloption):tcpuregisterset;
81       begin
82         result:=[];
83       end;
84 
85 
tcpuparamanager.get_volatile_registers_mmnull86     function tcpuparamanager.get_volatile_registers_mm(calloption: tproccalloption): tcpuregisterset;
87       begin
88         result:=VOLATILE_MMREGISTERS;
89       end;
90 
91 
tcpuparamanager.get_saved_registers_intnull92     function tcpuparamanager.get_saved_registers_int(calloption: tproccalloption): tcpuregisterarray;
93       const
94         saved_regs : array[0..9] of tsuperregister =
95           (RS_X19,RS_X20,RS_X21,RS_X22,RS_X23,RS_X24,RS_X25,RS_X26,RS_X27,RS_X28);
96       begin
97         result:=saved_regs;
98       end;
99 
100 
tcpuparamanager.get_saved_registers_mmnull101     function tcpuparamanager.get_saved_registers_mm(calloption: tproccalloption): tcpuregisterarray;
102       const
103         saved_mm_regs : array[0..7] of tsuperregister = (RS_D8,RS_D9,RS_D10,RS_D11,RS_D12,RS_D13,RS_D14,RS_D15);
104       begin
105         result:=saved_mm_regs;
106       end;
107 
108 
is_hfa_internalnull109     function is_hfa_internal(p: tdef; var basedef: tdef; var elecount: longint): boolean;
110       var
111         i: longint;
112         sym: tsym;
113         tmpelecount: longint;
114       begin
115         result:=false;
116         case p.typ of
117           arraydef:
118             begin
119               if is_special_array(p) then
120                 exit;
121               { an array of empty records has no influence }
122               if tarraydef(p).elementdef.size=0 then
123                 begin
124                   result:=true;
125                   exit
126                 end;
127               tmpelecount:=0;
128               if not is_hfa_internal(tarraydef(p).elementdef,basedef,tmpelecount) then
129                 exit;
130               { tmpelecount now contains the number of hfa elements in a
131                 single array element (e.g. 2 if it's an array of a record
132                 containing two singles) -> multiply by number of elements
133                 in the array }
134               inc(elecount,tarraydef(p).elecount*tmpelecount);
135               if elecount>4 then
136                 exit;
137               result:=true;
138             end;
139           floatdef:
140             begin
141               if not assigned(basedef) then
142                 basedef:=p
143               else if basedef<>p then
144                 exit;
145               inc(elecount);
146               result:=true;
147             end;
148           recorddef:
149             begin
150               for i:=0 to tabstractrecorddef(p).symtable.symlist.count-1 do
151                 begin
152                   sym:=tsym(tabstractrecorddef(p).symtable.symlist[i]);
153                   if sym.typ<>fieldvarsym then
154                     continue;
155                   if not is_hfa_internal(tfieldvarsym(sym).vardef,basedef,elecount) then
156                     exit
157                 end;
158               result:=true;
159             end;
160           else
161             exit
162         end;
163       end;
164 
165 
166     { Returns whether a def is a "homogeneous float array" at the machine level.
167       This means that in the memory layout, the def only consists of maximally
168       4 floating point values that appear consecutively in memory }
is_hfanull169     function is_hfa(p: tdef; out basedef: tdef) : boolean;
170       var
171         elecount: longint;
172       begin
173         result:=false;
174         basedef:=nil;
175         elecount:=0;
176         result:=is_hfa_internal(p,basedef,elecount);
177         result:=
178           result and
179           (elecount>0) and
180           (elecount<=4) and
181           (p.size=basedef.size*elecount)
182       end;
183 
184 
getparalocnull185     function getparaloc(calloption: tproccalloption; p: tdef): tcgloc;
186       var
187         hfabasedef: tdef;
188       begin
189          { Later, the LOC_REFERENCE is in most cases changed into LOC_REGISTER
190            if push_addr_param for the def is true
191          }
192          case p.typ of
193             orddef:
194               getparaloc:=LOC_REGISTER;
195             floatdef:
196               getparaloc:=LOC_MMREGISTER;
197             enumdef:
198               getparaloc:=LOC_REGISTER;
199             pointerdef:
200               getparaloc:=LOC_REGISTER;
201             formaldef:
202               getparaloc:=LOC_REGISTER;
203             classrefdef:
204               getparaloc:=LOC_REGISTER;
205             recorddef:
206               if not is_hfa(p,hfabasedef) then
207                 getparaloc:=LOC_REGISTER
208               else
209                 getparaloc:=LOC_MMREGISTER;
210             objectdef:
211               getparaloc:=LOC_REGISTER;
212             stringdef:
213               if is_shortstring(p) or is_longstring(p) then
214                 getparaloc:=LOC_REFERENCE
215               else
216                 getparaloc:=LOC_REGISTER;
217             procvardef:
218               getparaloc:=LOC_REGISTER;
219             filedef:
220               getparaloc:=LOC_REGISTER;
221             arraydef:
222               if not is_hfa(p,hfabasedef) then
223                 getparaloc:=LOC_REGISTER
224               else
225                 getparaloc:=LOC_MMREGISTER;
226             setdef:
227               getparaloc:=LOC_REGISTER;
228             variantdef:
229               getparaloc:=LOC_REGISTER;
230             { avoid problems with errornous definitions }
231             errordef:
232               getparaloc:=LOC_REGISTER;
233             else
234               internalerror(2002071001);
235          end;
236       end;
237 
238 
tcpuparamanager.push_addr_paramnull239     function tcpuparamanager.push_addr_param(varspez: tvarspez; def :tdef; calloption: tproccalloption): boolean;
240       var
241         hfabasedef: tdef;
242       begin
243         result:=false;
244         if varspez in [vs_var,vs_out,vs_constref] then
245           begin
246             result:=true;
247             exit;
248           end;
249         case def.typ of
250           objectdef:
251             result:=is_object(def);
252           recorddef:
253             { ABI: any composite > 16 bytes that not a hfa/hva
254               Special case: MWPascal, which passes all const parameters by
255                 reference for compatibility reasons
256             }
257             result:=
258               ((varspez=vs_const) and
259                (calloption=pocall_mwpascal)) or
260               (not is_hfa(def,hfabasedef) and
261                (def.size>16));
262           variantdef,
263           formaldef:
264             result:=true;
265           { arrays are composites and hence treated the same as records by the
266             ABI (watch out for C, where an array is a pointer)
267             Also: all other platforms pass const arrays by reference. Do the
268               same here, because there is too much hacky code out there that
269               relies on this ("array[0..0] of x" passed as const parameter and
270               then indexed beyond its bounds) }
271           arraydef:
272             result:=
273               ((calloption in cdecl_pocalls) and
274                not is_dynamic_array(def)) or
275               is_open_array(def) or
276               is_array_of_const(def) or
277               is_array_constructor(def) or
278               ((tarraydef(def).highrange>=tarraydef(def).lowrange) and
279                ((varspez=vs_const) or
280                 (not is_hfa(def,hfabasedef) and
281                  (def.size>16))));
282           setdef :
283             result:=def.size>16;
284           stringdef :
285             result:=tstringdef(def).stringtype in [st_shortstring,st_longstring];
286         end;
287       end;
288 
289 
tcpuparamanager.ret_in_paramnull290     function tcpuparamanager.ret_in_param(def: tdef; pd: tabstractprocdef): boolean;
291       begin
292         if handle_common_ret_in_param(def,pd,result) then
293           exit;
294         { ABI: if the parameter would be passed in registers, it is returned
295             in those registers; otherwise, it's returned by reference }
296         result:=push_addr_param(vs_value,def,pd.proccalloption);
297       end;
298 
299 
300     procedure tcpuparamanager.create_paraloc_info_intern(p : tabstractprocdef; side: tcallercallee; paras: tparalist; isvariadic: boolean);
301       var
302         hp: tparavarsym;
303         i: longint;
304       begin
305         for i:=0 to paras.count-1 do
306           begin
307             hp:=tparavarsym(paras[i]);
308             { hidden function result parameter is passed in X8 (doesn't have to
309               be valid on return) according to the ABI
310 
311               -- don't follow the ABI for managed types, because
312                a) they are passed in registers as parameters, so we should also
313                   return them in a register to be ABI-compliant (which we can't
314                   because the entire compiler is built around the idea that
315                   they are returned by reference, for ref-counting performance
316                   and Delphi-compatibility reasons)
317                b) there are hacks in the system unit that expect that you can
318                   call
319                     function f: com_interface;
320                   as
321                     procedure p(out o: obj);
322                   That can only work in case we do not use x8 to return them
323                   from the function, but the regular first parameter register.
324 
325               As the ABI says this behaviour is ok for C++ classes with a
326               non-trivial copy constructor or destructor, it seems reasonable
327               for us to do this for managed types as well.}
328             if (vo_is_funcret in hp.varoptions) and
329                not is_managed_type(hp.vardef) then
330               begin
331                 hp.paraloc[side].reset;
332                 hp.paraloc[side].size:=OS_ADDR;
333                 hp.paraloc[side].alignment:=voidpointertype.alignment;
334                 hp.paraloc[side].intsize:=voidpointertype.size;
335                 hp.paraloc[side].def:=cpointerdef.getreusable_no_free(hp.vardef);
336                 with hp.paraloc[side].add_location^ do
337                   begin
338                     size:=OS_ADDR;
339                     def:=hp.paraloc[side].def;
340                     loc:=LOC_REGISTER;
341                     register:=NR_X8;
342                   end
343               end
344             else
345               alloc_para(hp.paraloc[side],p,hp.varspez,side,hp.vardef,isvariadic,
346                 (vo_is_parentfp in hp.varoptions) and
347                 (po_delphi_nested_cc in p.procoptions));
348           end;
349       end;
350 
351 
tcpuparamanager.get_funcretlocnull352     function  tcpuparamanager.get_funcretloc(p : tabstractprocdef; side: tcallercallee; forcetempdef: tdef): tcgpara;
353       var
354         retcgsize: tcgsize;
355         otherside: tcallercallee;
356       begin
357          if set_common_funcretloc_info(p,forcetempdef,retcgsize,result) then
358            exit;
359 
360          { in this case, it must be returned in registers as if it were passed
361            as the first parameter }
362          init_para_alloc_values;
363          { if we're on the callee side, filling the result location is actually the "callerside"
364           as far passing it as a parameter value is concerned }
365          if side=callerside then
366            otherside:=calleeside
367          else
368            otherside:=callerside;
369          alloc_para(result,p,vs_value,otherside,result.def,false,false);
370          { sanity check (LOC_VOID for empty records) }
371          if not assigned(result.location) or
372             not(result.location^.loc in [LOC_REGISTER,LOC_MMREGISTER,LOC_VOID]) then
373            internalerror(2014113001);
374          {
375            According to ARM64 ABI: "If the size of the argument is less than 8 bytes then
376            the size of the argument is set to 8 bytes. The effect is as if the argument
377            was copied to the least significant bits of a 64-bit register and the remaining
378            bits filled with unspecified values."
379 
380            Therefore at caller side force the ordinal result to be always 64-bit, so it
381            will be stripped to the required size and uneeded bits are discarded.
382 
383            This is not required for iOS, where the result is zero/sign extended.
384          }
385          if (target_info.abi<>abi_aarch64_darwin) and
386             (side=callerside) and (result.location^.loc = LOC_REGISTER) and
387             (result.def.size<8) and is_ordinal(result.def) then
388            begin
389              result.location^.size:=OS_64;
390              result.location^.def:=u64inttype;
391            end;
392       end;
393 
394 
tcpuparamanager.param_use_paralocnull395     function tcpuparamanager.param_use_paraloc(const cgpara: tcgpara): boolean;
396       begin
397         { we always set up a stack frame -> we can always access the parameters
398           this way }
399         result:=
400           (cgpara.location^.loc=LOC_REFERENCE) and
401           not assigned(cgpara.location^.next);
402       end;
403 
404 
405     procedure tcpuparamanager.init_para_alloc_values;
406       begin
407         curintreg:=RS_FIRST_INT_PARAM_SUPREG;
408         curmmreg:=RS_FIRST_MM_PARAM_SUPREG;
409         curstackoffset:=0;
410       end;
411 
412 
413     procedure tcpuparamanager.alloc_para(out result: tcgpara; p: tabstractprocdef; varspez: tvarspez; side: tcallercallee; paradef: tdef; isvariadic, isdelphinestedcc: boolean);
414       var
415         hfabasedef, locdef: tdef;
416         paraloc: pcgparalocation;
417         paralen, stackslotlen: asizeint;
418         loc: tcgloc;
419         paracgsize, locsize: tcgsize;
420         firstparaloc: boolean;
421       begin
422         result.init;
423 
424         { currently only support C-style array of const,
425           there should be no location assigned to the vararg array itself }
426         if (p.proccalloption in cstylearrayofconst) and
427            is_array_of_const(paradef) then
428           begin
429             paraloc:=result.add_location;
430             { hack: the paraloc must be valid, but is not actually used }
431             paraloc^.loc:=LOC_REGISTER;
432             paraloc^.register:=NR_X0;
433             paraloc^.size:=OS_ADDR;
434             exit;
435           end;
436 
437         if push_addr_param(varspez,paradef,p.proccalloption) then
438           begin
439             paradef:=cpointerdef.getreusable_no_free(paradef);
440             loc:=LOC_REGISTER;
441             paracgsize:=OS_ADDR;
442             paralen:=tcgsize2size[OS_ADDR];
443           end
444         else
445           begin
446             if not is_special_array(paradef) then
447               paralen:=paradef.size
448             else
449               paralen:=tcgsize2size[def_cgsize(paradef)];
450             loc:=getparaloc(p.proccalloption,paradef);
451             if (paradef.typ in [objectdef,arraydef,recorddef]) and
452                not is_special_array(paradef) and
453                (varspez in [vs_value,vs_const]) then
454               paracgsize:=int_cgsize(paralen)
455             else
456               begin
457                 paracgsize:=def_cgsize(paradef);
458                 { for things like formaldef }
459                 if paracgsize=OS_NO then
460                   begin
461                     paracgsize:=OS_ADDR;
462                     paralen:=tcgsize2size[OS_ADDR];
463                     paradef:=voidpointertype;
464                   end;
465               end
466           end;
467 
468           { get hfa basedef if applicable }
469           if not is_hfa(paradef,hfabasedef) then
470             hfabasedef:=nil;
471 
472          result.size:=paracgsize;
473          result.alignment:=std_param_align;
474          result.intsize:=paralen;
475          result.def:=paradef;
476 
477          { empty record: skipped (explicitly defined by Apple ABI, undefined
478            by general ABI; libffi also skips them in all cases) }
479          if not is_special_array(paradef) and
480             (paradef.size=0) then
481            begin
482              paraloc:=result.add_location;
483              paraloc^.loc:=LOC_VOID;
484              paraloc^.def:=paradef;
485              paraloc^.size:=OS_NO;
486              exit;
487            end;
488 
489          { sufficient registers left? }
490          case loc of
491            LOC_REGISTER:
492              begin
493                { In case of po_delphi_nested_cc, the parent frame pointer
494                  is always passed on the stack. }
495                if isdelphinestedcc then
496                  loc:=LOC_REFERENCE
497                else if curintreg+((paralen-1) shr 3)>RS_LAST_INT_PARAM_SUPREG then
498                  begin
499                    { not enough integer registers left -> no more register
500                      parameters, copy all to stack
501                    }
502                    curintreg:=succ(RS_LAST_INT_PARAM_SUPREG);
503                    loc:=LOC_REFERENCE;
504                  end;
505              end;
506            LOC_MMREGISTER:
507              begin;
508                { every hfa element must be passed in a separate register }
509                if (assigned(hfabasedef) and
510                    (curmmreg+((paralen-1) div hfabasedef.size)>RS_LAST_MM_PARAM_SUPREG)) or
511                   (curmmreg+((paralen-1) shr 3)>RS_LAST_MM_PARAM_SUPREG) then
512                  begin
513                    { not enough mm registers left -> no more register
514                      parameters, copy all to stack
515                    }
516                    curmmreg:=succ(RS_LAST_MM_PARAM_SUPREG);
517                    loc:=LOC_REFERENCE;
518                  end;
519              end;
520          end;
521 
522          { allocate registers/stack locations }
523          firstparaloc:=true;
524          repeat
525            paraloc:=result.add_location;
526 
527            { set paraloc size/def }
528            if assigned(hfabasedef) then
529              begin
530                locsize:=def_cgsize(hfabasedef);
531                locdef:=hfabasedef;
532              end
533            { make sure we don't lose whether or not the type is signed }
534            else if (loc=LOC_REGISTER) and
535                    (paradef.typ<>orddef) then
536              begin
537                locsize:=int_cgsize(paralen);
538                locdef:=get_paraloc_def(paradef,paralen,firstparaloc);
539              end
540            else
541              begin
542                locsize:=paracgsize;
543                locdef:=paradef;
544              end;
545            if locsize in [OS_NO,OS_128,OS_S128] then
546              begin
547                if paralen>4 then
548                  begin
549                    paraloc^.size:=OS_INT;
550                    paraloc^.def:=u64inttype;
551                  end
552                else
553                  begin
554                    { for 3-byte records }
555                    paraloc^.size:=OS_32;
556                    paraloc^.def:=u32inttype;
557                  end;
558              end
559            else
560              begin
561                paraloc^.size:=locsize;
562                paraloc^.def:=locdef;
563              end;
564 
565            { paraloc loc }
566            paraloc^.loc:=loc;
567 
568            { assign register/stack address }
569            case loc of
570              LOC_REGISTER:
571                begin
572                  paraloc^.register:=newreg(R_INTREGISTER,curintreg,cgsize2subreg(R_INTREGISTER,paraloc^.size));
573                  inc(curintreg);
574                  dec(paralen,tcgsize2size[paraloc^.size]);
575 
576                  { "The general ABI specifies that it is the callee's
577                     responsibility to sign or zero-extend arguments having fewer
578                     than 32 bits, and that unused bits in a register are
579                     unspecified. In iOS, however, the caller must perform such
580                     extensions, up to 32 bits."
581                     Zero extend an argument at caller side for iOS and
582                     ignore the argument's unspecified high bits at callee side for
583                     all other platforms. }
584                  if (paradef.size<4) and is_ordinal(paradef) then
585                    begin
586                      if target_info.abi=abi_aarch64_darwin then
587                        begin
588                          if side=callerside then
589                            begin
590                              paraloc^.size:=OS_32;
591                              paraloc^.def:=u32inttype;
592                            end;
593                        end
594                      else
595                        begin
596                          if side=calleeside then
597                            begin
598                              paraloc^.size:=OS_32;
599                              paraloc^.def:=u32inttype;
600                            end;
601                        end;
602                    end;
603 
604                  { in case it's a composite, "The argument is passed as though
605                    it had been loaded into the registers from a double-word-
606                    aligned address with an appropriate sequence of LDR
607                    instructions loading consecutive registers from memory" ->
608                    in case of big endian, values in not completely filled
609                    registers must be shifted to the top bits }
610                  if (target_info.endian=endian_big) and
611                     not(paraloc^.size in [OS_64,OS_S64]) and
612                     (paradef.typ in [setdef,recorddef,arraydef,objectdef]) then
613                    paraloc^.shiftval:=-(8-tcgsize2size[paraloc^.size])*8;
614                end;
615              LOC_MMREGISTER:
616                begin
617                  paraloc^.register:=newreg(R_MMREGISTER,curmmreg,cgsize2subreg(R_MMREGISTER,paraloc^.size));
618                  inc(curmmreg);
619                  dec(paralen,tcgsize2size[paraloc^.size]);
620                end;
621              LOC_REFERENCE:
622                begin
623                   paraloc^.size:=paracgsize;
624                   paraloc^.loc:=LOC_REFERENCE;
625                   if assigned(hfabasedef) then
626                     paraloc^.def:=carraydef.getreusable_no_free(hfabasedef,paralen div hfabasedef.size)
627                   else
628                     paraloc^.def:=paradef;
629 
630                   { the current stack offset may not be properly aligned in
631                     case we're on Darwin and have allocated a non-variadic argument
632                     < 8 bytes previously }
633                   if target_info.abi=abi_aarch64_darwin then
634                     curstackoffset:=align(curstackoffset,paraloc^.def.alignment);
635 
636                   { on Darwin, non-variadic arguments take up their actual size
637                     on the stack; on other platforms, they take up a multiple of
638                     8 bytes }
639                   if (target_info.abi=abi_aarch64_darwin) and
640                      not isvariadic then
641                     stackslotlen:=paralen
642                   else
643                     stackslotlen:=align(paralen,8);
644 
645                   { from the ABI: if arguments occupy partial stack space, they
646                     have to occupy the lowest significant bits of a register
647                     containing that value which is then stored to memory ->
648                     in case of big endian, skip the alignment bytes (if any) }
649                   if target_info.endian=endian_little then
650                     paraloc^.reference.offset:=curstackoffset
651                   else
652                     paraloc^.reference.offset:=curstackoffset+stackslotlen-paralen;
653                   if side=callerside then
654                     paraloc^.reference.index:=NR_STACK_POINTER_REG
655                   else
656                     begin
657                       paraloc^.reference.index:=NR_FRAME_POINTER_REG;
658                       inc(paraloc^.reference.offset,16);
659                     end;
660                   inc(curstackoffset,stackslotlen);
661                   paralen:=0
662                end;
663              else
664                internalerror(2002071002);
665            end;
666          firstparaloc:=false;
667          { <=0 for sign/zero-extended locations }
668          until paralen<=0;
669       end;
670 
671 
tcpuparamanager.create_paraloc_infonull672     function tcpuparamanager.create_paraloc_info(p: tabstractprocdef; side: tcallercallee):longint;
673       begin
674         init_para_alloc_values;
675 
676         create_paraloc_info_intern(p,side,p.paras,false);
677         result:=curstackoffset;
678 
679         create_funcretloc_info(p,side);
680      end;
681 
682 
tcpuparamanager.create_varargs_paraloc_infonull683     function tcpuparamanager.create_varargs_paraloc_info(p: tabstractprocdef; varargspara: tvarargsparalist):longint;
684       begin
685         init_para_alloc_values;
686 
687         { non-variadic parameters }
688         create_paraloc_info_intern(p,callerside,p.paras,false);
689         if p.proccalloption in cstylearrayofconst then
690           begin
691             { on Darwin, we cannot use any registers for variadic parameters }
692             if target_info.abi=abi_aarch64_darwin then
693               begin
694                 curintreg:=succ(RS_LAST_INT_PARAM_SUPREG);
695                 curmmreg:=succ(RS_LAST_MM_PARAM_SUPREG);
696               end;
697             { continue loading the parameters  }
698             create_paraloc_info_intern(p,callerside,varargspara,true);
699             result:=curstackoffset;
700           end
701         else
702           internalerror(200410231);
703       end;
704 
705 begin
706    paramanager:=tcpuparamanager.create;
707 end.
708