cgcpu.pas 66 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890
  1. {
  2. Copyright (c) 1998-2002 by Florian Klaempfl
  3. This unit implements the code generator for the PowerPC
  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 cgcpu;
  18. {$I fpcdefs.inc}
  19. interface
  20. uses
  21. globtype, symtype, symdef, symsym,
  22. cgbase, cgobj,cgppc,
  23. aasmbase, aasmcpu, aasmtai,aasmdata,
  24. cpubase, cpuinfo, cgutils, rgcpu,
  25. parabase;
  26. type
  27. tcgppc = class(tcgppcgen)
  28. procedure init_register_allocators; override;
  29. procedure done_register_allocators; override;
  30. procedure a_call_name(list: TAsmList; const s: string; weak: boolean); override;
  31. procedure a_call_reg(list: TAsmList; reg: tregister); override;
  32. procedure a_op_const_reg(list: TAsmList; Op: TOpCG; size: TCGSize; a:
  33. aint; reg: TRegister); override;
  34. procedure a_op_reg_reg(list: TAsmList; Op: TOpCG; size: TCGSize; src,
  35. dst: TRegister); override;
  36. procedure a_op_const_reg_reg(list: TAsmList; op: TOpCg;
  37. size: tcgsize; a: aint; src, dst: tregister); override;
  38. procedure a_op_reg_reg_reg(list: TAsmList; op: TOpCg;
  39. size: tcgsize; src1, src2, dst: tregister); override;
  40. { move instructions }
  41. procedure a_load_const_reg(list: TAsmList; size: tcgsize; a: aint; reg:
  42. tregister); override;
  43. { loads the memory pointed to by ref into register reg }
  44. procedure a_load_ref_reg(list: TAsmList; fromsize, tosize: tcgsize; const
  45. Ref: treference; reg: tregister); override;
  46. procedure a_load_reg_reg(list: TAsmList; fromsize, tosize: tcgsize; reg1,
  47. reg2: tregister); override;
  48. { comparison operations }
  49. procedure a_cmp_const_reg_label(list: TAsmList; size: tcgsize; cmp_op:
  50. topcmp; a: aint; reg: tregister;
  51. l: tasmlabel); override;
  52. procedure a_cmp_reg_reg_label(list: TAsmList; size: tcgsize; cmp_op:
  53. topcmp; reg1, reg2: tregister; l: tasmlabel); override;
  54. procedure a_jmp_name(list: TAsmList; const s: string); override;
  55. procedure a_jmp_always(list: TAsmList; l: tasmlabel); override;
  56. { need to override this for ppc64 to avoid calling CG methods which allocate
  57. registers during creation of the interface wrappers to subtract ioffset from
  58. the self pointer. But register allocation does not take place for them (which
  59. would probably be the generic fix) so we need to have a specialized method
  60. that uses the R11 scratch register in these cases.
  61. At the same time this allows > 32 bit offsets as well.
  62. }
  63. procedure g_adjust_self_value(list:TAsmList;procdef: tprocdef;ioffset: aint);override;
  64. procedure g_profilecode(list: TAsmList); override;
  65. procedure g_proc_entry(list: TAsmList; localsize: longint; nostackframe:
  66. boolean); override;
  67. procedure g_proc_exit(list: TAsmList; parasize: longint; nostackframe:
  68. boolean); override;
  69. procedure g_save_registers(list: TAsmList); override;
  70. procedure g_restore_registers(list: TAsmList); override;
  71. procedure a_loadaddr_ref_reg(list: TAsmList; const ref: treference; r:
  72. tregister); override;
  73. procedure g_concatcopy(list: TAsmList; const source, dest: treference;
  74. len: aint); override;
  75. private
  76. procedure maybeadjustresult(list: TAsmList; op: TOpCg; size: tcgsize; dst: tregister);
  77. { returns whether a reference can be used immediately in a powerpc }
  78. { instruction }
  79. function issimpleref(const ref: treference): boolean;
  80. { contains the common code of a_load_reg_ref and a_load_ref_reg }
  81. procedure a_load_store(list: TAsmList; op: tasmop; reg: tregister;
  82. ref: treference); override;
  83. { returns the lowest numbered FP register in use, and the number of used FP registers
  84. for the current procedure }
  85. procedure calcFirstUsedFPR(out firstfpr : TSuperRegister; out fprcount : aint);
  86. { returns the lowest numbered GP register in use, and the number of used GP registers
  87. for the current procedure }
  88. procedure calcFirstUsedGPR(out firstgpr : TSuperRegister; out gprcount : aint);
  89. { generates code to call a method with the given string name. The boolean options
  90. control code generation. If prependDot is true, a single dot character is prepended to
  91. the string, if addNOP is true a single NOP instruction is added after the call, and
  92. if includeCall is true, the method is marked as having a call, not if false. This
  93. option is particularly useful to prevent generation of a larger stack frame for the
  94. register save and restore helper functions. }
  95. procedure a_call_name_direct(list: TAsmList; opc: tasmop; s: string; weak: boolean; prependDot : boolean;
  96. addNOP : boolean; includeCall : boolean = true);
  97. procedure a_jmp_name_direct(list : TAsmList; opc: tasmop; s : string; prependDot : boolean);
  98. { emits code to store the given value a into the TOC (if not already in there), and load it from there
  99. as well }
  100. procedure loadConstantPIC(list : TAsmList; size : TCGSize; a : aint; reg : TRegister);
  101. procedure profilecode_savepara(para : tparavarsym; list : TAsmList);
  102. procedure profilecode_restorepara(para : tparavarsym; list : TAsmList);
  103. end;
  104. procedure create_codegen;
  105. const
  106. TShiftOpCG2AsmOpConst : array[boolean, OP_SAR..OP_SHR] of TAsmOp = (
  107. (A_SRAWI, A_SLWI, A_SRWI), (A_SRADI, A_SLDI, A_SRDI)
  108. );
  109. implementation
  110. uses
  111. sysutils, cclasses,
  112. globals, verbose, systems, cutils,
  113. symconst, fmodule,
  114. rgobj, tgobj, cpupi, procinfo, paramgr, cpupara;
  115. function is_signed_cgsize(const size : TCgSize) : Boolean;
  116. begin
  117. case size of
  118. OS_S8,OS_S16,OS_S32,OS_S64 : result := true;
  119. OS_8,OS_16,OS_32,OS_64 : result := false;
  120. else
  121. internalerror(2006050701);
  122. end;
  123. end;
  124. { finds positive and negative powers of two of the given value, returning the
  125. power and whether it's a negative power or not in addition to the actual result
  126. of the function }
  127. function ispowerof2(value : aInt; out power : byte; out neg : boolean) : boolean;
  128. var
  129. i : longint;
  130. hl : aInt;
  131. begin
  132. result := false;
  133. neg := false;
  134. { also try to find negative power of two's by negating if the
  135. value is negative. low(aInt) is special because it can not be
  136. negated. Simply return the appropriate values for it }
  137. if (value < 0) then begin
  138. neg := true;
  139. if (value = low(aInt)) then begin
  140. power := sizeof(aInt)*8-1;
  141. result := true;
  142. exit;
  143. end;
  144. value := -value;
  145. end;
  146. if ((value and (value-1)) <> 0) then begin
  147. result := false;
  148. exit;
  149. end;
  150. hl := 1;
  151. for i := 0 to (sizeof(aInt)*8-1) do begin
  152. if (hl = value) then begin
  153. result := true;
  154. power := i;
  155. exit;
  156. end;
  157. hl := hl shl 1;
  158. end;
  159. end;
  160. { returns the number of instruction required to load the given integer into a register.
  161. This is basically a stripped down version of a_load_const_reg, increasing a counter
  162. instead of emitting instructions. }
  163. function getInstructionLength(a : aint) : longint;
  164. function get32bitlength(a : longint; var length : longint) : boolean; inline;
  165. var
  166. is_half_signed : byte;
  167. begin
  168. { if the lower 16 bits are zero, do a single LIS }
  169. if (smallint(a) = 0) and ((a shr 16) <> 0) then begin
  170. inc(length);
  171. get32bitlength := longint(a) < 0;
  172. end else begin
  173. is_half_signed := ord(smallint(lo(a)) < 0);
  174. inc(length);
  175. if smallint(hi(a) + is_half_signed) <> 0 then
  176. inc(length);
  177. get32bitlength := (smallint(a) < 0) or (a < 0);
  178. end;
  179. end;
  180. var
  181. extendssign : boolean;
  182. begin
  183. result := 0;
  184. if (lo(a) = 0) and (hi(a) <> 0) then begin
  185. get32bitlength(hi(a), result);
  186. inc(result);
  187. end else begin
  188. extendssign := get32bitlength(lo(a), result);
  189. if (extendssign) and (hi(a) = 0) then
  190. inc(result)
  191. else if (not
  192. ((extendssign and (longint(hi(a)) = -1)) or
  193. ((not extendssign) and (hi(a)=0)))
  194. ) then begin
  195. get32bitlength(hi(a), result);
  196. inc(result);
  197. end;
  198. end;
  199. end;
  200. procedure tcgppc.init_register_allocators;
  201. begin
  202. inherited init_register_allocators;
  203. if (target_info.system <> system_powerpc64_darwin) then
  204. // r13 is tls, do not use, r2 is not available
  205. rg[R_INTREGISTER] := trgintcpu.create(R_INTREGISTER, R_SUBWHOLE,
  206. [{$ifdef user0} RS_R0, {$endif} RS_R3, RS_R4, RS_R5, RS_R6, RS_R7, RS_R8,
  207. RS_R9, RS_R10, RS_R11, RS_R12, RS_R31, RS_R30, RS_R29,
  208. RS_R28, RS_R27, RS_R26, RS_R25, RS_R24, RS_R23, RS_R22,
  209. RS_R21, RS_R20, RS_R19, RS_R18, RS_R17, RS_R16, RS_R15,
  210. RS_R14], first_int_imreg, [])
  211. else
  212. { special for darwin/ppc64: r2 available volatile, r13 = tls }
  213. rg[R_INTREGISTER] := trgintcpu.create(R_INTREGISTER, R_SUBWHOLE,
  214. [{$ifdef user0} RS_R0, {$endif} RS_R2, RS_R3, RS_R4, RS_R5, RS_R6, RS_R7, RS_R8,
  215. RS_R9, RS_R10, RS_R11, RS_R12, RS_R31, RS_R30, RS_R29,
  216. RS_R28, RS_R27, RS_R26, RS_R25, RS_R24, RS_R23, RS_R22,
  217. RS_R21, RS_R20, RS_R19, RS_R18, RS_R17, RS_R16, RS_R15,
  218. RS_R14], first_int_imreg, []);
  219. rg[R_FPUREGISTER] := trgcpu.create(R_FPUREGISTER, R_SUBNONE,
  220. [RS_F0, RS_F1, RS_F2, RS_F3, RS_F4, RS_F5, RS_F6, RS_F7, RS_F8, RS_F9,
  221. RS_F10, RS_F11, RS_F12, RS_F13, RS_F31, RS_F30, RS_F29, RS_F28, RS_F27,
  222. RS_F26, RS_F25, RS_F24, RS_F23, RS_F22, RS_F21, RS_F20, RS_F19, RS_F18,
  223. RS_F17, RS_F16, RS_F15, RS_F14], first_fpu_imreg, []);
  224. { TODO: FIX ME}
  225. rg[R_MMREGISTER] := trgcpu.create(R_MMREGISTER, R_SUBNONE,
  226. [RS_M0, RS_M1, RS_M2], first_mm_imreg, []);
  227. end;
  228. procedure tcgppc.done_register_allocators;
  229. begin
  230. rg[R_INTREGISTER].free;
  231. rg[R_FPUREGISTER].free;
  232. rg[R_MMREGISTER].free;
  233. inherited done_register_allocators;
  234. end;
  235. { calling a procedure by name }
  236. procedure tcgppc.a_call_name(list: TAsmList; const s: string; weak: boolean);
  237. begin
  238. if (target_info.system <> system_powerpc64_darwin) then
  239. a_call_name_direct(list, A_BL, s, weak, target_info.system=system_powerpc64_aix, true)
  240. else
  241. begin
  242. list.concat(taicpu.op_sym(A_BL,get_darwin_call_stub(s,weak)));
  243. include(current_procinfo.flags,pi_do_call);
  244. end;
  245. end;
  246. procedure tcgppc.a_call_name_direct(list: TAsmList; opc: tasmop; s: string; weak: boolean; prependDot : boolean; addNOP : boolean; includeCall : boolean);
  247. begin
  248. if (prependDot) then
  249. s := '.' + s;
  250. if not(weak) then
  251. list.concat(taicpu.op_sym(opc, current_asmdata.RefAsmSymbol(s,AT_FUNCTION)))
  252. else
  253. list.concat(taicpu.op_sym(opc, current_asmdata.WeakRefAsmSymbol(s,AT_FUNCTION)));
  254. if (addNOP) then
  255. list.concat(taicpu.op_none(A_NOP));
  256. if (includeCall) and
  257. assigned(current_procinfo) then
  258. include(current_procinfo.flags, pi_do_call);
  259. end;
  260. function get_rtoc_offset: longint;
  261. begin
  262. result:=0;
  263. case target_info.abi of
  264. abi_powerpc_aix,
  265. abi_powerpc_darwin:
  266. result:=LA_RTOC_AIX;
  267. abi_powerpc_elfv1:
  268. result:=LA_RTOC_SYSV;
  269. abi_powerpc_elfv2:
  270. result:=LA_RTOC_ELFV2;
  271. else
  272. internalerror(2015021001);
  273. end;
  274. end;
  275. { calling a procedure by address }
  276. procedure tcgppc.a_call_reg(list: TAsmList; reg: tregister);
  277. var
  278. tmpref: treference;
  279. tempreg : TRegister;
  280. begin
  281. if (target_info.abi<>abi_powerpc_sysv) then
  282. inherited a_call_reg(list,reg)
  283. else if (not (cs_opt_size in current_settings.optimizerswitches)) then begin
  284. tempreg := getintregister(list, OS_INT);
  285. { load actual function entry (reg contains the reference to the function descriptor)
  286. into tempreg }
  287. reference_reset_base(tmpref, reg, 0, ctempposinvalid, sizeof(pint), []);
  288. a_load_ref_reg(list, OS_ADDR, OS_ADDR, tmpref, tempreg);
  289. { move actual function pointer to CTR register }
  290. list.concat(taicpu.op_reg(A_MTCTR, tempreg));
  291. { load new TOC pointer from function descriptor into RTOC register }
  292. reference_reset_base(tmpref, reg, tcgsize2size[OS_ADDR], ctempposinvalid, 8, []);
  293. a_load_ref_reg(list, OS_ADDR, OS_ADDR, tmpref, NR_RTOC);
  294. { load new environment pointer from function descriptor into R11 register }
  295. reference_reset_base(tmpref, reg, 2*tcgsize2size[OS_ADDR], ctempposinvalid, 8, []);
  296. a_reg_alloc(list, NR_R11);
  297. a_load_ref_reg(list, OS_ADDR, OS_ADDR, tmpref, NR_R11);
  298. { call function }
  299. list.concat(taicpu.op_none(A_BCTRL));
  300. a_reg_dealloc(list, NR_R11);
  301. end else begin
  302. { call ptrgl helper routine which expects the pointer to the function descriptor
  303. in R11 }
  304. a_reg_alloc(list, NR_R11);
  305. a_load_reg_reg(list, OS_ADDR, OS_ADDR, reg, NR_R11);
  306. a_call_name_direct(list, A_BL, '.ptrgl', false, false, false);
  307. a_reg_dealloc(list, NR_R11);
  308. end;
  309. { we need to load the old RTOC from stackframe because we changed it}
  310. reference_reset_base(tmpref, NR_STACK_POINTER_REG, get_rtoc_offset, ctempposinvalid, 8, []);
  311. a_load_ref_reg(list, OS_ADDR, OS_ADDR, tmpref, NR_RTOC);
  312. include(current_procinfo.flags, pi_do_call);
  313. end;
  314. {********************** load instructions ********************}
  315. procedure tcgppc.a_load_const_reg(list: TAsmList; size: TCGSize; a: aint;
  316. reg: TRegister);
  317. { loads a 32 bit constant into the given register, using an optimal instruction sequence.
  318. This is either LIS, LI or LI+ADDIS.
  319. Returns true if during these operations the upper 32 bits were filled with 1 bits (e.g.
  320. sign extension was performed) }
  321. function load32bitconstant(list : TAsmList; size : TCGSize; a : longint;
  322. reg : TRegister) : boolean;
  323. var
  324. is_half_signed : byte;
  325. begin
  326. { if the lower 16 bits are zero, do a single LIS }
  327. if (smallint(a) = 0) and ((a shr 16) <> 0) then begin
  328. list.concat(taicpu.op_reg_const(A_LIS, reg, smallint(hi(a))));
  329. load32bitconstant := longint(a) < 0;
  330. end else begin
  331. is_half_signed := ord(smallint(lo(a)) < 0);
  332. list.concat(taicpu.op_reg_const(A_LI, reg, smallint(a and $ffff)));
  333. if smallint(hi(a) + is_half_signed) <> 0 then begin
  334. list.concat(taicpu.op_reg_reg_const(A_ADDIS, reg, reg, smallint(hi(a) + is_half_signed)));
  335. end;
  336. load32bitconstant := (smallint(a) < 0) or (a < 0);
  337. end;
  338. end;
  339. { loads a 32 bit constant into R0, using an optimal instruction sequence.
  340. This is either LIS, LI or LI+ORIS.
  341. Returns true if during these operations the upper 32 bits were filled with 1 bits (e.g.
  342. sign extension was performed) }
  343. function load32bitconstantR0(list : TAsmList; size : TCGSize; a : longint) : boolean;
  344. begin
  345. { if it's a value we can load with a single LI, do it }
  346. if (a >= low(smallint)) and (a <= high(smallint)) then begin
  347. list.concat(taicpu.op_reg_const(A_LI, NR_R0, smallint(a)));
  348. end else begin
  349. { if the lower 16 bits are zero, do a single LIS }
  350. list.concat(taicpu.op_reg_const(A_LIS, NR_R0, smallint(a shr 16)));
  351. if (smallint(a) <> 0) then begin
  352. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(a)));
  353. end;
  354. end;
  355. load32bitconstantR0 := a < 0;
  356. end;
  357. { emits the code to load a constant by emitting various instructions into the output
  358. code}
  359. procedure loadConstantNormal(list: TAsmList; size : TCgSize; a: aint; reg: TRegister);
  360. var
  361. extendssign : boolean;
  362. instr : taicpu;
  363. begin
  364. if (lo(a) = 0) and (hi(a) <> 0) then begin
  365. { load only upper 32 bits, and shift }
  366. load32bitconstant(list, size, longint(hi(a)), reg);
  367. list.concat(taicpu.op_reg_reg_const(A_SLDI, reg, reg, 32));
  368. end else begin
  369. { load lower 32 bits }
  370. extendssign := load32bitconstant(list, size, longint(lo(a)), reg);
  371. if (extendssign) and (hi(a) = 0) then
  372. { if upper 32 bits are zero, but loading the lower 32 bit resulted in automatic
  373. sign extension, clear those bits }
  374. list.concat(taicpu.op_reg_reg_const_const(A_RLDICL, reg, reg, 0, 32))
  375. else if (not
  376. ((extendssign and (longint(hi(a)) = -1)) or
  377. ((not extendssign) and (hi(a)=0)))
  378. ) then begin
  379. { only load the upper 32 bits, if the automatic sign extension is not okay,
  380. that is, _not_ if
  381. - loading the lower 32 bits resulted in -1 in the upper 32 bits, and the upper
  382. 32 bits should contain -1
  383. - loading the lower 32 bits resulted in 0 in the upper 32 bits, and the upper
  384. 32 bits should contain 0 }
  385. a_reg_alloc(list, NR_R0);
  386. load32bitconstantR0(list, size, longint(hi(a)));
  387. { combine both registers }
  388. list.concat(taicpu.op_reg_reg_const_const(A_RLDIMI, reg, NR_R0, 32, 0));
  389. a_reg_dealloc(list, NR_R0);
  390. end;
  391. end;
  392. end;
  393. {$IFDEF EXTDEBUG}
  394. var
  395. astring : string;
  396. {$ENDIF EXTDEBUG}
  397. begin
  398. {$IFDEF EXTDEBUG}
  399. astring := 'a_load_const_reg ' + inttostr(hi(a)) + ' ' + inttostr(lo(a)) + ' ' + inttostr(ord(size)) + ' ' + inttostr(tcgsize2size[size]) + ' ' + hexstr(a, 16);
  400. list.concat(tai_comment.create(strpnew(astring)));
  401. {$ENDIF EXTDEBUG}
  402. if not (size in [OS_8, OS_S8, OS_16, OS_S16, OS_32, OS_S32, OS_64, OS_S64]) then
  403. internalerror(2002090902);
  404. { if PIC or basic optimizations are enabled, and the number of instructions which would be
  405. required to load the value is greater than 2, store (and later load) the value from there }
  406. // if (((cs_opt_peephole in current_settings.optimizerswitches) or (cs_create_pic in current_settings.moduleswitches)) and
  407. // (getInstructionLength(a) > 2)) then
  408. // loadConstantPIC(list, size, a, reg)
  409. // else
  410. loadConstantNormal(list, size, a, reg);
  411. end;
  412. procedure tcgppc.a_load_ref_reg(list: TAsmList; fromsize, tosize: tcgsize;
  413. const ref: treference; reg: tregister);
  414. const
  415. LoadInstr: array[OS_8..OS_S64, boolean, boolean] of TAsmOp =
  416. { indexed? updating? }
  417. (((A_LBZ, A_LBZU), (A_LBZX, A_LBZUX)),
  418. ((A_LHZ, A_LHZU), (A_LHZX, A_LHZUX)),
  419. ((A_LWZ, A_LWZU), (A_LWZX, A_LWZUX)),
  420. ((A_LD, A_LDU), (A_LDX, A_LDUX)),
  421. { 128bit stuff too }
  422. ((A_NONE, A_NONE), (A_NONE, A_NONE)),
  423. { there's no load-byte-with-sign-extend :( }
  424. ((A_LBZ, A_LBZU), (A_LBZX, A_LBZUX)),
  425. ((A_LHA, A_LHAU), (A_LHAX, A_LHAUX)),
  426. { there's no load-word-arithmetic-indexed with update, simulate it in code :( }
  427. ((A_LWA, A_NOP), (A_LWAX, A_LWAUX)),
  428. ((A_LD, A_LDU), (A_LDX, A_LDUX))
  429. );
  430. var
  431. op: tasmop;
  432. ref2: treference;
  433. tmpreg: tregister;
  434. begin
  435. if target_info.system=system_powerpc64_aix then
  436. g_load_check_simple(list,ref,65536);
  437. {$IFDEF EXTDEBUG}
  438. list.concat(tai_comment.create(strpnew('a_load_ref_reg ' + ref2string(ref))));
  439. {$ENDIF EXTDEBUG}
  440. if not (fromsize in [OS_8, OS_S8, OS_16, OS_S16, OS_32, OS_S32, OS_64, OS_S64]) then
  441. internalerror(2002090910);
  442. { the caller is expected to have adjusted the reference already
  443. in this case }
  444. if (TCGSize2Size[fromsize] >= TCGSize2Size[tosize]) then
  445. fromsize := tosize;
  446. ref2 := ref;
  447. fixref(list, ref2);
  448. op := loadinstr[fromsize, ref2.index <> NR_NO, false];
  449. { there is no LWAU instruction, simulate using ADDI and LWA }
  450. if (op = A_NOP) then begin
  451. list.concat(taicpu.op_reg_reg_const(A_ADDI, reg, reg, ref2.offset));
  452. ref2.offset := 0;
  453. op := A_LWA;
  454. end;
  455. a_load_store(list, op, reg, ref2);
  456. { sign extend shortint if necessary (because there is
  457. no load instruction to sign extend an 8 bit value automatically)
  458. and mask out extra sign bits when loading from a smaller
  459. signed to a larger unsigned type (where it matters) }
  460. if (fromsize = OS_S8) then begin
  461. a_load_reg_reg(list, OS_8, OS_S8, reg, reg);
  462. a_load_reg_reg(list, OS_S8, tosize, reg, reg);
  463. end else if (fromsize = OS_S16) and (tosize = OS_32) then
  464. a_load_reg_reg(list, fromsize, tosize, reg, reg);
  465. end;
  466. procedure tcgppc.a_load_reg_reg(list: TAsmList; fromsize, tosize: tcgsize;
  467. reg1, reg2: tregister);
  468. var
  469. instr: TAiCpu;
  470. bytesize : byte;
  471. begin
  472. {$ifdef extdebug}
  473. list.concat(tai_comment.create(strpnew('a_load_reg_reg from : ' + tcgsize2str(fromsize) + ' to ' + tcgsize2str(tosize))));
  474. {$endif}
  475. if (tcgsize2size[fromsize] > tcgsize2size[tosize]) or
  476. ((tcgsize2size[fromsize] = tcgsize2size[tosize]) and (fromsize <> tosize)) or
  477. { do we need to mask out the sign when loading from smaller signed to larger unsigned type? }
  478. ( is_signed_cgsize(fromsize) and (not is_signed_cgsize(tosize)) and
  479. (tcgsize2size[fromsize] < tcgsize2size[tosize]) and (tcgsize2size[tosize] <> sizeof(pint)) ) then begin
  480. case tosize of
  481. OS_S8:
  482. instr := taicpu.op_reg_reg(A_EXTSB,reg2,reg1);
  483. OS_S16:
  484. instr := taicpu.op_reg_reg(A_EXTSH,reg2,reg1);
  485. OS_S32:
  486. instr := taicpu.op_reg_reg(A_EXTSW,reg2,reg1);
  487. OS_8, OS_16, OS_32:
  488. instr := taicpu.op_reg_reg_const_const(A_RLDICL, reg2, reg1, 0, (8-tcgsize2size[tosize])*8);
  489. OS_S64, OS_64:
  490. instr := taicpu.op_reg_reg(A_MR, reg2, reg1);
  491. else
  492. internalerror(2013113007);
  493. end;
  494. end else
  495. instr := taicpu.op_reg_reg(A_MR, reg2, reg1);
  496. list.concat(instr);
  497. rg[R_INTREGISTER].add_move_instruction(instr);
  498. end;
  499. procedure tcgppc.a_op_const_reg(list: TAsmList; Op: TOpCG; size: TCGSize; a:
  500. aint; reg: TRegister);
  501. begin
  502. a_op_const_reg_reg(list, op, size, a, reg, reg);
  503. end;
  504. procedure tcgppc.a_op_reg_reg(list: TAsmList; Op: TOpCG; size: TCGSize; src,
  505. dst: TRegister);
  506. begin
  507. a_op_reg_reg_reg(list, op, size, src, dst, dst);
  508. end;
  509. procedure tcgppc.a_op_const_reg_reg(list: TAsmList; op: TOpCg;
  510. size: tcgsize; a: aint; src, dst: tregister);
  511. var
  512. useReg : boolean;
  513. procedure do_lo_hi(loOp, hiOp : TAsmOp);
  514. begin
  515. { Optimization for logical ops (excluding AND), trying to do this as efficiently
  516. as possible by only generating code for the affected halfwords. Note that all
  517. the instructions handled here must have "X op 0 = X" for every halfword. }
  518. usereg := false;
  519. if (aword(a) > high(dword)) then begin
  520. usereg := true;
  521. end else begin
  522. if (word(a) <> 0) then begin
  523. list.concat(taicpu.op_reg_reg_const(loOp, dst, src, word(a)));
  524. if (word(a shr 16) <> 0) then
  525. list.concat(taicpu.op_reg_reg_const(hiOp, dst, dst, word(a shr 16)));
  526. end else if (word(a shr 16) <> 0) then
  527. list.concat(taicpu.op_reg_reg_const(hiOp, dst, src, word(a shr 16)));
  528. end;
  529. end;
  530. procedure do_lo_hi_and;
  531. begin
  532. { optimization logical and with immediate: only use "andi." for 16 bit
  533. ands, otherwise use register method. Doing this for 32 bit constants
  534. would not give any advantage to the register method (via useReg := true),
  535. requiring a scratch register and three instructions. }
  536. usereg := false;
  537. if (aword(a) > high(word)) then
  538. usereg := true
  539. else
  540. list.concat(taicpu.op_reg_reg_const(A_ANDI_, dst, src, word(a)));
  541. end;
  542. procedure do_constant_div(list : TAsmList; size : TCgSize; a : aint; src, dst : TRegister;
  543. signed : boolean);
  544. const
  545. negops : array[boolean] of tasmop = (A_NEG, A_NEGO);
  546. var
  547. magic : int64;
  548. u_magic : qword;
  549. u_shift : byte;
  550. u_add : boolean;
  551. power : byte;
  552. isNegPower : boolean;
  553. divreg : tregister;
  554. begin
  555. if (a = 0) then begin
  556. internalerror(2005061701);
  557. end else if (a = 1) then begin
  558. a_load_reg_reg(list, OS_INT, OS_INT, src, dst);
  559. end else if (a = -1) and (signed) then begin
  560. { note: only in the signed case possible..., may overflow }
  561. list.concat(taicpu.op_reg_reg(negops[cs_check_overflow in current_settings.localswitches], dst, src));
  562. end else if (ispowerof2(a, power, isNegPower)) then begin
  563. if (signed) then begin
  564. { From "The PowerPC Compiler Writer's Guide", pg. 52ff }
  565. a_op_const_reg_reg(list, OP_SAR, OS_INT, power,
  566. src, dst);
  567. list.concat(taicpu.op_reg_reg(A_ADDZE, dst, dst));
  568. if (isNegPower) then
  569. list.concat(taicpu.op_reg_reg(A_NEG, dst, dst));
  570. end else begin
  571. a_op_const_reg_reg(list, OP_SHR, OS_INT, power, src, dst)
  572. end;
  573. end else begin
  574. { replace division by multiplication, both implementations }
  575. { from "The PowerPC Compiler Writer's Guide" pg. 53ff }
  576. divreg := getintregister(list, OS_INT);
  577. if (signed) then begin
  578. calc_divconst_magic_signed(sizeof(aInt)*8, a, magic, u_shift);
  579. { load magic value }
  580. a_load_const_reg(list, OS_INT, magic, divreg);
  581. { multiply }
  582. list.concat(taicpu.op_reg_reg_reg(A_MULHD, dst, src, divreg));
  583. { add/subtract numerator }
  584. if (a > 0) and (magic < 0) then begin
  585. a_op_reg_reg_reg(list, OP_ADD, OS_INT, src, dst, dst);
  586. end else if (a < 0) and (magic > 0) then begin
  587. a_op_reg_reg_reg(list, OP_SUB, OS_INT, src, dst, dst);
  588. end;
  589. { shift shift places to the right (arithmetic) }
  590. a_op_const_reg_reg(list, OP_SAR, OS_INT, u_shift, dst, dst);
  591. { extract and add sign bit }
  592. if (a >= 0) then begin
  593. a_op_const_reg_reg(list, OP_SHR, OS_INT, 63, src, divreg);
  594. end else begin
  595. a_op_const_reg_reg(list, OP_SHR, OS_INT, 63, dst, divreg);
  596. end;
  597. a_op_reg_reg_reg(list, OP_ADD, OS_INT, dst, divreg, dst);
  598. end else begin
  599. calc_divconst_magic_unsigned(sizeof(aWord)*8, a, u_magic, u_add, u_shift);
  600. { load magic in divreg }
  601. a_load_const_reg(list, OS_INT, aint(u_magic), divreg);
  602. list.concat(taicpu.op_reg_reg_reg(A_MULHDU, dst, src, divreg));
  603. if (u_add) then begin
  604. a_op_reg_reg_reg(list, OP_SUB, OS_INT, dst, src, divreg);
  605. a_op_const_reg_reg(list, OP_SHR, OS_INT, 1, divreg, divreg);
  606. a_op_reg_reg_reg(list, OP_ADD, OS_INT, divreg, dst, divreg);
  607. a_op_const_reg_reg(list, OP_SHR, OS_INT, u_shift-1, divreg, dst);
  608. end else begin
  609. a_op_const_reg_reg(list, OP_SHR, OS_INT, u_shift, dst, dst);
  610. end;
  611. end;
  612. end;
  613. end;
  614. var
  615. scratchreg: tregister;
  616. shift : byte;
  617. shiftmask : longint;
  618. isneg : boolean;
  619. begin
  620. { subtraction is the same as addition with negative constant }
  621. if op = OP_SUB then begin
  622. a_op_const_reg_reg(list, OP_ADD, size, -a, src, dst);
  623. exit;
  624. end;
  625. {$IFDEF EXTDEBUG}
  626. list.concat(tai_comment.create(strpnew('a_op_const_reg_reg ' + cgop2string(op))));
  627. {$ENDIF EXTDEBUG}
  628. { This case includes some peephole optimizations for the various operations,
  629. (e.g. AND, OR, XOR, ..) - can't this be done at some higher level,
  630. independent of architecture? }
  631. { assume that we do not need a scratch register for the operation }
  632. useReg := false;
  633. case (op) of
  634. OP_DIV, OP_IDIV:
  635. if (cs_opt_level1 in current_settings.optimizerswitches) then
  636. do_constant_div(list, size, a, src, dst, op = OP_IDIV)
  637. else
  638. usereg := true;
  639. OP_IMUL, OP_MUL:
  640. { idea: factorize constant multiplicands and use adds/shifts with few factors;
  641. however, even a 64 bit multiply is already quite fast on PPC64 }
  642. if (a = 0) then
  643. a_load_const_reg(list, size, 0, dst)
  644. else if (a = -1) then
  645. list.concat(taicpu.op_reg_reg(A_NEG, dst, dst))
  646. else if (a = 1) then
  647. a_load_reg_reg(list, OS_INT, OS_INT, src, dst)
  648. else if ispowerof2(a, shift, isneg) then begin
  649. list.concat(taicpu.op_reg_reg_const(A_SLDI, dst, src, shift));
  650. if (isneg) then
  651. list.concat(taicpu.op_reg_reg(A_NEG, dst, dst));
  652. end else if (a >= low(smallint)) and (a <= high(smallint)) then
  653. list.concat(taicpu.op_reg_reg_const(A_MULLI, dst, src,
  654. smallint(a)))
  655. else
  656. usereg := true;
  657. OP_ADD:
  658. if (a = 0) then
  659. a_load_reg_reg(list, size, size, src, dst)
  660. else if (a >= low(smallint)) and (a <= high(smallint)) then
  661. list.concat(taicpu.op_reg_reg_const(A_ADDI, dst, src, smallint(a)))
  662. else
  663. useReg := true;
  664. OP_OR:
  665. if (a = 0) then
  666. a_load_reg_reg(list, size, size, src, dst)
  667. else if (a = -1) then
  668. a_load_const_reg(list, size, -1, dst)
  669. else
  670. do_lo_hi(A_ORI, A_ORIS);
  671. OP_AND:
  672. if (a = 0) then
  673. a_load_const_reg(list, size, 0, dst)
  674. else if (a = -1) then
  675. a_load_reg_reg(list, size, size, src, dst)
  676. else
  677. do_lo_hi_and;
  678. OP_XOR:
  679. if (a = 0) then
  680. a_load_reg_reg(list, size, size, src, dst)
  681. else if (a = -1) then
  682. list.concat(taicpu.op_reg_reg(A_NOT, dst, src))
  683. else
  684. do_lo_hi(A_XORI, A_XORIS);
  685. OP_ROL:
  686. begin
  687. if (size in [OS_64, OS_S64]) then begin
  688. list.concat(taicpu.op_reg_reg_const_const(A_RLDICL, dst, src, a and 63, 0));
  689. end else if (size in [OS_32, OS_S32]) then begin
  690. list.concat(taicpu.op_reg_reg_const_const_const(A_RLWINM, dst, src, a and 31, 0, 31));
  691. end else begin
  692. internalerror(2008091303);
  693. end;
  694. end;
  695. OP_ROR:
  696. begin
  697. if (size in [OS_64, OS_S64]) then begin
  698. list.concat(taicpu.op_reg_reg_const_const(A_RLDICL, dst, src, ((64 - a) and 63), 0));
  699. end else if (size in [OS_32, OS_S32]) then begin
  700. list.concat(taicpu.op_reg_reg_const_const_const(A_RLWINM, dst, src, (32 - a) and 31, 0, 31));
  701. end else begin
  702. internalerror(2008091304);
  703. end;
  704. end;
  705. OP_SHL, OP_SHR, OP_SAR:
  706. begin
  707. if (size in [OS_64, OS_S64]) then
  708. shift := 6
  709. else
  710. shift := 5;
  711. shiftmask := (1 shl shift)-1;
  712. if (a and shiftmask) <> 0 then begin
  713. list.concat(taicpu.op_reg_reg_const(
  714. TShiftOpCG2AsmOpConst[size in [OS_64, OS_S64], op], dst, src, a and shiftmask));
  715. end else
  716. a_load_reg_reg(list, size, size, src, dst);
  717. if ((a shr shift) <> 0) then
  718. internalError(68991);
  719. end
  720. else
  721. internalerror(200109091);
  722. end;
  723. { if all else failed, load the constant in a register and then
  724. perform the operation }
  725. if (useReg) then begin
  726. scratchreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  727. a_load_const_reg(list, size, a, scratchreg);
  728. a_op_reg_reg_reg(list, op, size, scratchreg, src, dst);
  729. end else
  730. maybeadjustresult(list, op, size, dst);
  731. end;
  732. procedure tcgppc.a_op_reg_reg_reg(list: TAsmList; op: TOpCg;
  733. size: tcgsize; src1, src2, dst: tregister);
  734. const
  735. op_reg_reg_opcg2asmop32: array[TOpCG] of tasmop =
  736. (A_NONE, A_MR, A_ADD, A_AND, A_DIVWU, A_DIVW, A_MULLW, A_MULLW, A_NEG, A_NOT, A_OR,
  737. A_SRAW, A_SLW, A_SRW, A_SUB, A_XOR, A_NONE, A_NONE);
  738. op_reg_reg_opcg2asmop64: array[TOpCG] of tasmop =
  739. (A_NONE, A_MR, A_ADD, A_AND, A_DIVDU, A_DIVD, A_MULLD, A_MULLD, A_NEG, A_NOT, A_OR,
  740. A_SRAD, A_SLD, A_SRD, A_SUB, A_XOR, A_NONE, A_NONE);
  741. var
  742. tmpreg : TRegister;
  743. begin
  744. case op of
  745. OP_NEG, OP_NOT:
  746. begin
  747. list.concat(taicpu.op_reg_reg(op_reg_reg_opcg2asmop64[op], dst, src1));
  748. if (op = OP_NOT) and not (size in [OS_64, OS_S64]) then
  749. { zero/sign extend result again, fromsize is not important here }
  750. a_load_reg_reg(list, OS_S64, size, dst, dst)
  751. end;
  752. OP_ROL:
  753. begin
  754. if (size in [OS_64, OS_S64]) then begin
  755. list.concat(taicpu.op_reg_reg_reg_const(A_RLDCL, dst, src2, src1, 0));
  756. end else if (size in [OS_32, OS_S32]) then begin
  757. list.concat(taicpu.op_reg_reg_reg_const_const(A_RLWNM, dst, src2, src1, 0, 31));
  758. end else begin
  759. internalerror(2008091301);
  760. end;
  761. end;
  762. OP_ROR:
  763. begin
  764. tmpreg := getintregister(list, OS_INT);
  765. list.concat(taicpu.op_reg_reg(A_NEG, tmpreg, src1));
  766. if (size in [OS_64, OS_S64]) then begin
  767. list.concat(taicpu.op_reg_reg_reg_const(A_RLDCL, dst, src2, tmpreg, 0));
  768. end else if (size in [OS_32, OS_S32]) then begin
  769. list.concat(taicpu.op_reg_reg_reg_const_const(A_RLWNM, dst, src2, tmpreg, 0, 31));
  770. end else begin
  771. internalerror(2008091302);
  772. end;
  773. end;
  774. else
  775. if (size in [OS_64, OS_S64]) then begin
  776. list.concat(taicpu.op_reg_reg_reg(op_reg_reg_opcg2asmop64[op], dst, src2,
  777. src1));
  778. end else begin
  779. list.concat(taicpu.op_reg_reg_reg(op_reg_reg_opcg2asmop32[op], dst, src2,
  780. src1));
  781. maybeadjustresult(list, op, size, dst);
  782. end;
  783. end;
  784. end;
  785. {*************** compare instructructions ****************}
  786. procedure tcgppc.a_cmp_const_reg_label(list: TAsmList; size: tcgsize;
  787. cmp_op: topcmp; a: aint; reg: tregister; l: tasmlabel);
  788. const
  789. { unsigned useconst 32bit-op }
  790. cmpop_table : array[boolean, boolean, boolean] of TAsmOp = (
  791. ((A_CMPD, A_CMPW), (A_CMPDI, A_CMPWI)),
  792. ((A_CMPLD, A_CMPLW), (A_CMPLDI, A_CMPLWI))
  793. );
  794. var
  795. tmpreg : TRegister;
  796. signed, useconst : boolean;
  797. opsize : TCgSize;
  798. op : TAsmOp;
  799. begin
  800. {$IFDEF EXTDEBUG}
  801. list.concat(tai_comment.create(strpnew('a_cmp_const_reg_label ' + tcgsize2str(size) + ' ' + booltostr(cmp_op in [OC_GT, OC_LT, OC_GTE, OC_LTE]) + ' ' + inttostr(a) )));
  802. {$ENDIF EXTDEBUG}
  803. signed := cmp_op in [OC_GT, OC_LT, OC_GTE, OC_LTE];
  804. { in the following case, we generate more efficient code when
  805. signed is true }
  806. if (cmp_op in [OC_EQ, OC_NE]) and
  807. (aword(a) > $FFFF) then
  808. signed := true;
  809. opsize := size;
  810. { do we need to change the operand size because ppc64 only supports 32 and
  811. 64 bit compares? }
  812. if (not (size in [OS_32, OS_S32, OS_64, OS_S64])) then begin
  813. if (signed) then
  814. opsize := OS_S32
  815. else
  816. opsize := OS_32;
  817. a_load_reg_reg(list, size, opsize, reg, reg);
  818. end;
  819. { can we use immediate compares? }
  820. useconst := (signed and ( (a >= low(smallint)) and (a <= high(smallint)))) or
  821. ((not signed) and (aword(a) <= $FFFF));
  822. op := cmpop_table[not signed, useconst, opsize in [OS_32, OS_S32]];
  823. if (useconst) then begin
  824. list.concat(taicpu.op_reg_reg_const(op, NR_CR0, reg, a));
  825. end else begin
  826. tmpreg := getintregister(list, OS_INT);
  827. a_load_const_reg(list, opsize, a, tmpreg);
  828. list.concat(taicpu.op_reg_reg_reg(op, NR_CR0, reg, tmpreg));
  829. end;
  830. a_jmp(list, A_BC, TOpCmp2AsmCond[cmp_op], 0, l);
  831. end;
  832. procedure tcgppc.a_cmp_reg_reg_label(list: TAsmList; size: tcgsize;
  833. cmp_op: topcmp; reg1, reg2: tregister; l: tasmlabel);
  834. var
  835. op: tasmop;
  836. begin
  837. {$IFDEF extdebug}
  838. list.concat(tai_comment.create(strpnew('a_cmp_reg_reg_label, size ' + tcgsize2str(size) + ' op ' + inttostr(ord(cmp_op)))));
  839. {$ENDIF extdebug}
  840. {$note Commented out below check because of compiler weirdness}
  841. {
  842. if (not (size in [OS_32, OS_S32, OS_64, OS_S64])) then
  843. internalerror(200606041);
  844. }
  845. if cmp_op in [OC_GT, OC_LT, OC_GTE, OC_LTE] then
  846. if (size in [OS_64, OS_S64]) then
  847. op := A_CMPD
  848. else
  849. op := A_CMPW
  850. else
  851. if (size in [OS_64, OS_S64]) then
  852. op := A_CMPLD
  853. else
  854. op := A_CMPLW;
  855. list.concat(taicpu.op_reg_reg_reg(op, NR_CR0, reg2, reg1));
  856. a_jmp(list, A_BC, TOpCmp2AsmCond[cmp_op], 0, l);
  857. end;
  858. procedure tcgppc.a_jmp_name_direct(list : TAsmList; opc: tasmop; s : string; prependDot : boolean);
  859. var
  860. p: taicpu;
  861. begin
  862. if (prependDot) then
  863. s := '.' + s;
  864. p := taicpu.op_sym(opc, current_asmdata.RefAsmSymbol(s,AT_FUNCTION));
  865. p.is_jmp := true;
  866. list.concat(p)
  867. end;
  868. procedure tcgppc.a_jmp_name(list: TAsmList; const s: string);
  869. var
  870. p: taicpu;
  871. begin
  872. if (target_info.system = system_powerpc64_darwin) then
  873. begin
  874. p := taicpu.op_sym(A_B,get_darwin_call_stub(s,false));
  875. p.is_jmp := true;
  876. list.concat(p)
  877. end
  878. else
  879. a_jmp_name_direct(list, A_B, s, true);
  880. end;
  881. procedure tcgppc.a_jmp_always(list: TAsmList; l: tasmlabel);
  882. begin
  883. a_jmp(list, A_B, C_None, 0, l);
  884. end;
  885. { *********** entry/exit code and address loading ************ }
  886. procedure tcgppc.g_save_registers(list: TAsmList);
  887. begin
  888. { this work is done in g_proc_entry; additionally it is not safe
  889. to use it because it is called at some weird time }
  890. end;
  891. procedure tcgppc.g_restore_registers(list: TAsmList);
  892. begin
  893. { this work is done in g_proc_exit; mainly because it is not safe to
  894. put the register restore code here because it is called at some weird time }
  895. end;
  896. procedure tcgppc.calcFirstUsedFPR(out firstfpr : TSuperRegister; out fprcount : aint);
  897. var
  898. reg : TSuperRegister;
  899. begin
  900. fprcount := 0;
  901. firstfpr := RS_F31;
  902. if not (po_assembler in current_procinfo.procdef.procoptions) then
  903. for reg := RS_F14 to RS_F31 do
  904. if reg in rg[R_FPUREGISTER].used_in_proc then begin
  905. fprcount := ord(RS_F31)-ord(reg)+1;
  906. firstfpr := reg;
  907. break;
  908. end;
  909. end;
  910. procedure tcgppc.calcFirstUsedGPR(out firstgpr : TSuperRegister; out gprcount : aint);
  911. var
  912. reg : TSuperRegister;
  913. begin
  914. gprcount := 0;
  915. firstgpr := RS_R31;
  916. if not (po_assembler in current_procinfo.procdef.procoptions) then
  917. for reg := RS_R14 to RS_R31 do
  918. if reg in rg[R_INTREGISTER].used_in_proc then begin
  919. gprcount := ord(RS_R31)-ord(reg)+1;
  920. firstgpr := reg;
  921. break;
  922. end;
  923. end;
  924. procedure tcgppc.profilecode_savepara(para : tparavarsym; list : TAsmList);
  925. begin
  926. case (para.paraloc[calleeside].location^.loc) of
  927. LOC_REGISTER, LOC_CREGISTER:
  928. a_load_reg_ref(list, OS_INT, para.paraloc[calleeside].Location^.size,
  929. para.paraloc[calleeside].Location^.register, para.localloc.reference);
  930. LOC_FPUREGISTER, LOC_CFPUREGISTER:
  931. a_loadfpu_reg_ref(list, para.paraloc[calleeside].Location^.size,
  932. para.paraloc[calleeside].Location^.size,
  933. para.paraloc[calleeside].Location^.register, para.localloc.reference);
  934. LOC_MMREGISTER, LOC_CMMREGISTER:
  935. { not supported }
  936. internalerror(2006041801);
  937. else
  938. ;
  939. end;
  940. end;
  941. procedure tcgppc.profilecode_restorepara(para : tparavarsym; list : TAsmList);
  942. begin
  943. case (para.paraloc[calleeside].Location^.loc) of
  944. LOC_REGISTER, LOC_CREGISTER:
  945. a_load_ref_reg(list, para.paraloc[calleeside].Location^.size, OS_INT,
  946. para.localloc.reference, para.paraloc[calleeside].Location^.register);
  947. LOC_FPUREGISTER, LOC_CFPUREGISTER:
  948. a_loadfpu_ref_reg(list, para.paraloc[calleeside].Location^.size,
  949. para.paraloc[calleeside].Location^.size,
  950. para.localloc.reference, para.paraloc[calleeside].Location^.register);
  951. LOC_MMREGISTER, LOC_CMMREGISTER:
  952. { not supported }
  953. internalerror(2006041802);
  954. else
  955. ;
  956. end;
  957. end;
  958. procedure tcgppc.g_adjust_self_value(list:TAsmList;procdef: tprocdef;ioffset: aint);
  959. var
  960. hsym : tsym;
  961. href : treference;
  962. paraloc : Pcgparalocation;
  963. begin
  964. if ((ioffset >= low(smallint)) and (ioffset < high(smallint))) then begin
  965. { the original method can handle this }
  966. inherited g_adjust_self_value(list, procdef, ioffset);
  967. exit;
  968. end;
  969. { calculate the parameter info for the procdef }
  970. procdef.init_paraloc_info(callerside);
  971. hsym:=tsym(procdef.parast.Find('self'));
  972. if not(assigned(hsym) and
  973. (hsym.typ=paravarsym)) then
  974. internalerror(2010103101);
  975. paraloc:=tparavarsym(hsym).paraloc[callerside].location;
  976. while paraloc<>nil do
  977. with paraloc^ do begin
  978. case loc of
  979. LOC_REGISTER:
  980. begin
  981. a_load_const_reg(list, size, ioffset, NR_R11);
  982. a_op_reg_reg(list, OP_SUB, size, NR_R11, register);
  983. end else
  984. internalerror(2010103102);
  985. end;
  986. paraloc:=next;
  987. end;
  988. end;
  989. procedure tcgppc.g_profilecode(list: TAsmList);
  990. begin
  991. current_procinfo.procdef.paras.ForEachCall(TObjectListCallback(@profilecode_savepara), list);
  992. a_call_name_direct(list, A_BL, '_mcount', false, false, true);
  993. current_procinfo.procdef.paras.ForEachCall(TObjectListCallback(@profilecode_restorepara), list);
  994. end;
  995. { Generates the entry code of a procedure/function.
  996. This procedure may be called before, as well as after g_return_from_proc
  997. is called. localsize is the sum of the size necessary for local variables
  998. and the maximum possible combined size of ALL the parameters of a procedure
  999. called by the current one
  1000. IMPORTANT: registers are not to be allocated through the register
  1001. allocator here, because the register colouring has already occurred !!
  1002. }
  1003. procedure tcgppc.g_proc_entry(list: TAsmList; localsize: longint;
  1004. nostackframe: boolean);
  1005. var
  1006. firstregfpu, firstreggpr: TSuperRegister;
  1007. needslinkreg: boolean;
  1008. fprcount, gprcount : aint;
  1009. { Save standard registers, both FPR and GPR; does not support VMX/Altivec }
  1010. procedure save_standard_registers;
  1011. var
  1012. regcount : TSuperRegister;
  1013. href : TReference;
  1014. mayNeedLRStore : boolean;
  1015. opc : tasmop;
  1016. begin
  1017. { there are two ways to do this: manually, by generating a few "std" instructions,
  1018. or via the restore helper functions. The latter are selected by the -Og switch,
  1019. i.e. "optimize for size" }
  1020. if (cs_opt_size in current_settings.optimizerswitches) and
  1021. (target_info.system <> system_powerpc64_darwin) then begin
  1022. mayNeedLRStore := false;
  1023. if target_info.system=system_powerpc64_aix then
  1024. opc:=A_BLA
  1025. else
  1026. opc:=A_BL;
  1027. if ((fprcount > 0) and (gprcount > 0)) then begin
  1028. a_op_const_reg_reg(list, OP_SUB, OS_INT, 8 * fprcount, NR_R1, NR_R12);
  1029. a_call_name_direct(list, opc, '_savegpr1_' + intToStr(32-gprcount), false, false, false, false);
  1030. a_call_name_direct(list, opc, '_savefpr_' + intToStr(32-fprcount), false, false, false, false);
  1031. end else if (gprcount > 0) then
  1032. a_call_name_direct(list, opc, '_savegpr0_' + intToStr(32-gprcount), false, false, false, false)
  1033. else if (fprcount > 0) then
  1034. a_call_name_direct(list, opc, '_savefpr_' + intToStr(32-fprcount), false, false, false, false)
  1035. else
  1036. mayNeedLRStore := true;
  1037. end else begin
  1038. { save registers, FPU first, then GPR }
  1039. reference_reset_base(href, NR_STACK_POINTER_REG, -8, ctempposinvalid, 8, []);
  1040. if (fprcount > 0) then
  1041. for regcount := RS_F31 downto firstregfpu do begin
  1042. a_loadfpu_reg_ref(list, OS_FLOAT, OS_FLOAT, newreg(R_FPUREGISTER,
  1043. regcount, R_SUBNONE), href);
  1044. dec(href.offset, tcgsize2size[OS_FLOAT]);
  1045. end;
  1046. if (gprcount > 0) then
  1047. for regcount := RS_R31 downto firstreggpr do begin
  1048. a_load_reg_ref(list, OS_INT, OS_INT, newreg(R_INTREGISTER, regcount,
  1049. R_SUBNONE), href);
  1050. dec(href.offset, sizeof(pint));
  1051. end;
  1052. { VMX registers not supported by FPC atm }
  1053. { in this branch we always need to store LR ourselves}
  1054. mayNeedLRStore := true;
  1055. end;
  1056. { we may need to store R0 (=LR) ourselves }
  1057. if ((cs_profile in init_settings.moduleswitches) or (mayNeedLRStore)) and (needslinkreg) then begin
  1058. reference_reset_base(href, NR_STACK_POINTER_REG, LA_LR_SYSV, ctempposinvalid, 8, []);
  1059. list.concat(taicpu.op_reg_ref(A_STD, NR_R0, href));
  1060. end;
  1061. end;
  1062. var
  1063. href: treference;
  1064. lab: tasmlabel;
  1065. procmangledname: TSymStr;
  1066. begin
  1067. { In ELFv2 the function is required to initialise the TOC register itself
  1068. if necessary. Additionally, it has to mark the end of this TOC
  1069. initialisation code with a .localfunc directive, which will be used as
  1070. local entry code by the linker (when it knows the TOC value is the same
  1071. for the caller and callee). It must load the TOC in a PIC-way, which it
  1072. can do easily because R12 is guaranteed to hold the address of this function
  1073. on entry. }
  1074. if (target_info.abi=abi_powerpc_elfv2) and
  1075. (pi_needs_got in current_procinfo.flags) and
  1076. not nostackframe then
  1077. begin
  1078. current_asmdata.getlabel(lab,alt_addr);
  1079. getcpuregister(list,NR_R12);
  1080. getcpuregister(list,NR_R2);
  1081. cg.a_label(list,lab);
  1082. reference_reset_symbol(href,current_asmdata.RefAsmSymbol('.TOC.',AT_DATA),0,sizeof(PInt),[]);
  1083. href.relsymbol:=lab;
  1084. href.refaddr:=addr_higha;
  1085. list.concat(taicpu.op_reg_reg_ref(a_addis,NR_R2,NR_R12,href));
  1086. href.refaddr:=addr_low;
  1087. list.concat(taicpu.op_reg_reg_ref(a_addi,NR_R2,NR_R2,href));
  1088. procmangledname:=current_procinfo.procdef.mangledname;
  1089. list.concat(tai_symbolpair.create(spk_localentry,procmangledname,procmangledname));
  1090. end;
  1091. calcFirstUsedFPR(firstregfpu, fprcount);
  1092. calcFirstUsedGPR(firstreggpr, gprcount);
  1093. { calculate real stack frame size }
  1094. localsize := tcpuprocinfo(current_procinfo).calc_stackframe_size(
  1095. gprcount, fprcount);
  1096. { determine whether we need to save the link register }
  1097. needslinkreg :=
  1098. not(nostackframe) and
  1099. (save_lr_in_prologue or
  1100. ((cs_opt_size in current_settings.optimizerswitches) and
  1101. ((fprcount > 0) or
  1102. (gprcount > 0))));
  1103. a_reg_alloc(list, NR_STACK_POINTER_REG);
  1104. a_reg_alloc(list, NR_R0);
  1105. { move link register to r0 }
  1106. if (needslinkreg) then
  1107. list.concat(taicpu.op_reg(A_MFLR, NR_R0));
  1108. save_standard_registers;
  1109. { save old stack frame pointer }
  1110. if (tcpuprocinfo(current_procinfo).needs_frame_pointer) then
  1111. list.concat(taicpu.op_reg_reg(A_MR, NR_OLD_STACK_POINTER_REG, NR_STACK_POINTER_REG));
  1112. { create stack frame }
  1113. if (not nostackframe) and (localsize > 0) and
  1114. tcpuprocinfo(current_procinfo).needstackframe then begin
  1115. if (localsize <= high(smallint)) then begin
  1116. reference_reset_base(href, NR_STACK_POINTER_REG, -localsize, ctempposinvalid, 8, []);
  1117. a_load_store(list, A_STDU, NR_STACK_POINTER_REG, href);
  1118. end else begin
  1119. reference_reset_base(href, NR_NO, -localsize, ctempposinvalid, 8, []);
  1120. { Use R0 for loading the constant (which is definitely > 32k when entering
  1121. this branch).
  1122. Inlined at this position because it must not use temp registers because
  1123. register allocations have already been done }
  1124. { Code template:
  1125. lis r0,ofs@highest
  1126. ori r0,r0,ofs@higher
  1127. sldi r0,r0,32
  1128. oris r0,r0,ofs@h
  1129. ori r0,r0,ofs@l
  1130. }
  1131. list.concat(taicpu.op_reg_const(A_LIS, NR_R0, word(href.offset shr 48)));
  1132. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset shr 32)));
  1133. list.concat(taicpu.op_reg_reg_const(A_SLDI, NR_R0, NR_R0, 32));
  1134. list.concat(taicpu.op_reg_reg_const(A_ORIS, NR_R0, NR_R0, word(href.offset shr 16)));
  1135. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset)));
  1136. list.concat(taicpu.op_reg_reg_reg(A_STDUX, NR_R1, NR_R1, NR_R0));
  1137. end;
  1138. end;
  1139. { save current RTOC for restoration after calls if necessary }
  1140. if pi_do_call in current_procinfo.flags then
  1141. begin
  1142. reference_reset_base(href,NR_STACK_POINTER_REG,get_rtoc_offset,ctempposinvalid,target_info.stackalign,[]);
  1143. a_load_reg_ref(list,OS_ADDR,OS_ADDR,NR_RTOC,href);
  1144. end;
  1145. { CR register not used by FPC atm }
  1146. { keep R1 allocated??? }
  1147. a_reg_dealloc(list, NR_R0);
  1148. end;
  1149. { Generates the exit code for a method.
  1150. This procedure may be called before, as well as after g_stackframe_entry
  1151. is called.
  1152. IMPORTANT: registers are not to be allocated through the register
  1153. allocator here, because the register colouring has already occurred !!
  1154. }
  1155. procedure tcgppc.g_proc_exit(list: TAsmList; parasize: longint; nostackframe:
  1156. boolean);
  1157. var
  1158. firstregfpu, firstreggpr: TSuperRegister;
  1159. needslinkreg : boolean;
  1160. fprcount, gprcount: aint;
  1161. { Restore standard registers, both FPR and GPR; does not support VMX/Altivec }
  1162. procedure restore_standard_registers;
  1163. var
  1164. { flag indicating whether we need to manually add the exit code (e.g. blr instruction)
  1165. or not }
  1166. needsExitCode : Boolean;
  1167. href : treference;
  1168. regcount : TSuperRegister;
  1169. callopc,
  1170. jmpopc: tasmop;
  1171. begin
  1172. { there are two ways to do this: manually, by generating a few "ld" instructions,
  1173. or via the restore helper functions. The latter are selected by the -Og switch,
  1174. i.e. "optimize for size" }
  1175. if (cs_opt_size in current_settings.optimizerswitches) then begin
  1176. if target_info.system=system_powerpc64_aix then begin
  1177. callopc:=A_BLA;
  1178. jmpopc:=A_BA;
  1179. end
  1180. else begin
  1181. callopc:=A_BL;
  1182. jmpopc:=A_B;
  1183. end;
  1184. needsExitCode := false;
  1185. if ((fprcount > 0) and (gprcount > 0)) then begin
  1186. a_op_const_reg_reg(list, OP_SUB, OS_INT, 8 * fprcount, NR_R1, NR_R12);
  1187. a_call_name_direct(list, callopc, '_restgpr1_' + intToStr(32-gprcount), false, false, false, false);
  1188. a_jmp_name_direct(list, jmpopc, '_restfpr_' + intToStr(32-fprcount), false);
  1189. end else if (gprcount > 0) then
  1190. a_jmp_name_direct(list, jmpopc, '_restgpr0_' + intToStr(32-gprcount), false)
  1191. else if (fprcount > 0) then
  1192. a_jmp_name_direct(list, jmpopc, '_restfpr_' + intToStr(32-fprcount), false)
  1193. else
  1194. needsExitCode := true;
  1195. end else begin
  1196. needsExitCode := true;
  1197. { restore registers, FPU first, GPR next }
  1198. reference_reset_base(href, NR_STACK_POINTER_REG, -tcgsize2size[OS_FLOAT], ctempposinvalid, 8, []);
  1199. if (fprcount > 0) then
  1200. for regcount := RS_F31 downto firstregfpu do begin
  1201. a_loadfpu_ref_reg(list, OS_FLOAT, OS_FLOAT, href, newreg(R_FPUREGISTER, regcount,
  1202. R_SUBNONE));
  1203. dec(href.offset, tcgsize2size[OS_FLOAT]);
  1204. end;
  1205. if (gprcount > 0) then
  1206. for regcount := RS_R31 downto firstreggpr do begin
  1207. a_load_ref_reg(list, OS_INT, OS_INT, href, newreg(R_INTREGISTER, regcount,
  1208. R_SUBNONE));
  1209. dec(href.offset, sizeof(pint));
  1210. end;
  1211. { VMX not supported by FPC atm }
  1212. end;
  1213. if (needsExitCode) then begin
  1214. { restore LR (if needed) }
  1215. if (needslinkreg) then begin
  1216. reference_reset_base(href, NR_STACK_POINTER_REG, LA_LR_SYSV, ctempposinvalid, 8, []);
  1217. list.concat(taicpu.op_reg_ref(A_LD, NR_R0, href));
  1218. list.concat(taicpu.op_reg(A_MTLR, NR_R0));
  1219. end;
  1220. { generate return instruction }
  1221. list.concat(taicpu.op_none(A_BLR));
  1222. end;
  1223. end;
  1224. var
  1225. href: treference;
  1226. localsize : aint;
  1227. begin
  1228. calcFirstUsedFPR(firstregfpu, fprcount);
  1229. calcFirstUsedGPR(firstreggpr, gprcount);
  1230. { determine whether we need to restore the link register }
  1231. needslinkreg :=
  1232. not(nostackframe) and
  1233. (((not (po_assembler in current_procinfo.procdef.procoptions)) and
  1234. ((pi_do_call in current_procinfo.flags) or (cs_profile in init_settings.moduleswitches))) or
  1235. ((cs_opt_size in current_settings.optimizerswitches) and ((fprcount > 0) or (gprcount > 0))) or
  1236. ([cs_lineinfo, cs_debuginfo] * current_settings.moduleswitches <> []));
  1237. { calculate stack frame }
  1238. localsize := tcpuprocinfo(current_procinfo).calc_stackframe_size(
  1239. gprcount, fprcount);
  1240. { CR register not supported }
  1241. { restore stack pointer }
  1242. if (not nostackframe) and (localsize > 0) and
  1243. tcpuprocinfo(current_procinfo).needstackframe then begin
  1244. if (localsize <= high(smallint)) then begin
  1245. list.concat(taicpu.op_reg_reg_const(A_ADDI, NR_STACK_POINTER_REG, NR_STACK_POINTER_REG, localsize));
  1246. end else begin
  1247. reference_reset_base(href, NR_NO, localsize, ctempposinvalid, 8, []);
  1248. { use R0 for loading the constant (which is definitely > 32k when entering
  1249. this branch)
  1250. Inlined because it must not use temp registers because register allocations
  1251. have already been done
  1252. }
  1253. { Code template:
  1254. lis r0,ofs@highest
  1255. ori r0,ofs@higher
  1256. sldi r0,r0,32
  1257. oris r0,r0,ofs@h
  1258. ori r0,r0,ofs@l
  1259. }
  1260. list.concat(taicpu.op_reg_const(A_LIS, NR_R0, word(href.offset shr 48)));
  1261. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset shr 32)));
  1262. list.concat(taicpu.op_reg_reg_const(A_SLDI, NR_R0, NR_R0, 32));
  1263. list.concat(taicpu.op_reg_reg_const(A_ORIS, NR_R0, NR_R0, word(href.offset shr 16)));
  1264. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset)));
  1265. list.concat(taicpu.op_reg_reg_reg(A_ADD, NR_R1, NR_R1, NR_R0));
  1266. end;
  1267. end;
  1268. restore_standard_registers;
  1269. end;
  1270. procedure tcgppc.a_loadaddr_ref_reg(list: TAsmList; const ref: treference; r:
  1271. tregister);
  1272. var
  1273. ref2, tmpref: treference;
  1274. { register used to construct address }
  1275. tempreg : TRegister;
  1276. begin
  1277. if (target_info.system in [system_powerpc64_darwin,system_powerpc64_aix]) then
  1278. begin
  1279. inherited a_loadaddr_ref_reg(list,ref,r);
  1280. exit;
  1281. end;
  1282. ref2 := ref;
  1283. fixref(list, ref2);
  1284. { load a symbol }
  1285. if (assigned(ref2.symbol) or (hasLargeOffset(ref2))) then begin
  1286. { add the symbol's value to the base of the reference, and if the }
  1287. { reference doesn't have a base, create one }
  1288. reference_reset(tmpref, ref2.alignment, ref2.volatility);
  1289. tmpref.offset := ref2.offset;
  1290. tmpref.symbol := ref2.symbol;
  1291. tmpref.relsymbol := ref2.relsymbol;
  1292. { load 64 bit reference into r. If the reference already has a base register,
  1293. first load the 64 bit value into a temp register, then add it to the result
  1294. register rD }
  1295. if (ref2.base <> NR_NO) then begin
  1296. { already have a base register, so allocate a new one }
  1297. tempreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1298. end else begin
  1299. tempreg := r;
  1300. end;
  1301. { code for loading a reference from a symbol into a register rD }
  1302. (*
  1303. lis rX,SYM@highest
  1304. ori rX,SYM@higher
  1305. sldi rX,rX,32
  1306. oris rX,rX,SYM@h
  1307. ori rX,rX,SYM@l
  1308. *)
  1309. {$IFDEF EXTDEBUG}
  1310. list.concat(tai_comment.create(strpnew('loadaddr_ref_reg ')));
  1311. {$ENDIF EXTDEBUG}
  1312. if (assigned(tmpref.symbol)) then begin
  1313. tmpref.refaddr := addr_highest;
  1314. list.concat(taicpu.op_reg_ref(A_LIS, tempreg, tmpref));
  1315. tmpref.refaddr := addr_higher;
  1316. list.concat(taicpu.op_reg_reg_ref(A_ORI, tempreg, tempreg, tmpref));
  1317. list.concat(taicpu.op_reg_reg_const(A_SLDI, tempreg, tempreg, 32));
  1318. tmpref.refaddr := addr_high;
  1319. list.concat(taicpu.op_reg_reg_ref(A_ORIS, tempreg, tempreg, tmpref));
  1320. tmpref.refaddr := addr_low;
  1321. list.concat(taicpu.op_reg_reg_ref(A_ORI, tempreg, tempreg, tmpref));
  1322. end else
  1323. a_load_const_reg(list, OS_ADDR, tmpref.offset, tempreg);
  1324. { if there's already a base register, add the temp register contents to
  1325. the base register }
  1326. if (ref2.base <> NR_NO) then begin
  1327. list.concat(taicpu.op_reg_reg_reg(A_ADD, r, tempreg, ref2.base));
  1328. end;
  1329. end else if (ref2.offset <> 0) then begin
  1330. { no symbol, but offset <> 0 }
  1331. if (ref2.base <> NR_NO) then begin
  1332. a_op_const_reg_reg(list, OP_ADD, OS_64, ref2.offset, ref2.base, r)
  1333. { FixRef makes sure that "(ref.index <> R_NO) and (ref.offset <> 0)" never
  1334. occurs, so now only ref.offset has to be loaded }
  1335. end else begin
  1336. a_load_const_reg(list, OS_64, ref2.offset, r);
  1337. end;
  1338. end else if (ref2.index <> NR_NO) then begin
  1339. list.concat(taicpu.op_reg_reg_reg(A_ADD, r, ref2.base, ref2.index))
  1340. end else if (ref2.base <> NR_NO) and
  1341. (r <> ref2.base) then begin
  1342. a_load_reg_reg(list, OS_ADDR, OS_ADDR, ref2.base, r)
  1343. end else begin
  1344. list.concat(taicpu.op_reg_const(A_LI, r, 0));
  1345. end;
  1346. end;
  1347. { ************* concatcopy ************ }
  1348. procedure tcgppc.g_concatcopy(list: TAsmList; const source, dest: treference;
  1349. len: aint);
  1350. var
  1351. countreg, tempreg:TRegister;
  1352. src, dst: TReference;
  1353. lab: tasmlabel;
  1354. count, count2, step: longint;
  1355. size: tcgsize;
  1356. begin
  1357. {$IFDEF extdebug}
  1358. list.concat(tai_comment.create(strpnew('g_concatcopy1 ' + inttostr(len) + ' bytes left ')));
  1359. {$ENDIF extdebug}
  1360. { if the references are equal, exit, there is no need to copy anything }
  1361. if references_equal(source, dest) or
  1362. (len=0) then
  1363. exit;
  1364. { make sure short loads are handled as optimally as possible;
  1365. note that the data here never overlaps, so we can do a forward
  1366. copy at all times.
  1367. NOTE: maybe use some scratch registers to pair load/store instructions
  1368. }
  1369. if (len <= 8) then begin
  1370. src := source; dst := dest;
  1371. {$IFDEF extdebug}
  1372. list.concat(tai_comment.create(strpnew('g_concatcopy3 ' + inttostr(src.offset) + ' ' + inttostr(dst.offset))));
  1373. {$ENDIF extdebug}
  1374. while (len <> 0) do begin
  1375. if (len = 8) then begin
  1376. a_load_ref_ref(list, OS_64, OS_64, src, dst);
  1377. dec(len, 8);
  1378. end else if (len >= 4) then begin
  1379. a_load_ref_ref(list, OS_32, OS_32, src, dst);
  1380. inc(src.offset, 4); inc(dst.offset, 4);
  1381. dec(len, 4);
  1382. end else if (len >= 2) then begin
  1383. a_load_ref_ref(list, OS_16, OS_16, src, dst);
  1384. inc(src.offset, 2); inc(dst.offset, 2);
  1385. dec(len, 2);
  1386. end else begin
  1387. a_load_ref_ref(list, OS_8, OS_8, src, dst);
  1388. inc(src.offset, 1); inc(dst.offset, 1);
  1389. dec(len, 1);
  1390. end;
  1391. end;
  1392. exit;
  1393. end;
  1394. {$IFDEF extdebug}
  1395. list.concat(tai_comment.create(strpnew('g_concatcopy2 ' + inttostr(len) + ' bytes left ')));
  1396. {$ENDIF extdebug}
  1397. if not(source.alignment in [1,2]) and
  1398. not(dest.alignment in [1,2]) then
  1399. begin
  1400. count:=len div 8;
  1401. step:=8;
  1402. size:=OS_64;
  1403. end
  1404. else
  1405. begin
  1406. count:=len div 4;
  1407. step:=4;
  1408. size:=OS_32;
  1409. end;
  1410. tempreg:=getintregister(list,size);
  1411. reference_reset(src,source.alignment,source.volatility);
  1412. reference_reset(dst,dest.alignment,dest.volatility);
  1413. { load the address of source into src.base }
  1414. if (count > 4) or
  1415. not issimpleref(source) or
  1416. ((source.index <> NR_NO) and
  1417. ((source.offset + len) > high(smallint))) then begin
  1418. src.base := getaddressregister(list);
  1419. a_loadaddr_ref_reg(list, source, src.base);
  1420. end else begin
  1421. src := source;
  1422. end;
  1423. { load the address of dest into dst.base }
  1424. if (count > 4) or
  1425. not issimpleref(dest) or
  1426. ((dest.index <> NR_NO) and
  1427. ((dest.offset + len) > high(smallint))) then begin
  1428. dst.base := getaddressregister(list);
  1429. a_loadaddr_ref_reg(list, dest, dst.base);
  1430. end else begin
  1431. dst := dest;
  1432. end;
  1433. { generate a loop }
  1434. if count > 4 then begin
  1435. { the offsets are zero after the a_loadaddress_ref_reg and just
  1436. have to be set to step. I put an Inc there so debugging may be
  1437. easier (should offset be different from zero here, it will be
  1438. easy to notice in the generated assembler }
  1439. inc(dst.offset, step);
  1440. inc(src.offset, step);
  1441. list.concat(taicpu.op_reg_reg_const(A_SUBI, src.base, src.base, step));
  1442. list.concat(taicpu.op_reg_reg_const(A_SUBI, dst.base, dst.base, step));
  1443. countreg := getintregister(list, OS_INT);
  1444. a_load_const_reg(list, OS_INT, count, countreg);
  1445. current_asmdata.getjumplabel(lab);
  1446. a_label(list, lab);
  1447. list.concat(taicpu.op_reg_reg_const(A_SUBIC_, countreg, countreg, 1));
  1448. if (size=OS_64) then
  1449. begin
  1450. list.concat(taicpu.op_reg_ref(A_LDU, tempreg, src));
  1451. list.concat(taicpu.op_reg_ref(A_STDU, tempreg, dst));
  1452. end
  1453. else
  1454. begin
  1455. list.concat(taicpu.op_reg_ref(A_LWZU, tempreg, src));
  1456. list.concat(taicpu.op_reg_ref(A_STWU, tempreg, dst));
  1457. end;
  1458. a_jmp(list, A_BC, C_NE, 0, lab);
  1459. a_reg_sync(list,src.base);
  1460. a_reg_sync(list,dst.base);
  1461. a_reg_sync(list,countreg);
  1462. len := len mod step;
  1463. count := 0;
  1464. end;
  1465. { unrolled loop }
  1466. if count > 0 then begin
  1467. for count2 := 1 to count do begin
  1468. a_load_ref_reg(list, size, size, src, tempreg);
  1469. a_load_reg_ref(list, size, size, tempreg, dst);
  1470. inc(src.offset, step);
  1471. inc(dst.offset, step);
  1472. end;
  1473. len := len mod step;
  1474. end;
  1475. if (len and 4) <> 0 then begin
  1476. a_load_ref_reg(list, OS_32, OS_32, src, tempreg);
  1477. a_load_reg_ref(list, OS_32, OS_32, tempreg, dst);
  1478. inc(src.offset, 4);
  1479. inc(dst.offset, 4);
  1480. end;
  1481. { copy the leftovers }
  1482. if (len and 2) <> 0 then begin
  1483. a_load_ref_reg(list, OS_16, OS_16, src, tempreg);
  1484. a_load_reg_ref(list, OS_16, OS_16, tempreg, dst);
  1485. inc(src.offset, 2);
  1486. inc(dst.offset, 2);
  1487. end;
  1488. if (len and 1) <> 0 then begin
  1489. a_load_ref_reg(list, OS_8, OS_8, src, tempreg);
  1490. a_load_reg_ref(list, OS_8, OS_8, tempreg, dst);
  1491. end;
  1492. end;
  1493. {***************** This is private property, keep out! :) *****************}
  1494. procedure tcgppc.maybeadjustresult(list: TAsmList; op: TOpCg; size: tcgsize; dst: tregister);
  1495. const
  1496. overflowops = [OP_MUL,OP_SHL,OP_ADD,OP_SUB,OP_NOT,OP_NEG];
  1497. begin
  1498. {$IFDEF EXTDEBUG}
  1499. list.concat(tai_comment.create(strpnew('maybeadjustresult op = ' + cgop2string(op) + ' size = ' + tcgsize2str(size))));
  1500. {$ENDIF EXTDEBUG}
  1501. if (op in overflowops) and (size in [OS_8, OS_S8, OS_16, OS_S16, OS_32, OS_S32]) then
  1502. a_load_reg_reg(list, OS_64, size, dst, dst);
  1503. end;
  1504. function tcgppc.issimpleref(const ref: treference): boolean;
  1505. begin
  1506. if (ref.base = NR_NO) and
  1507. (ref.index <> NR_NO) then
  1508. internalerror(200208101);
  1509. result :=
  1510. not (assigned(ref.symbol)) and
  1511. (((ref.index = NR_NO) and
  1512. (ref.offset >= low(smallint)) and
  1513. (ref.offset <= high(smallint))) or
  1514. ((ref.index <> NR_NO) and
  1515. (ref.offset = 0)));
  1516. end;
  1517. procedure tcgppc.a_load_store(list: TAsmList; op: tasmop; reg: tregister;
  1518. ref: treference);
  1519. procedure maybefixup64bitoffset;
  1520. var
  1521. tmpreg: tregister;
  1522. begin
  1523. { for some instructions we need to check that the offset is divisible by at
  1524. least four. If not, add the bytes which are "off" to the base register and
  1525. adjust the offset accordingly }
  1526. case op of
  1527. A_LD, A_LDU, A_STD, A_STDU, A_LWA :
  1528. if ((ref.offset mod 4) <> 0) then begin
  1529. tmpreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1530. if (ref.base <> NR_NO) then begin
  1531. a_op_const_reg_reg(list, OP_ADD, OS_ADDR, ref.offset mod 4, ref.base, tmpreg);
  1532. ref.base := tmpreg;
  1533. end else begin
  1534. list.concat(taicpu.op_reg_const(A_LI, tmpreg, ref.offset mod 4));
  1535. ref.base := tmpreg;
  1536. end;
  1537. ref.offset := (ref.offset div 4) * 4;
  1538. end;
  1539. else
  1540. ;
  1541. end;
  1542. end;
  1543. var
  1544. tmpreg, tmpreg2: tregister;
  1545. tmpref: treference;
  1546. largeOffset: Boolean;
  1547. begin
  1548. if (target_info.system = system_powerpc64_darwin) then
  1549. begin
  1550. { darwin/ppc64 works with 32 bit relocatable symbol addresses }
  1551. maybefixup64bitoffset;
  1552. inherited a_load_store(list,op,reg,ref);
  1553. exit
  1554. end;
  1555. { at this point there must not be a combination of values in the ref treference
  1556. which is not possible to directly map to instructions of the PowerPC architecture }
  1557. if (ref.index <> NR_NO) and ((ref.offset <> 0) or (assigned(ref.symbol))) then
  1558. internalerror(200310131);
  1559. { if this is a PIC'ed address, handle it and exit }
  1560. if (ref.refaddr in [addr_pic,addr_pic_no_got]) then begin
  1561. if (ref.offset <> 0) then
  1562. internalerror(2006010501);
  1563. if (ref.index <> NR_NO) then
  1564. internalerror(2006010502);
  1565. if (not assigned(ref.symbol)) then
  1566. internalerror(200601050);
  1567. list.concat(taicpu.op_reg_ref(op, reg, ref));
  1568. exit;
  1569. end;
  1570. maybefixup64bitoffset;
  1571. {$IFDEF EXTDEBUG}
  1572. list.concat(tai_comment.create(strpnew('a_load_store1 ' + BoolToStr(ref.refaddr = addr_pic))));
  1573. {$ENDIF EXTDEBUG}
  1574. { if we have to load/store from a symbol or large addresses, use a temporary register
  1575. containing the address }
  1576. if (assigned(ref.symbol) or (hasLargeOffset(ref))) then begin
  1577. tmpreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1578. if (hasLargeOffset(ref) and (ref.base = NR_NO)) then begin
  1579. ref.base := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1580. a_load_const_reg(list, OS_ADDR, ref.offset, ref.base);
  1581. ref.offset := 0;
  1582. end;
  1583. reference_reset(tmpref, ref.alignment, ref.volatility);
  1584. tmpref.symbol := ref.symbol;
  1585. tmpref.relsymbol := ref.relsymbol;
  1586. tmpref.offset := ref.offset;
  1587. if (ref.base <> NR_NO) then begin
  1588. { As long as the TOC isn't working we try to achieve highest speed (in this
  1589. case by allowing instructions execute in parallel) as possible at the cost
  1590. of using another temporary register. So the code template when there is
  1591. a base register and an offset is the following:
  1592. lis rT1, SYM+offs@highest
  1593. ori rT1, rT1, SYM+offs@higher
  1594. lis rT2, SYM+offs@hi
  1595. ori rT2, SYM+offs@lo
  1596. rldimi rT2, rT1, 32
  1597. <op>X reg, base, rT2
  1598. }
  1599. tmpreg2 := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1600. if (assigned(tmpref.symbol)) then begin
  1601. tmpref.refaddr := addr_highest;
  1602. list.concat(taicpu.op_reg_ref(A_LIS, tmpreg, tmpref));
  1603. tmpref.refaddr := addr_higher;
  1604. list.concat(taicpu.op_reg_reg_ref(A_ORI, tmpreg, tmpreg, tmpref));
  1605. tmpref.refaddr := addr_high;
  1606. list.concat(taicpu.op_reg_ref(A_LIS, tmpreg2, tmpref));
  1607. tmpref.refaddr := addr_low;
  1608. list.concat(taicpu.op_reg_reg_ref(A_ORI, tmpreg2, tmpreg2, tmpref));
  1609. list.concat(taicpu.op_reg_reg_const_const(A_RLDIMI, tmpreg2, tmpreg, 32, 0));
  1610. end else
  1611. a_load_const_reg(list, OS_ADDR, tmpref.offset, tmpreg2);
  1612. reference_reset(tmpref, ref.alignment, ref.volatility);
  1613. tmpref.base := ref.base;
  1614. tmpref.index := tmpreg2;
  1615. case op of
  1616. { the code generator doesn't generate update instructions anyway, so
  1617. error out on those instructions }
  1618. A_LBZ : op := A_LBZX;
  1619. A_LHZ : op := A_LHZX;
  1620. A_LWZ : op := A_LWZX;
  1621. A_LD : op := A_LDX;
  1622. A_LHA : op := A_LHAX;
  1623. A_LWA : op := A_LWAX;
  1624. A_LFS : op := A_LFSX;
  1625. A_LFD : op := A_LFDX;
  1626. A_STB : op := A_STBX;
  1627. A_STH : op := A_STHX;
  1628. A_STW : op := A_STWX;
  1629. A_STD : op := A_STDX;
  1630. A_STFS : op := A_STFSX;
  1631. A_STFD : op := A_STFDX;
  1632. else
  1633. { unknown load/store opcode }
  1634. internalerror(2005101302);
  1635. end;
  1636. list.concat(taicpu.op_reg_ref(op, reg, tmpref));
  1637. end else begin
  1638. { when accessing value from a reference without a base register, use the
  1639. following code template:
  1640. lis rT,SYM+offs@highesta
  1641. ori rT,SYM+offs@highera
  1642. sldi rT,rT,32
  1643. oris rT,rT,SYM+offs@ha
  1644. ld rD,SYM+offs@l(rT)
  1645. }
  1646. tmpref.refaddr := addr_highesta;
  1647. list.concat(taicpu.op_reg_ref(A_LIS, tmpreg, tmpref));
  1648. tmpref.refaddr := addr_highera;
  1649. list.concat(taicpu.op_reg_reg_ref(A_ORI, tmpreg, tmpreg, tmpref));
  1650. list.concat(taicpu.op_reg_reg_const(A_SLDI, tmpreg, tmpreg, 32));
  1651. tmpref.refaddr := addr_higha;
  1652. list.concat(taicpu.op_reg_reg_ref(A_ORIS, tmpreg, tmpreg, tmpref));
  1653. tmpref.base := tmpreg;
  1654. tmpref.refaddr := addr_low;
  1655. list.concat(taicpu.op_reg_ref(op, reg, tmpref));
  1656. end;
  1657. end else begin
  1658. list.concat(taicpu.op_reg_ref(op, reg, ref));
  1659. end;
  1660. end;
  1661. procedure tcgppc.loadConstantPIC(list : TAsmList; size : TCGSize; a : aint; reg : TRegister);
  1662. var
  1663. l: tasmsymbol;
  1664. ref: treference;
  1665. symname : string;
  1666. begin
  1667. maybe_new_object_file(current_asmdata.asmlists[al_picdata]);
  1668. symname := '_$' + current_asmdata.name^ + '$toc$' + hexstr(a, sizeof(a)*2);
  1669. l:=current_asmdata.getasmsymbol(symname);
  1670. if not(assigned(l)) then begin
  1671. l:=current_asmdata.DefineAsmSymbol(symname,AB_GLOBAL, AT_METADATA, voidpointertype);
  1672. new_section(current_asmdata.asmlists[al_picdata],sec_toc, '.toc', 8);
  1673. current_asmdata.asmlists[al_picdata].concat(tai_symbol.create_global(l,0));
  1674. current_asmdata.asmlists[al_picdata].concat(tai_directive.create(asd_toc_entry, symname + '[TC], ' + inttostr(a)));
  1675. end;
  1676. reference_reset_symbol(ref,l,0,8,[]);
  1677. ref.base := NR_R2;
  1678. ref.refaddr := addr_no;
  1679. {$IFDEF EXTDEBUG}
  1680. list.concat(tai_comment.create(strpnew('loading value from TOC reference for ' + symname)));
  1681. {$ENDIF EXTDEBUG}
  1682. a_load_ref_reg(list, OS_INT, OS_INT, ref, reg);
  1683. end;
  1684. procedure create_codegen;
  1685. begin
  1686. cg := tcgppc.create;
  1687. cg128:=tcg128.create;
  1688. end;
  1689. end.