cpupara.pas 26 KB

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