cpupara.pas 27 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807
  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. case target_info.abi of
  279. abi_powerpc_elfv2:
  280. cur_stack_offset := 32;
  281. else
  282. cur_stack_offset := 48;
  283. end;
  284. curintreg := RS_R3;
  285. curfloatreg := RS_F1;
  286. curmmreg := RS_M2;
  287. end;
  288. function tcpuparamanager.get_funcretloc(p : tabstractprocdef; side:
  289. tcallercallee; forcetempdef: tdef): tcgpara;
  290. var
  291. paraloc: pcgparalocation;
  292. retcgsize: tcgsize;
  293. nextfloatreg, nextintreg, nextmmreg: tsuperregister;
  294. stack_offset: aword;
  295. begin
  296. if set_common_funcretloc_info(p,forcetempdef,retcgsize,result) then
  297. exit;
  298. { on Darwin and with ELFv2, results are returned the same way as they are
  299. passed }
  300. if target_info.abi in [abi_powerpc_elfv2,abi_powerpc_darwin] then
  301. begin
  302. init_values(nextintreg,nextfloatreg,nextmmreg,stack_offset);
  303. create_paraloc_for_def(result,vs_value,result.def,nextfloatreg,nextintreg,stack_offset,false,false,side,p);
  304. end
  305. else
  306. begin
  307. { for AIX and ELFv1, the situation is simpler: always just one register }
  308. paraloc:=result.add_location;
  309. { Return in FPU register? }
  310. if result.def.typ=floatdef then
  311. begin
  312. paraloc^.loc:=LOC_FPUREGISTER;
  313. paraloc^.register:=NR_FPU_RESULT_REG;
  314. paraloc^.size:=retcgsize;
  315. paraloc^.def:=result.def;
  316. end
  317. else
  318. { Return in register }
  319. begin
  320. paraloc^.loc:=LOC_REGISTER;
  321. if side=callerside then
  322. paraloc^.register:=newreg(R_INTREGISTER,RS_FUNCTION_RESULT_REG,cgsize2subreg(R_INTREGISTER,retcgsize))
  323. else
  324. paraloc^.register:=newreg(R_INTREGISTER,RS_FUNCTION_RETURN_REG,cgsize2subreg(R_INTREGISTER,retcgsize));
  325. paraloc^.size:=retcgsize;
  326. paraloc^.def:=result.def;
  327. end;
  328. end;
  329. end;
  330. function tcpuparamanager.create_paraloc_info(p: tabstractprocdef; side:
  331. tcallercallee): longint;
  332. var
  333. cur_stack_offset: aword;
  334. curintreg, curfloatreg, curmmreg : tsuperregister;
  335. begin
  336. init_values(curintreg, curfloatreg, curmmreg, cur_stack_offset);
  337. result := create_paraloc_info_intern(p, side, p.paras, curintreg, curfloatreg,
  338. curmmreg, cur_stack_offset, false);
  339. create_funcretloc_info(p, side);
  340. end;
  341. function tcpuparamanager.create_paraloc_info_intern(p: tabstractprocdef; side:
  342. tcallercallee; paras: tparalist;
  343. var curintreg, curfloatreg, curmmreg: tsuperregister; var cur_stack_offset:
  344. aword; isVararg : boolean): longint;
  345. var
  346. nextintreg, nextfloatreg, nextmmreg : tsuperregister;
  347. i: integer;
  348. hp: tparavarsym;
  349. paraloc: pcgparalocation;
  350. delphi_nestedfp: boolean;
  351. begin
  352. {$IFDEF extdebug}
  353. if po_explicitparaloc in p.procoptions then
  354. internalerror(200411141);
  355. {$ENDIF extdebug}
  356. result := 0;
  357. nextintreg := curintreg;
  358. nextfloatreg := curfloatreg;
  359. nextmmreg := curmmreg;
  360. for i := 0 to paras.count - 1 do begin
  361. hp := tparavarsym(paras[i]);
  362. { Syscall for Morphos can have already a paraloc set; not supported on ppc64 }
  363. if (vo_has_explicit_paraloc in hp.varoptions) then begin
  364. internalerror(200412153);
  365. end;
  366. { currently only support C-style array of const }
  367. if (p.proccalloption in cstylearrayofconst) and
  368. is_array_of_const(hp.vardef) then begin
  369. paraloc := hp.paraloc[side].add_location;
  370. { hack: the paraloc must be valid, but is not actually used }
  371. paraloc^.loc := LOC_REGISTER;
  372. paraloc^.register := NR_R0;
  373. paraloc^.size := OS_ADDR;
  374. paraloc^.def := voidpointertype;
  375. break;
  376. end;
  377. delphi_nestedfp:=(vo_is_parentfp in hp.varoptions) and (po_delphi_nested_cc in p.procoptions);
  378. create_paraloc_for_def(hp.paraloc[side], hp.varspez, hp.vardef,
  379. nextfloatreg, nextintreg, cur_stack_offset, isVararg, delphi_nestedfp, side, p);
  380. end;
  381. curintreg := nextintreg;
  382. curfloatreg := nextfloatreg;
  383. curmmreg := nextmmreg;
  384. result := cur_stack_offset;
  385. end;
  386. 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);
  387. var
  388. paracgsize: tcgsize;
  389. loc: tcgloc;
  390. paraloc: pcgparalocation;
  391. { def to use for all paralocs if <> nil }
  392. alllocdef,
  393. { def to use for the current paraloc }
  394. locdef,
  395. tmpdef: tdef;
  396. paralen: aint;
  397. parashift: byte;
  398. tailpadding,
  399. firstparaloc,
  400. paraaligned: boolean;
  401. begin
  402. alllocdef:=nil;
  403. locdef:=nil;
  404. parashift := 0;
  405. para.reset;
  406. { should the tail be shifted into the most significant bits? }
  407. tailpadding:=false;
  408. { have we ensured that the next parameter location will be aligned to the
  409. next 8 byte boundary? }
  410. paraaligned:=false;
  411. if push_addr_param(varspez, paradef, p.proccalloption) then begin
  412. paradef := cpointerdef.getreusable_no_free(paradef);
  413. loc := LOC_REGISTER;
  414. paracgsize := OS_ADDR;
  415. paralen := tcgsize2size[OS_ADDR];
  416. end else begin
  417. if not is_special_array(paradef) then
  418. paralen := paradef.size
  419. else
  420. paralen := tcgsize2size[def_cgsize(paradef)];
  421. { default rules:
  422. * integer parameters sign/zero-extended to 64 bit
  423. * floating point register used -> skip equivalent GP register
  424. * floating point parameters passed as is (32/64 bit)
  425. * floating point parameters to variable arguments -> in int registers
  426. * aggregates passed in consecutive integer registers
  427. * all *aggregate* data in integer registers exactly mirrors the data
  428. in memory -> on big endian it's left aligned (passed in most
  429. significant part of the 64 bit word if it's < 64 bit), on little
  430. endian it's right aligned (least significant part of the 64 bit
  431. word)
  432. special rules:
  433. implemented
  434. |
  435. | * AIX/ELFv1/SysV ppc64 ABI (big endian only):
  436. x a) single precision floats are stored in the second word of a 64 bit
  437. location when passed on the stack
  438. x b) aggregate with 1 floating point element passed like a floating
  439. point parameter of the same size
  440. x c) aggregates smaller than 64 bit are aligned in least significant bits
  441. of a single 64bit location (incl. register) (AIX exception: it puts
  442. them in the most significant bits)
  443. * ELFv2 ppc64 ABI:
  444. x a) so-called "homogeneous" aggregates, i.e. struct, arrays, or unions
  445. that (recursively) contain only elements of the same floating-
  446. point or vector type, are passed as if those elements were passed as
  447. separate arguments. This is done for up to 8 such elements.
  448. x b) other than a), it's the same as the AIX ppc64 ABI
  449. * Darwin ppc64 ABI:
  450. - as in the general case, aggregates in registers mirror their place in
  451. memory, so if e.g. a struct starts with a 32 bit integer, it's
  452. placed in the upper 32 bits of a the corresponding register. A plain
  453. 32 bit integer para is however passed in the lower 32 bits, since it
  454. is promoted to a 64 bit int first (see below)
  455. x a) aggregates with sizes 1, 2 and 4 bytes are padded with 0s on the left
  456. (-> aligned in least significant bits of 64 bit word on big endian) to
  457. a multiple of *4 bytes* (when passed by memory, don't occupy 8 bytes)
  458. x b) other aggregates are padded with 0s on the right (-> aligned in most
  459. signifcant bits of 64 bit word of integer register) to a multiple of
  460. *4 bytes*
  461. x c) all floating pointer parameters (not in aggregates) are promoted to
  462. double (doesn't seem to be correct: 8 bytes are reserved in the
  463. stack frame, but the compiler still stores a single in it (in the
  464. lower 4 bytes -- like with SysV a) )
  465. x d) all integer parameters (not in aggregates) are promoted to 64 bit
  466. (x) e) aggregates (incl. arrays) of exactly 16 bytes passed in two integer
  467. registers
  468. f) floats in *structures without unions* are processed per rule c)
  469. (similar for vector fields)
  470. g) other fields in *structures without unions* are processed
  471. recursively according to e) / f) if they are aggragates, and h)
  472. otherwise (i.e, without promotion!)
  473. (x) h) everything else (structures with unions and size<>16, arrays with
  474. size<>16, ...) is passed "normally" in integer registers
  475. }
  476. { ELFv2 a) }
  477. if (target_info.abi=abi_powerpc_elfv2) and
  478. (((paradef.typ=recorddef) and
  479. tcpurecorddef(paradef).has_single_type_elfv2(tmpdef)) or
  480. ((paradef.typ=arraydef) and
  481. tcpuarraydef(paradef).has_single_type_elfv2(tmpdef))) and
  482. (tmpdef.typ=floatdef { or vectordef }) and
  483. (paradef.size<=(8*tmpdef.size)) then
  484. begin
  485. alllocdef:=tmpdef;
  486. loc:=getparaloc(alllocdef);
  487. paracgsize:=def_cgsize(paradef);
  488. end
  489. { AIX/ELFv1 b) }
  490. else if (target_info.abi in [abi_powerpc_aix,abi_powerpc_sysv]) and
  491. (paradef.typ=recorddef) and
  492. tabstractrecordsymtable(tabstractrecorddef(paradef).symtable).has_single_field(tmpdef) and
  493. (tmpdef.typ=floatdef) then
  494. begin
  495. paradef:=tmpdef;
  496. loc:=getparaloc(paradef);
  497. paracgsize:=def_cgsize(paradef)
  498. end
  499. else if (((paradef.typ=arraydef) and not
  500. is_special_array(paradef)) or
  501. (paradef.typ=recorddef)) then
  502. begin
  503. { should handle Darwin f/g/h) now, but can't model that yet }
  504. { general rule: aggregate data is aligned in the most significant bits
  505. except for ELFv1 c) and Darwin a) }
  506. if (target_info.endian=endian_big) and
  507. ((target_info.abi in [abi_powerpc_aix,abi_powerpc_elfv2]) or
  508. ((target_info.abi=abi_powerpc_sysv) and
  509. (paralen>8)) or
  510. ((target_info.abi=abi_powerpc_darwin) and
  511. not(paralen in [1,2,4]))) then
  512. tailpadding:=true
  513. { if we don't add tailpadding on the caller side, the callee will have
  514. to shift the value in the register before it can store it to memory }
  515. else if (target_info.endian=endian_big) and
  516. (paralen in [3,5,6,7]) then
  517. parashift:=(8-paralen)*8;
  518. { general fallback rule: pass aggregate types in integer registers
  519. without special adjustments (incl. Darwin h) }
  520. loc:=LOC_REGISTER;
  521. paracgsize:=int_cgsize(paralen);
  522. end
  523. else
  524. begin
  525. loc:=getparaloc(paradef);
  526. paracgsize:=def_cgsize(paradef);
  527. { for things like formaldef }
  528. if (paracgsize=OS_NO) then
  529. begin
  530. paracgsize:=OS_ADDR;
  531. paralen:=tcgsize2size[OS_ADDR];
  532. end;
  533. end
  534. end;
  535. { patch FPU values into integer registers if we are processing varargs }
  536. if (isVararg) and (paradef.typ = floatdef) then begin
  537. loc := LOC_REGISTER;
  538. if paracgsize = OS_F64 then
  539. paracgsize := OS_64
  540. else
  541. paracgsize := OS_32;
  542. end;
  543. { AIX/SysV a), Darwin c) -> skip 4 bytes in the stack frame }
  544. if (target_info.endian=endian_big) and
  545. (paradef.typ=floatdef) and
  546. (tfloatdef(paradef).floattype=s32real) and
  547. (nextfloatreg>RS_F13) then
  548. begin
  549. inc(stack_offset,4);
  550. paraaligned:=true;
  551. end;
  552. { Darwin d) }
  553. if (target_info.abi=abi_powerpc_darwin) and
  554. (paradef.typ in [orddef,enumdef]) and
  555. (paralen<8) and
  556. { we don't have to sign/zero extend the lower 8/16/32 bit on the callee
  557. side since it's done on the caller side; however, if the value is
  558. passed via memory, we do have to modify the stack offset since this
  559. is big endian and otherwise we'll load/store the wrong bytes) }
  560. ((side=callerside) or
  561. forceintmem or
  562. (nextintreg>RS_R10)) then
  563. begin
  564. if side=callerside then
  565. begin
  566. paralen:=8;
  567. paradef:=s64inttype;
  568. paracgsize:=OS_S64;
  569. end
  570. else
  571. begin
  572. inc(stack_offset,8-paralen);
  573. paraaligned:=true;
  574. end;
  575. end;
  576. para.alignment := std_param_align;
  577. para.size := paracgsize;
  578. para.intsize := paralen;
  579. para.def := paradef;
  580. if (paralen = 0) then
  581. if (paradef.typ = recorddef) then begin
  582. paraloc := para.add_location;
  583. paraloc^.loc := LOC_VOID;
  584. end else
  585. internalerror(2005011310);
  586. if not assigned(alllocdef) then
  587. locdef:=paradef
  588. else
  589. begin
  590. locdef:=alllocdef;
  591. paracgsize:=def_cgsize(locdef);
  592. end;
  593. firstparaloc:=true;
  594. { can become < 0 for e.g. 3-byte records }
  595. while (paralen > 0) do begin
  596. paraloc := para.add_location;
  597. { In case of po_delphi_nested_cc, the parent frame pointer
  598. is always passed on the stack. }
  599. if (loc = LOC_REGISTER) and
  600. (nextintreg <= RS_R10) and
  601. not forceintmem then begin
  602. paraloc^.loc := loc;
  603. paraloc^.shiftval := parashift;
  604. { make sure we don't lose whether or not the type is signed }
  605. if (paracgsize <> OS_NO) and
  606. (paradef.typ <> orddef) and
  607. not assigned(alllocdef) then
  608. begin
  609. paracgsize := int_cgsize(paralen);
  610. locdef:=get_paraloc_def(paradef, paralen, firstparaloc);
  611. end;
  612. { Partial aggregate data may have to be left-aligned. If so, add tail
  613. padding }
  614. if tailpadding and
  615. (paralen < sizeof(aint)) then
  616. begin
  617. paraloc^.shiftval := (sizeof(aint)-paralen)*(-8);
  618. paraloc^.size := OS_INT;
  619. paraloc^.def := u64inttype;
  620. end
  621. else if (paracgsize in [OS_NO, OS_128, OS_S128]) then
  622. begin
  623. if (paralen>4) or
  624. (parashift<>0) then
  625. begin
  626. paraloc^.size := OS_INT;
  627. paraloc^.def := osuinttype;
  628. end
  629. else
  630. begin
  631. { for 3-byte records aligned in the lower bits of register }
  632. paraloc^.size := OS_32;
  633. paraloc^.def := u32inttype;
  634. end;
  635. end
  636. else
  637. begin
  638. paraloc^.size := paracgsize;
  639. paraloc^.def := locdef;
  640. end;
  641. paraloc^.register := newreg(R_INTREGISTER, nextintreg, R_SUBNONE);
  642. inc(nextintreg);
  643. dec(paralen, tcgsize2size[paraloc^.size]);
  644. inc(stack_offset, sizeof(pint));
  645. end else if (loc = LOC_FPUREGISTER) and
  646. (nextfloatreg <= RS_F13) then begin
  647. paraloc^.loc := loc;
  648. paraloc^.size := paracgsize;
  649. paraloc^.def := locdef;
  650. paraloc^.register := newreg(R_FPUREGISTER, nextfloatreg, R_SUBWHOLE);
  651. { the PPC64 ABI says that the GPR index is increased for every parameter, no matter
  652. which type it is stored in }
  653. inc(nextintreg);
  654. inc(nextfloatreg);
  655. dec(paralen, tcgsize2size[paraloc^.size]);
  656. inc(stack_offset, tcgsize2size[OS_FLOAT]);
  657. end else if (loc = LOC_MMREGISTER) then begin
  658. { Altivec not supported }
  659. internalerror(200510192);
  660. end else begin
  661. { either LOC_REFERENCE, or one of the above which must be passed on the
  662. stack because of insufficient registers }
  663. paraloc^.loc := LOC_REFERENCE;
  664. case loc of
  665. LOC_FPUREGISTER:
  666. begin
  667. paraloc^.size:=int_float_cgsize(paralen);
  668. case paraloc^.size of
  669. OS_F32: paraloc^.def:=s32floattype;
  670. OS_F64: paraloc^.def:=s64floattype;
  671. else
  672. internalerror(2013060122);
  673. end;
  674. end;
  675. LOC_REGISTER,
  676. LOC_REFERENCE:
  677. begin
  678. paraloc^.size:=int_cgsize(paralen);
  679. paraloc^.def:=get_paraloc_def(paradef, paralen, firstparaloc);
  680. end;
  681. else
  682. internalerror(2006011101);
  683. end;
  684. if (side = callerside) then
  685. paraloc^.reference.index := NR_STACK_POINTER_REG
  686. else begin
  687. { during procedure entry, NR_OLD_STACK_POINTER_REG contains the old stack pointer }
  688. paraloc^.reference.index := NR_OLD_STACK_POINTER_REG;
  689. { create_paraloc_info_intern might be also called when being outside of
  690. code generation so current_procinfo might be not set }
  691. if assigned(current_procinfo) then
  692. tcpuprocinfo(current_procinfo).needs_frame_pointer := true;
  693. end;
  694. paraloc^.reference.offset := stack_offset;
  695. { align temp contents to next register size }
  696. if not paraaligned then
  697. inc(stack_offset, align(paralen, 8))
  698. else
  699. inc(stack_offset, paralen);
  700. paralen := 0;
  701. end;
  702. firstparaloc:=false;
  703. end;
  704. end;
  705. function tcpuparamanager.create_varargs_paraloc_info(p: tabstractprocdef; side: tcallercallee;
  706. varargspara: tvarargsparalist): longint;
  707. var
  708. cur_stack_offset: aword;
  709. parasize, l: longint;
  710. curintreg, firstfloatreg, curfloatreg, curmmreg: tsuperregister;
  711. i: integer;
  712. hp: tparavarsym;
  713. paraloc: pcgparalocation;
  714. begin
  715. init_values(curintreg, curfloatreg, curmmreg, cur_stack_offset);
  716. firstfloatreg := curfloatreg;
  717. result := create_paraloc_info_intern(p, side, p.paras, curintreg,
  718. curfloatreg, curmmreg, cur_stack_offset, false);
  719. if (p.proccalloption in cstylearrayofconst) then
  720. begin
  721. { just continue loading the parameters in the registers }
  722. if assigned(varargspara) then
  723. begin
  724. if side=callerside then
  725. result := create_paraloc_info_intern(p, side, varargspara, curintreg,
  726. curfloatreg, curmmreg, cur_stack_offset, true)
  727. else
  728. internalerror(2019021920);
  729. end;
  730. { varargs routines have to reserve at least 64 bytes for the PPC64 ABI }
  731. if (result < 64) then
  732. result := 64;
  733. end
  734. else
  735. internalerror(2019021911);
  736. if curfloatreg <> firstfloatreg then
  737. include(varargspara.varargsinfo, va_uses_float_reg);
  738. create_funcretloc_info(p, side);
  739. end;
  740. function tcpuparamanager.parseparaloc(p: tparavarsym; const s: string): boolean;
  741. begin
  742. { not supported/required for PowerPC64-linux target }
  743. internalerror(200404182);
  744. result := true;
  745. end;
  746. begin
  747. paramanager := tcpuparamanager.create;
  748. end.