cpupara.pas 26 KB

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