cpupara.pas 27 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803
  1. {
  2. Copyright (c) 2002 by Florian Klaempfl
  3. PowerPC64 specific calling conventions
  4. This program is free software; you can redistribute it and/or modify
  5. it under the terms of the GNU General Public License as published by
  6. the Free Software Foundation; either version 2 of the License, or
  7. (at your option) any later version.
  8. This program is distributed in the hope that it will be useful,
  9. but WITHOUT ANY WARRANTY; without even the implied warranty of
  10. MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
  11. GNU General Public License for more details.
  12. You should have received a copy of the GNU General Public License
  13. along with this program; if not, write to the Free Software
  14. Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
  15. ****************************************************************************
  16. }
  17. unit cpupara;
  18. {$I fpcdefs.inc}
  19. interface
  20. uses
  21. globtype,
  22. aasmtai,aasmdata,
  23. cpubase,
  24. symconst, symtype, symdef, symsym,
  25. paramgr, parabase, cgbase, cgutils;
  26. type
  27. tcpuparamanager = class(tparamanager)
  28. function get_volatile_registers_int(calloption: tproccalloption):
  29. tcpuregisterset; override;
  30. function get_volatile_registers_fpu(calloption: tproccalloption):
  31. tcpuregisterset; override;
  32. function get_saved_registers_int(calloption: tproccalloption):
  33. tcpuregisterarray; override;
  34. function push_addr_param(varspez: tvarspez; def: tdef; calloption:
  35. tproccalloption): boolean; override;
  36. function ret_in_param(def: tdef; pd: tabstractprocdef): boolean; override;
  37. procedure getintparaloc(list: TAsmList; pd : tabstractprocdef; nr: longint; var cgpara: tcgpara); override;
  38. function create_paraloc_info(p: tabstractprocdef; side: tcallercallee): longint; override;
  39. function create_varargs_paraloc_info(p: tabstractprocdef; side: tcallercallee; varargspara: tvarargsparalist): longint; override;
  40. function get_funcretloc(p : tabstractprocdef; side: tcallercallee; forcetempdef: tdef): tcgpara;override;
  41. private
  42. procedure init_values(var curintreg, curfloatreg, curmmreg: tsuperregister;
  43. var cur_stack_offset: aword);
  44. function create_paraloc_info_intern(p: tabstractprocdef; side:
  45. tcallercallee; paras: tparalist;
  46. var curintreg, curfloatreg, curmmreg: tsuperregister; var
  47. cur_stack_offset: aword; isVararg : boolean): longint;
  48. function parseparaloc(p: tparavarsym; const s: string): boolean; override;
  49. procedure create_paraloc_for_def(var para: TCGPara; varspez: tvarspez; paradef: tdef; var nextfloatreg, nextintreg: tsuperregister; var stack_offset: aword; const isVararg, forceintmem: boolean; const side: tcallercallee; const p: tabstractprocdef);
  50. end;
  51. implementation
  52. uses
  53. verbose, systems,
  54. defutil,symtable,symcpu,
  55. procinfo, cpupi;
  56. function tcpuparamanager.get_volatile_registers_int(calloption:
  57. tproccalloption): tcpuregisterset;
  58. begin
  59. result := [RS_R0,RS_R3..RS_R12];
  60. if (target_info.system = system_powerpc64_darwin) then
  61. include(result,RS_R2);
  62. end;
  63. function tcpuparamanager.get_volatile_registers_fpu(calloption:
  64. tproccalloption): tcpuregisterset;
  65. begin
  66. result := [RS_F0..RS_F13];
  67. end;
  68. function tcpuparamanager.get_saved_registers_int(calloption: tproccalloption):
  69. tcpuregisterarray;
  70. const
  71. saved_regs: {$ifndef VER3_0}tcpuregisterarray{$else}array[0..17] of tsuperregister{$endif} = (
  72. RS_R14, RS_R15, RS_R16, RS_R17, RS_R18, RS_R19,
  73. RS_R20, RS_R21, RS_R22, RS_R23, RS_R24, RS_R25,
  74. RS_R26, RS_R27, RS_R28, RS_R29, RS_R30, RS_R31
  75. );
  76. begin
  77. result:=saved_regs;
  78. end;
  79. procedure tcpuparamanager.getintparaloc(list: TAsmList; pd : tabstractprocdef; nr: longint; var cgpara: tcgpara);
  80. var
  81. paraloc: pcgparalocation;
  82. psym: tparavarsym;
  83. pdef: tdef;
  84. begin
  85. psym:=tparavarsym(pd.paras[nr-1]);
  86. pdef:=psym.vardef;
  87. if push_addr_param(psym.varspez,pdef,pd.proccalloption) then
  88. pdef:=cpointerdef.getreusable_no_free(pdef);
  89. cgpara.reset;
  90. cgpara.size := def_cgsize(pdef);
  91. cgpara.intsize := tcgsize2size[cgpara.size];
  92. cgpara.alignment := get_para_align(pd.proccalloption);
  93. cgpara.def:=pdef;
  94. paraloc := cgpara.add_location;
  95. with paraloc^ do begin
  96. size := def_cgsize(pdef);
  97. def := pdef;
  98. if (nr <= 8) then begin
  99. if (nr = 0) then
  100. internalerror(200309271);
  101. loc := LOC_REGISTER;
  102. register := newreg(R_INTREGISTER, RS_R2 + nr, R_SUBWHOLE);
  103. end else begin
  104. loc := LOC_REFERENCE;
  105. paraloc^.reference.index := NR_STACK_POINTER_REG;
  106. reference.offset := sizeof(aint) * (nr - 8);
  107. end;
  108. end;
  109. end;
  110. function getparaloc(p: tdef): tcgloc;
  111. begin
  112. { Later, the LOC_REFERENCE is in most cases changed into LOC_REGISTER
  113. if push_addr_param for the def is true
  114. }
  115. case p.typ of
  116. orddef:
  117. result := LOC_REGISTER;
  118. floatdef:
  119. result := LOC_FPUREGISTER;
  120. enumdef:
  121. result := LOC_REGISTER;
  122. pointerdef:
  123. result := LOC_REGISTER;
  124. formaldef:
  125. result := LOC_REGISTER;
  126. classrefdef:
  127. result := LOC_REGISTER;
  128. procvardef,
  129. recorddef:
  130. result := LOC_REGISTER;
  131. objectdef:
  132. if is_object(p) then
  133. result := LOC_REFERENCE
  134. else
  135. result := LOC_REGISTER;
  136. stringdef:
  137. if is_shortstring(p) or is_longstring(p) then
  138. result := LOC_REFERENCE
  139. else
  140. result := LOC_REGISTER;
  141. filedef:
  142. result := LOC_REGISTER;
  143. arraydef:
  144. if is_dynamic_array(p) then
  145. getparaloc:=LOC_REGISTER
  146. else
  147. result := LOC_REFERENCE;
  148. setdef:
  149. if is_smallset(p) then
  150. result := LOC_REGISTER
  151. else
  152. result := LOC_REFERENCE;
  153. variantdef:
  154. result := LOC_REFERENCE;
  155. { avoid problems with errornous definitions }
  156. errordef:
  157. result := LOC_REGISTER;
  158. else
  159. internalerror(2002071001);
  160. end;
  161. end;
  162. function tcpuparamanager.push_addr_param(varspez: tvarspez; def: tdef;
  163. calloption: tproccalloption): boolean;
  164. begin
  165. result := false;
  166. { var,out,constref always require address }
  167. if varspez in [vs_var, vs_out, vs_constref] then
  168. begin
  169. result := true;
  170. exit;
  171. end;
  172. case def.typ of
  173. variantdef,
  174. formaldef:
  175. result := true;
  176. procvardef,
  177. recorddef:
  178. result :=
  179. (varspez = vs_const) and
  180. (
  181. (
  182. (not (calloption in cdecl_pocalls) and
  183. (def.size > 8))
  184. ) or
  185. (calloption = pocall_mwpascal)
  186. );
  187. arraydef:
  188. result := (tarraydef(def).highrange >= tarraydef(def).lowrange) or
  189. is_open_array(def) or
  190. is_array_of_const(def) or
  191. is_array_constructor(def);
  192. objectdef:
  193. result := is_object(def);
  194. setdef:
  195. result := not is_smallset(def);
  196. stringdef:
  197. result := tstringdef(def).stringtype in [st_shortstring, st_longstring];
  198. else
  199. ;
  200. end;
  201. end;
  202. function tcpuparamanager.ret_in_param(def: tdef; pd: tabstractprocdef): boolean;
  203. var
  204. tmpdef: tdef;
  205. begin
  206. if handle_common_ret_in_param(def,pd,result) then
  207. exit;
  208. { general rule: passed in registers -> returned in registers }
  209. result:=push_addr_param(vs_value,def,pd.proccalloption);
  210. case target_info.abi of
  211. { elfv2: non-homogeneous aggregate larger than 2 doublewords or a
  212. homogeneous aggregate with more than eight registers are returned by
  213. reference }
  214. abi_powerpc_elfv2:
  215. begin
  216. if not result then
  217. begin
  218. if (def.typ=recorddef) then
  219. begin
  220. if tcpurecorddef(def).has_single_type_elfv2(tmpdef) then
  221. begin
  222. if def.size>8*tmpdef.size then
  223. result:=true
  224. end
  225. else if def.size>2*sizeof(aint) then
  226. result:=true;
  227. end
  228. else if (def.typ=arraydef) then
  229. begin
  230. if tcpuarraydef(def).has_single_type_elfv2(tmpdef) then
  231. begin
  232. if def.size>8*tmpdef.size then
  233. result:=true
  234. end
  235. else if def.size>2*sizeof(aint) then
  236. result:=true;
  237. end;
  238. end;
  239. end;
  240. { sysv/aix: any non-scalar/non-floating point is returned by reference }
  241. abi_powerpc_sysv,
  242. abi_powerpc_aix:
  243. begin
  244. case def.typ of
  245. procvardef:
  246. result:=def.size>8;
  247. recorddef:
  248. result:=true;
  249. else
  250. ;
  251. end;
  252. end;
  253. { Darwin: if completely passed in registers -> returned by registers;
  254. i.e., if part is passed via memory because there are not enough
  255. registers, return via memory }
  256. abi_powerpc_darwin:
  257. begin
  258. case def.typ of
  259. recorddef:
  260. begin
  261. { todo: fix once the Darwin/ppc64 abi is fully implemented, as it
  262. requires individual fields to be passed in individual registers,
  263. so a record with 9 bytes may need to be passed via memory }
  264. if def.size>8*sizeof(aint) then
  265. result:=true;
  266. end;
  267. else
  268. ;
  269. end;
  270. end;
  271. else
  272. internalerror(2019051030);
  273. end;
  274. end;
  275. procedure tcpuparamanager.init_values(var curintreg, curfloatreg, curmmreg:
  276. tsuperregister; var cur_stack_offset: aword);
  277. begin
  278. { register parameter save area begins at 48(r2) }
  279. cur_stack_offset := 48;
  280. curintreg := RS_R3;
  281. curfloatreg := RS_F1;
  282. curmmreg := RS_M2;
  283. end;
  284. function tcpuparamanager.get_funcretloc(p : tabstractprocdef; side:
  285. tcallercallee; forcetempdef: tdef): tcgpara;
  286. var
  287. paraloc: pcgparalocation;
  288. retcgsize: tcgsize;
  289. nextfloatreg, nextintreg, nextmmreg: tsuperregister;
  290. stack_offset: aword;
  291. begin
  292. if set_common_funcretloc_info(p,forcetempdef,retcgsize,result) then
  293. exit;
  294. { on Darwin and with ELFv2, results are returned the same way as they are
  295. passed }
  296. if target_info.abi in [abi_powerpc_elfv2,abi_powerpc_darwin] then
  297. begin
  298. init_values(nextintreg,nextfloatreg,nextmmreg,stack_offset);
  299. create_paraloc_for_def(result,vs_value,result.def,nextfloatreg,nextintreg,stack_offset,false,false,side,p);
  300. end
  301. else
  302. begin
  303. { for AIX and ELFv1, the situation is simpler: always just one register }
  304. paraloc:=result.add_location;
  305. { Return in FPU register? }
  306. if result.def.typ=floatdef then
  307. begin
  308. paraloc^.loc:=LOC_FPUREGISTER;
  309. paraloc^.register:=NR_FPU_RESULT_REG;
  310. paraloc^.size:=retcgsize;
  311. paraloc^.def:=result.def;
  312. end
  313. else
  314. { Return in register }
  315. begin
  316. paraloc^.loc:=LOC_REGISTER;
  317. if side=callerside then
  318. paraloc^.register:=newreg(R_INTREGISTER,RS_FUNCTION_RESULT_REG,cgsize2subreg(R_INTREGISTER,retcgsize))
  319. else
  320. paraloc^.register:=newreg(R_INTREGISTER,RS_FUNCTION_RETURN_REG,cgsize2subreg(R_INTREGISTER,retcgsize));
  321. paraloc^.size:=retcgsize;
  322. paraloc^.def:=result.def;
  323. end;
  324. end;
  325. end;
  326. function tcpuparamanager.create_paraloc_info(p: tabstractprocdef; side:
  327. tcallercallee): longint;
  328. var
  329. cur_stack_offset: aword;
  330. curintreg, curfloatreg, curmmreg : tsuperregister;
  331. begin
  332. init_values(curintreg, curfloatreg, curmmreg, cur_stack_offset);
  333. result := create_paraloc_info_intern(p, side, p.paras, curintreg, curfloatreg,
  334. curmmreg, cur_stack_offset, false);
  335. create_funcretloc_info(p, side);
  336. end;
  337. function tcpuparamanager.create_paraloc_info_intern(p: tabstractprocdef; side:
  338. tcallercallee; paras: tparalist;
  339. var curintreg, curfloatreg, curmmreg: tsuperregister; var cur_stack_offset:
  340. aword; isVararg : boolean): longint;
  341. var
  342. nextintreg, nextfloatreg, nextmmreg : tsuperregister;
  343. i: integer;
  344. hp: tparavarsym;
  345. paraloc: pcgparalocation;
  346. delphi_nestedfp: boolean;
  347. begin
  348. {$IFDEF extdebug}
  349. if po_explicitparaloc in p.procoptions then
  350. internalerror(200411141);
  351. {$ENDIF extdebug}
  352. result := 0;
  353. nextintreg := curintreg;
  354. nextfloatreg := curfloatreg;
  355. nextmmreg := curmmreg;
  356. for i := 0 to paras.count - 1 do begin
  357. hp := tparavarsym(paras[i]);
  358. { Syscall for Morphos can have already a paraloc set; not supported on ppc64 }
  359. if (vo_has_explicit_paraloc in hp.varoptions) then begin
  360. internalerror(200412153);
  361. end;
  362. { currently only support C-style array of const }
  363. if (p.proccalloption in cstylearrayofconst) and
  364. is_array_of_const(hp.vardef) then begin
  365. paraloc := hp.paraloc[side].add_location;
  366. { hack: the paraloc must be valid, but is not actually used }
  367. paraloc^.loc := LOC_REGISTER;
  368. paraloc^.register := NR_R0;
  369. paraloc^.size := OS_ADDR;
  370. paraloc^.def := voidpointertype;
  371. break;
  372. end;
  373. delphi_nestedfp:=(vo_is_parentfp in hp.varoptions) and (po_delphi_nested_cc in p.procoptions);
  374. create_paraloc_for_def(hp.paraloc[side], hp.varspez, hp.vardef,
  375. nextfloatreg, nextintreg, cur_stack_offset, isVararg, delphi_nestedfp, side, p);
  376. end;
  377. curintreg := nextintreg;
  378. curfloatreg := nextfloatreg;
  379. curmmreg := nextmmreg;
  380. result := cur_stack_offset;
  381. end;
  382. procedure tcpuparamanager.create_paraloc_for_def(var para: TCGPara; varspez: tvarspez; paradef: tdef; var nextfloatreg, nextintreg: tsuperregister; var stack_offset: aword; const isVararg, forceintmem: boolean; const side: tcallercallee; const p: tabstractprocdef);
  383. var
  384. paracgsize: tcgsize;
  385. loc: tcgloc;
  386. paraloc: pcgparalocation;
  387. { def to use for all paralocs if <> nil }
  388. alllocdef,
  389. { def to use for the current paraloc }
  390. locdef,
  391. tmpdef: tdef;
  392. paralen: aint;
  393. parashift: byte;
  394. tailpadding,
  395. firstparaloc,
  396. paraaligned: boolean;
  397. begin
  398. alllocdef:=nil;
  399. locdef:=nil;
  400. parashift := 0;
  401. para.reset;
  402. { should the tail be shifted into the most significant bits? }
  403. tailpadding:=false;
  404. { have we ensured that the next parameter location will be aligned to the
  405. next 8 byte boundary? }
  406. paraaligned:=false;
  407. if push_addr_param(varspez, paradef, p.proccalloption) then begin
  408. paradef := cpointerdef.getreusable_no_free(paradef);
  409. loc := LOC_REGISTER;
  410. paracgsize := OS_ADDR;
  411. paralen := tcgsize2size[OS_ADDR];
  412. end else begin
  413. if not is_special_array(paradef) then
  414. paralen := paradef.size
  415. else
  416. paralen := tcgsize2size[def_cgsize(paradef)];
  417. { default rules:
  418. * integer parameters sign/zero-extended to 64 bit
  419. * floating point register used -> skip equivalent GP register
  420. * floating point parameters passed as is (32/64 bit)
  421. * floating point parameters to variable arguments -> in int registers
  422. * aggregates passed in consecutive integer registers
  423. * all *aggregate* data in integer registers exactly mirrors the data
  424. in memory -> on big endian it's left aligned (passed in most
  425. significant part of the 64 bit word if it's < 64 bit), on little
  426. endian it's right aligned (least significant part of the 64 bit
  427. word)
  428. special rules:
  429. implemented
  430. |
  431. | * AIX/ELFv1/SysV ppc64 ABI (big endian only):
  432. x a) single precision floats are stored in the second word of a 64 bit
  433. location when passed on the stack
  434. x b) aggregate with 1 floating point element passed like a floating
  435. point parameter of the same size
  436. x c) aggregates smaller than 64 bit are aligned in least significant bits
  437. of a single 64bit location (incl. register) (AIX exception: it puts
  438. them in the most significant bits)
  439. * ELFv2 ppc64 ABI:
  440. x a) so-called "homogeneous" aggregates, i.e. struct, arrays, or unions
  441. that (recursively) contain only elements of the same floating-
  442. point or vector type, are passed as if those elements were passed as
  443. separate arguments. This is done for up to 8 such elements.
  444. x b) other than a), it's the same as the AIX ppc64 ABI
  445. * Darwin ppc64 ABI:
  446. - as in the general case, aggregates in registers mirror their place in
  447. memory, so if e.g. a struct starts with a 32 bit integer, it's
  448. placed in the upper 32 bits of a the corresponding register. A plain
  449. 32 bit integer para is however passed in the lower 32 bits, since it
  450. is promoted to a 64 bit int first (see below)
  451. x a) aggregates with sizes 1, 2 and 4 bytes are padded with 0s on the left
  452. (-> aligned in least significant bits of 64 bit word on big endian) to
  453. a multiple of *4 bytes* (when passed by memory, don't occupy 8 bytes)
  454. x b) other aggregates are padded with 0s on the right (-> aligned in most
  455. signifcant bits of 64 bit word of integer register) to a multiple of
  456. *4 bytes*
  457. x c) all floating pointer parameters (not in aggregates) are promoted to
  458. double (doesn't seem to be correct: 8 bytes are reserved in the
  459. stack frame, but the compiler still stores a single in it (in the
  460. lower 4 bytes -- like with SysV a) )
  461. x d) all integer parameters (not in aggregates) are promoted to 64 bit
  462. (x) e) aggregates (incl. arrays) of exactly 16 bytes passed in two integer
  463. registers
  464. f) floats in *structures without unions* are processed per rule c)
  465. (similar for vector fields)
  466. g) other fields in *structures without unions* are processed
  467. recursively according to e) / f) if they are aggragates, and h)
  468. otherwise (i.e, without promotion!)
  469. (x) h) everything else (structures with unions and size<>16, arrays with
  470. size<>16, ...) is passed "normally" in integer registers
  471. }
  472. { ELFv2 a) }
  473. if (target_info.abi=abi_powerpc_elfv2) and
  474. (((paradef.typ=recorddef) and
  475. tcpurecorddef(paradef).has_single_type_elfv2(tmpdef)) or
  476. ((paradef.typ=arraydef) and
  477. tcpuarraydef(paradef).has_single_type_elfv2(tmpdef))) and
  478. (tmpdef.typ=floatdef { or vectordef }) and
  479. (paradef.size<=(8*tmpdef.size)) then
  480. begin
  481. alllocdef:=tmpdef;
  482. loc:=getparaloc(alllocdef);
  483. paracgsize:=def_cgsize(paradef);
  484. end
  485. { AIX/ELFv1 b) }
  486. else if (target_info.abi in [abi_powerpc_aix,abi_powerpc_sysv]) and
  487. (paradef.typ=recorddef) and
  488. tabstractrecordsymtable(tabstractrecorddef(paradef).symtable).has_single_field(tmpdef) and
  489. (tmpdef.typ=floatdef) then
  490. begin
  491. paradef:=tmpdef;
  492. loc:=getparaloc(paradef);
  493. paracgsize:=def_cgsize(paradef)
  494. end
  495. else if (((paradef.typ=arraydef) and not
  496. is_special_array(paradef)) or
  497. (paradef.typ=recorddef)) then
  498. begin
  499. { should handle Darwin f/g/h) now, but can't model that yet }
  500. { general rule: aggregate data is aligned in the most significant bits
  501. except for ELFv1 c) and Darwin a) }
  502. if (target_info.endian=endian_big) and
  503. ((target_info.abi in [abi_powerpc_aix,abi_powerpc_elfv2]) or
  504. ((target_info.abi=abi_powerpc_sysv) and
  505. (paralen>8)) or
  506. ((target_info.abi=abi_powerpc_darwin) and
  507. not(paralen in [1,2,4]))) then
  508. tailpadding:=true
  509. { if we don't add tailpadding on the caller side, the callee will have
  510. to shift the value in the register before it can store it to memory }
  511. else if (target_info.endian=endian_big) and
  512. (paralen in [3,5,6,7]) then
  513. parashift:=(8-paralen)*8;
  514. { general fallback rule: pass aggregate types in integer registers
  515. without special adjustments (incl. Darwin h) }
  516. loc:=LOC_REGISTER;
  517. paracgsize:=int_cgsize(paralen);
  518. end
  519. else
  520. begin
  521. loc:=getparaloc(paradef);
  522. paracgsize:=def_cgsize(paradef);
  523. { for things like formaldef }
  524. if (paracgsize=OS_NO) then
  525. begin
  526. paracgsize:=OS_ADDR;
  527. paralen:=tcgsize2size[OS_ADDR];
  528. end;
  529. end
  530. end;
  531. { patch FPU values into integer registers if we are processing varargs }
  532. if (isVararg) and (paradef.typ = floatdef) then begin
  533. loc := LOC_REGISTER;
  534. if paracgsize = OS_F64 then
  535. paracgsize := OS_64
  536. else
  537. paracgsize := OS_32;
  538. end;
  539. { AIX/SysV a), Darwin c) -> skip 4 bytes in the stack frame }
  540. if (target_info.endian=endian_big) and
  541. (paradef.typ=floatdef) and
  542. (tfloatdef(paradef).floattype=s32real) and
  543. (nextfloatreg>RS_F13) then
  544. begin
  545. inc(stack_offset,4);
  546. paraaligned:=true;
  547. end;
  548. { Darwin d) }
  549. if (target_info.abi=abi_powerpc_darwin) and
  550. (paradef.typ in [orddef,enumdef]) and
  551. (paralen<8) and
  552. { we don't have to sign/zero extend the lower 8/16/32 bit on the callee
  553. side since it's done on the caller side; however, if the value is
  554. passed via memory, we do have to modify the stack offset since this
  555. is big endian and otherwise we'll load/store the wrong bytes) }
  556. ((side=callerside) or
  557. forceintmem or
  558. (nextintreg>RS_R10)) then
  559. begin
  560. if side=callerside then
  561. begin
  562. paralen:=8;
  563. paradef:=s64inttype;
  564. paracgsize:=OS_S64;
  565. end
  566. else
  567. begin
  568. inc(stack_offset,8-paralen);
  569. paraaligned:=true;
  570. end;
  571. end;
  572. para.alignment := std_param_align;
  573. para.size := paracgsize;
  574. para.intsize := paralen;
  575. para.def := paradef;
  576. if (paralen = 0) then
  577. if (paradef.typ = recorddef) then begin
  578. paraloc := para.add_location;
  579. paraloc^.loc := LOC_VOID;
  580. end else
  581. internalerror(2005011310);
  582. if not assigned(alllocdef) then
  583. locdef:=paradef
  584. else
  585. begin
  586. locdef:=alllocdef;
  587. paracgsize:=def_cgsize(locdef);
  588. end;
  589. firstparaloc:=true;
  590. { can become < 0 for e.g. 3-byte records }
  591. while (paralen > 0) do begin
  592. paraloc := para.add_location;
  593. { In case of po_delphi_nested_cc, the parent frame pointer
  594. is always passed on the stack. }
  595. if (loc = LOC_REGISTER) and
  596. (nextintreg <= RS_R10) and
  597. not forceintmem then begin
  598. paraloc^.loc := loc;
  599. paraloc^.shiftval := parashift;
  600. { make sure we don't lose whether or not the type is signed }
  601. if (paracgsize <> OS_NO) and
  602. (paradef.typ <> orddef) and
  603. not assigned(alllocdef) then
  604. begin
  605. paracgsize := int_cgsize(paralen);
  606. locdef:=get_paraloc_def(paradef, paralen, firstparaloc);
  607. end;
  608. { Partial aggregate data may have to be left-aligned. If so, add tail
  609. padding }
  610. if tailpadding and
  611. (paralen < sizeof(aint)) then
  612. begin
  613. paraloc^.shiftval := (sizeof(aint)-paralen)*(-8);
  614. paraloc^.size := OS_INT;
  615. paraloc^.def := u64inttype;
  616. end
  617. else if (paracgsize in [OS_NO, OS_128, OS_S128]) then
  618. begin
  619. if (paralen>4) or
  620. (parashift<>0) then
  621. begin
  622. paraloc^.size := OS_INT;
  623. paraloc^.def := osuinttype;
  624. end
  625. else
  626. begin
  627. { for 3-byte records aligned in the lower bits of register }
  628. paraloc^.size := OS_32;
  629. paraloc^.def := u32inttype;
  630. end;
  631. end
  632. else
  633. begin
  634. paraloc^.size := paracgsize;
  635. paraloc^.def := locdef;
  636. end;
  637. paraloc^.register := newreg(R_INTREGISTER, nextintreg, R_SUBNONE);
  638. inc(nextintreg);
  639. dec(paralen, tcgsize2size[paraloc^.size]);
  640. inc(stack_offset, sizeof(pint));
  641. end else if (loc = LOC_FPUREGISTER) and
  642. (nextfloatreg <= RS_F13) then begin
  643. paraloc^.loc := loc;
  644. paraloc^.size := paracgsize;
  645. paraloc^.def := locdef;
  646. paraloc^.register := newreg(R_FPUREGISTER, nextfloatreg, R_SUBWHOLE);
  647. { the PPC64 ABI says that the GPR index is increased for every parameter, no matter
  648. which type it is stored in }
  649. inc(nextintreg);
  650. inc(nextfloatreg);
  651. dec(paralen, tcgsize2size[paraloc^.size]);
  652. inc(stack_offset, tcgsize2size[OS_FLOAT]);
  653. end else if (loc = LOC_MMREGISTER) then begin
  654. { Altivec not supported }
  655. internalerror(200510192);
  656. end else begin
  657. { either LOC_REFERENCE, or one of the above which must be passed on the
  658. stack because of insufficient registers }
  659. paraloc^.loc := LOC_REFERENCE;
  660. case loc of
  661. LOC_FPUREGISTER:
  662. begin
  663. paraloc^.size:=int_float_cgsize(paralen);
  664. case paraloc^.size of
  665. OS_F32: paraloc^.def:=s32floattype;
  666. OS_F64: paraloc^.def:=s64floattype;
  667. else
  668. internalerror(2013060122);
  669. end;
  670. end;
  671. LOC_REGISTER,
  672. LOC_REFERENCE:
  673. begin
  674. paraloc^.size:=int_cgsize(paralen);
  675. paraloc^.def:=get_paraloc_def(paradef, paralen, firstparaloc);
  676. end;
  677. else
  678. internalerror(2006011101);
  679. end;
  680. if (side = callerside) then
  681. paraloc^.reference.index := NR_STACK_POINTER_REG
  682. else begin
  683. { during procedure entry, NR_OLD_STACK_POINTER_REG contains the old stack pointer }
  684. paraloc^.reference.index := NR_OLD_STACK_POINTER_REG;
  685. { create_paraloc_info_intern might be also called when being outside of
  686. code generation so current_procinfo might be not set }
  687. if assigned(current_procinfo) then
  688. tcpuprocinfo(current_procinfo).needs_frame_pointer := true;
  689. end;
  690. paraloc^.reference.offset := stack_offset;
  691. { align temp contents to next register size }
  692. if not paraaligned then
  693. inc(stack_offset, align(paralen, 8))
  694. else
  695. inc(stack_offset, paralen);
  696. paralen := 0;
  697. end;
  698. firstparaloc:=false;
  699. end;
  700. end;
  701. function tcpuparamanager.create_varargs_paraloc_info(p: tabstractprocdef; side: tcallercallee;
  702. varargspara: tvarargsparalist): longint;
  703. var
  704. cur_stack_offset: aword;
  705. parasize, l: longint;
  706. curintreg, firstfloatreg, curfloatreg, curmmreg: tsuperregister;
  707. i: integer;
  708. hp: tparavarsym;
  709. paraloc: pcgparalocation;
  710. begin
  711. init_values(curintreg, curfloatreg, curmmreg, cur_stack_offset);
  712. firstfloatreg := curfloatreg;
  713. result := create_paraloc_info_intern(p, side, p.paras, curintreg,
  714. curfloatreg, curmmreg, cur_stack_offset, false);
  715. if (p.proccalloption in cstylearrayofconst) then
  716. begin
  717. { just continue loading the parameters in the registers }
  718. if assigned(varargspara) then
  719. begin
  720. if side=callerside then
  721. result := create_paraloc_info_intern(p, side, varargspara, curintreg,
  722. curfloatreg, curmmreg, cur_stack_offset, true)
  723. else
  724. internalerror(2019021920);
  725. end;
  726. { varargs routines have to reserve at least 64 bytes for the PPC64 ABI }
  727. if (result < 64) then
  728. result := 64;
  729. end
  730. else
  731. internalerror(2019021911);
  732. if curfloatreg <> firstfloatreg then
  733. include(varargspara.varargsinfo, va_uses_float_reg);
  734. create_funcretloc_info(p, side);
  735. end;
  736. function tcpuparamanager.parseparaloc(p: tparavarsym; const s: string): boolean;
  737. begin
  738. { not supported/required for PowerPC64-linux target }
  739. internalerror(200404182);
  740. result := true;
  741. end;
  742. begin
  743. paramanager := tcpuparamanager.create;
  744. end.