2
0

cgcpu.pas 56 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668
  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,
  22. cgbase, cgobj,
  23. aasmbase, aasmcpu, aasmtai,
  24. cpubase, cpuinfo, cgutils, rgcpu,
  25. parabase;
  26. type
  27. tcgppc = class(tcg)
  28. procedure init_register_allocators; override;
  29. procedure done_register_allocators; override;
  30. { passing parameters, per default the parameter is pushed }
  31. { nr gives the number of the parameter (enumerated from }
  32. { left to right), this allows to move the parameter to }
  33. { register, if the cpu supports register calling }
  34. { conventions }
  35. procedure a_param_const(list: taasmoutput; size: tcgsize; a: aint; const
  36. paraloc: tcgpara); override;
  37. procedure a_param_ref(list: taasmoutput; size: tcgsize; const r: treference;
  38. const paraloc: tcgpara); override;
  39. procedure a_paramaddr_ref(list: taasmoutput; const r: treference; const
  40. paraloc: tcgpara); override;
  41. procedure a_call_name(list: taasmoutput; const s: string); override;
  42. procedure a_call_name_direct(list: taasmoutput; s: string; prependDot : boolean);
  43. procedure a_call_reg(list: taasmoutput; reg: tregister); override;
  44. procedure a_op_const_reg(list: taasmoutput; Op: TOpCG; size: TCGSize; a:
  45. aint; reg: TRegister); override;
  46. procedure a_op_reg_reg(list: taasmoutput; Op: TOpCG; size: TCGSize; src,
  47. dst: TRegister); override;
  48. procedure a_op_const_reg_reg(list: taasmoutput; op: TOpCg;
  49. size: tcgsize; a: aint; src, dst: tregister); override;
  50. procedure a_op_reg_reg_reg(list: taasmoutput; op: TOpCg;
  51. size: tcgsize; src1, src2, dst: tregister); override;
  52. { move instructions }
  53. procedure a_load_const_reg(list: taasmoutput; size: tcgsize; a: aint; reg:
  54. tregister); override;
  55. procedure a_load_reg_ref(list: taasmoutput; fromsize, tosize: tcgsize; reg:
  56. tregister; const ref: treference); override;
  57. procedure a_load_ref_reg(list: taasmoutput; fromsize, tosize: tcgsize; const
  58. Ref: treference; reg: tregister); override;
  59. procedure a_load_reg_reg(list: taasmoutput; fromsize, tosize: tcgsize; reg1,
  60. reg2: tregister); override;
  61. { fpu move instructions }
  62. procedure a_loadfpu_reg_reg(list: taasmoutput; size: tcgsize; reg1, reg2:
  63. tregister); override;
  64. procedure a_loadfpu_ref_reg(list: taasmoutput; size: tcgsize; const ref:
  65. treference; reg: tregister); override;
  66. procedure a_loadfpu_reg_ref(list: taasmoutput; size: tcgsize; reg:
  67. tregister; const ref: treference); override;
  68. { comparison operations }
  69. procedure a_cmp_const_reg_label(list: taasmoutput; size: tcgsize; cmp_op:
  70. topcmp; a: aint; reg: tregister;
  71. l: tasmlabel); override;
  72. procedure a_cmp_reg_reg_label(list: taasmoutput; size: tcgsize; cmp_op:
  73. topcmp; reg1, reg2: tregister; l: tasmlabel); override;
  74. procedure a_jmp_name(list: taasmoutput; const s: string); override;
  75. procedure a_jmp_always(list: taasmoutput; l: tasmlabel); override;
  76. procedure a_jmp_flags(list: taasmoutput; const f: TResFlags; l: tasmlabel);
  77. override;
  78. procedure g_flags2reg(list: taasmoutput; size: TCgSize; const f: TResFlags;
  79. reg: TRegister); override;
  80. procedure g_proc_entry(list: taasmoutput; localsize: longint; nostackframe:
  81. boolean); override;
  82. procedure g_proc_exit(list: taasmoutput; parasize: longint; nostackframe:
  83. boolean); override;
  84. procedure g_save_standard_registers(list: Taasmoutput); override;
  85. procedure g_restore_standard_registers(list: Taasmoutput); override;
  86. procedure a_loadaddr_ref_reg(list: taasmoutput; const ref: treference; r:
  87. tregister); override;
  88. procedure g_concatcopy(list: taasmoutput; const source, dest: treference;
  89. len: aint); override;
  90. procedure g_overflowcheck(list: taasmoutput; const l: tlocation; def: tdef);
  91. override;
  92. procedure a_jmp_cond(list: taasmoutput; cond: TOpCmp; l: tasmlabel);
  93. procedure g_intf_wrapper(list: TAAsmoutput; procdef: tprocdef; const
  94. labelname: string; ioffset: longint); override;
  95. private
  96. { Make sure ref is a valid reference for the PowerPC and sets the }
  97. { base to the value of the index if (base = R_NO). }
  98. { Returns true if the reference contained a base, index and an }
  99. { offset or symbol, in which case the base will have been changed }
  100. { to a tempreg (which has to be freed by the caller) containing }
  101. { the sum of part of the original reference }
  102. function fixref(list: taasmoutput; var ref: treference; const size : TCgsize): boolean;
  103. { returns whether a reference can be used immediately in a powerpc }
  104. { instruction }
  105. function issimpleref(const ref: treference): boolean;
  106. { contains the common code of a_load_reg_ref and a_load_ref_reg }
  107. procedure a_load_store(list: taasmoutput; op: tasmop; reg: tregister;
  108. ref: treference);
  109. { creates the correct branch instruction for a given combination }
  110. { of asmcondflags and destination addressing mode }
  111. procedure a_jmp(list: taasmoutput; op: tasmop;
  112. c: tasmcondflag; crval: longint; l: tasmlabel);
  113. { returns the lowest numbered FP register in use, and the number of used FP registers
  114. for the current procedure }
  115. procedure calcFirstUsedFPR(out firstfpr : TSuperRegister; out fprcount : aint);
  116. { returns the lowest numbered GP register in use, and the number of used GP registers
  117. for the current procedure }
  118. procedure calcFirstUsedGPR(out firstgpr : TSuperRegister; out gprcount : aint);
  119. { returns true if the offset of the given reference can not be represented by a 16 bit
  120. immediate as required by some PowerPC instructions }
  121. function hasLargeOffset(const ref : TReference) : Boolean; inline;
  122. end;
  123. const
  124. TOpCG2AsmOpConstLo: array[topcg] of TAsmOp = (A_NONE, A_ADDI, A_ANDI_,
  125. A_DIVWU,
  126. A_DIVW, A_MULLW, A_MULLW, A_NONE, A_NONE, A_ORI,
  127. A_SRAWI, A_SLWI, A_SRWI, A_SUBI, A_XORI);
  128. TOpCG2AsmOpConstHi: array[topcg] of TAsmOp = (A_NONE, A_ADDIS, A_ANDIS_,
  129. A_DIVWU, A_DIVW, A_MULLW, A_MULLW, A_NONE, A_NONE,
  130. A_ORIS, A_NONE, A_NONE, A_NONE, A_SUBIS, A_XORIS);
  131. TShiftOpCG2AsmOpConst32 : array[OP_SAR..OP_SHR] of TAsmOp = (A_SRAWI, A_SLWI, A_SRWI);
  132. TShiftOpCG2AsmOpConst64 : array[OP_SAR..OP_SHR] of TAsmOp = (A_SRADI, A_SLDI, A_SRDI);
  133. TOpCmp2AsmCond: array[topcmp] of TAsmCondFlag = (C_NONE, C_EQ, C_GT,
  134. C_LT, C_GE, C_LE, C_NE, C_LE, C_LT, C_GE, C_GT);
  135. implementation
  136. uses
  137. sysutils,
  138. globals, verbose, systems, cutils,
  139. symconst, symsym, fmodule,
  140. rgobj, tgobj, cpupi, procinfo, paramgr;
  141. procedure tcgppc.init_register_allocators;
  142. begin
  143. inherited init_register_allocators;
  144. rg[R_INTREGISTER] := trgcpu.create(R_INTREGISTER, R_SUBWHOLE,
  145. [RS_R3, RS_R4, RS_R5, RS_R6, RS_R7, RS_R8,
  146. RS_R9, RS_R10, RS_R11, RS_R12, RS_R31, RS_R30, RS_R29,
  147. RS_R28, RS_R27, RS_R26, RS_R25, RS_R24, RS_R23, RS_R22,
  148. RS_R21, RS_R20, RS_R19, RS_R18, RS_R17, RS_R16, RS_R15,
  149. RS_R14, RS_R13], first_int_imreg, []);
  150. rg[R_FPUREGISTER] := trgcpu.create(R_FPUREGISTER, R_SUBNONE,
  151. [RS_F0, RS_F1, RS_F2, RS_F3, RS_F4, RS_F5, RS_F6, RS_F7, RS_F8, RS_F9,
  152. RS_F10, RS_F11, RS_F12, RS_F13, RS_F31, RS_F30, RS_F29, RS_F28, RS_F27,
  153. RS_F26, RS_F25, RS_F24, RS_F23, RS_F22, RS_F21, RS_F20, RS_F19, RS_F18,
  154. RS_F17, RS_F16, RS_F15, RS_F14], first_fpu_imreg, []);
  155. {$WARNING FIX ME}
  156. rg[R_MMREGISTER] := trgcpu.create(R_MMREGISTER, R_SUBNONE,
  157. [RS_M0, RS_M1, RS_M2], first_mm_imreg, []);
  158. end;
  159. procedure tcgppc.done_register_allocators;
  160. begin
  161. rg[R_INTREGISTER].free;
  162. rg[R_FPUREGISTER].free;
  163. rg[R_MMREGISTER].free;
  164. inherited done_register_allocators;
  165. end;
  166. procedure tcgppc.a_param_const(list: taasmoutput; size: tcgsize; a: aint; const
  167. paraloc: tcgpara);
  168. var
  169. ref: treference;
  170. begin
  171. paraloc.check_simple_location;
  172. case paraloc.location^.loc of
  173. LOC_REGISTER, LOC_CREGISTER:
  174. a_load_const_reg(list, size, a, paraloc.location^.register);
  175. LOC_REFERENCE:
  176. begin
  177. reference_reset(ref);
  178. ref.base := paraloc.location^.reference.index;
  179. ref.offset := paraloc.location^.reference.offset;
  180. a_load_const_ref(list, size, a, ref);
  181. end;
  182. else
  183. internalerror(2002081101);
  184. end;
  185. end;
  186. procedure tcgppc.a_param_ref(list: taasmoutput; size: tcgsize; const r:
  187. treference; const paraloc: tcgpara);
  188. var
  189. tmpref, ref: treference;
  190. location: pcgparalocation;
  191. sizeleft: aint;
  192. begin
  193. location := paraloc.location;
  194. tmpref := r;
  195. sizeleft := paraloc.intsize;
  196. while assigned(location) do
  197. begin
  198. case location^.loc of
  199. LOC_REGISTER, LOC_CREGISTER:
  200. begin
  201. a_load_ref_reg(list, location^.size, location^.size, tmpref,
  202. location^.register);
  203. end;
  204. LOC_REFERENCE:
  205. begin
  206. reference_reset_base(ref, location^.reference.index,
  207. location^.reference.offset);
  208. g_concatcopy(list, tmpref, ref, sizeleft);
  209. if assigned(location^.next) then
  210. internalerror(2005010710);
  211. end;
  212. LOC_FPUREGISTER, LOC_CFPUREGISTER:
  213. case location^.size of
  214. OS_F32, OS_F64:
  215. a_loadfpu_ref_reg(list, location^.size, tmpref, location^.register);
  216. else
  217. internalerror(2002072801);
  218. end;
  219. LOC_VOID:
  220. begin
  221. // nothing to do
  222. end;
  223. else
  224. internalerror(2002081103);
  225. end;
  226. inc(tmpref.offset, tcgsize2size[location^.size]);
  227. dec(sizeleft, tcgsize2size[location^.size]);
  228. location := location^.next;
  229. end;
  230. end;
  231. procedure tcgppc.a_paramaddr_ref(list: taasmoutput; const r: treference; const
  232. paraloc: tcgpara);
  233. var
  234. ref: treference;
  235. tmpreg: tregister;
  236. begin
  237. paraloc.check_simple_location;
  238. case paraloc.location^.loc of
  239. LOC_REGISTER, LOC_CREGISTER:
  240. a_loadaddr_ref_reg(list, r, paraloc.location^.register);
  241. LOC_REFERENCE:
  242. begin
  243. reference_reset(ref);
  244. ref.base := paraloc.location^.reference.index;
  245. ref.offset := paraloc.location^.reference.offset;
  246. tmpreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  247. a_loadaddr_ref_reg(list, r, tmpreg);
  248. a_load_reg_ref(list, OS_ADDR, OS_ADDR, tmpreg, ref);
  249. end;
  250. else
  251. internalerror(2002080701);
  252. end;
  253. end;
  254. { calling a procedure by name }
  255. procedure tcgppc.a_call_name(list: taasmoutput; const s: string);
  256. begin
  257. a_call_name_direct(list, s, true);
  258. end;
  259. procedure tcgppc.a_call_name_direct(list: taasmoutput; s: string; prependDot : boolean);
  260. begin
  261. if (prependDot) then begin
  262. s := '.' + s;
  263. end;
  264. list.concat(taicpu.op_sym(A_BL, objectlibrary.newasmsymbol(s, AB_EXTERNAL,
  265. AT_FUNCTION)));
  266. list.concat(taicpu.op_none(A_NOP));
  267. {
  268. the compiler does not properly set this flag anymore in pass 1, and
  269. for now we only need it after pass 2 (I hope) (JM)
  270. if not(pi_do_call in current_procinfo.flags) then
  271. internalerror(2003060703);
  272. }
  273. include(current_procinfo.flags, pi_do_call);
  274. end;
  275. { calling a procedure by address }
  276. procedure tcgppc.a_call_reg(list: taasmoutput; reg: tregister);
  277. var
  278. tmpreg: tregister;
  279. tmpref: treference;
  280. gotref : treference;
  281. begin
  282. tmpreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  283. reference_reset(tmpref);
  284. tmpref.offset := 0;
  285. tmpref.base := reg;
  286. list.concat(taicpu.op_reg_ref(A_LD, tmpreg, tmpref));
  287. // TODO: GOT change
  288. // reference_reset(gotref);
  289. // tmpref.offset := 40;
  290. // tmpref.base := rg[R_INTREGISTER].getregister(list, NR_STACK_POINTER_REG);
  291. // taicpu.op_load_reg_ref(list, OS_INT, OS_INT,
  292. list.concat(taicpu.op_reg(A_MTCTR, tmpreg));
  293. list.concat(taicpu.op_none(A_BCTRL));
  294. //if target_info.system=system_powerpc_macos then
  295. // //NOP is not needed here.
  296. // list.concat(taicpu.op_none(A_NOP));
  297. include(current_procinfo.flags, pi_do_call);
  298. end;
  299. {********************** load instructions ********************}
  300. procedure tcgppc.a_load_const_reg(list: taasmoutput; size: TCGSize; a: aint;
  301. reg: TRegister);
  302. { loads a 32 bit constant into the given register, using an optimal instruction sequence.
  303. This is either LIS, LI or LI+ADDIS.
  304. Returns true if during these operations the upper 32 bits were filled with 1 bits (e.g.
  305. sign extension was performed) }
  306. function load32bitconstant(list : taasmoutput; size : TCGSize; a : longint;
  307. reg : TRegister) : boolean;
  308. var
  309. is_half_signed : byte;
  310. begin
  311. { if the lower 16 bits are zero, do a single LIS }
  312. if (smallint(a) = 0) and ((a shr 16) <> 0) then begin
  313. list.concat(taicpu.op_reg_const(A_LIS, reg, smallint(hi(a))));
  314. load32bitconstant := longint(a) < 0;
  315. end else begin
  316. is_half_signed := ord(smallint(lo(a)) < 0);
  317. list.concat(taicpu.op_reg_const(A_LI, reg, smallint(a and $ffff)));
  318. if smallint(hi(a) + is_half_signed) <> 0 then begin
  319. list.concat(taicpu.op_reg_reg_const(A_ADDIS, reg, reg, smallint(hi(a) + is_half_signed)));
  320. end;
  321. load32bitconstant := (smallint(a) < 0) or (a < 0);
  322. end;
  323. end;
  324. { R0-safe version of the above (ADDIS doesn't work the same way with R0 as base), without
  325. the return value }
  326. procedure load32bitconstantR0(list : taasmoutput; size : TCGSize; a : longint;
  327. reg : TRegister);
  328. begin
  329. // only 16 bit constant? (-2^15 <= a <= +2^15-1)
  330. if (a >= low(smallint)) and (a <= high(smallint)) then begin
  331. list.concat(taicpu.op_reg_const(A_LI, reg, smallint(a)));
  332. end else begin
  333. { check if we have to start with LI or LIS, load as 32 bit constant }
  334. if ((a and $FFFF) <> 0) then begin
  335. list.concat(taicpu.op_reg_const(A_LIS, reg, smallint(a shr 16)));
  336. list.concat(taicpu.op_reg_reg_const(A_ORI, reg, reg, word(a)));
  337. end else begin
  338. list.concat(taicpu.op_reg_const(A_LIS, reg, smallint(a shr 16)));
  339. end;
  340. end;
  341. end;
  342. var
  343. extendssign : boolean;
  344. {$IFDEF EXTDEBUG}
  345. astring : string;
  346. {$ENDIF EXTDEBUG}
  347. begin
  348. {$IFDEF EXTDEBUG}
  349. astring := 'a_load_const reg ' + inttostr(hi(a)) + ' ' + inttostr(lo(a)) + ' ' + inttostr(ord(size)) + ' ' + inttostr(tcgsize2size[size]);
  350. list.concat(tai_comment.create(strpnew(astring)));
  351. {$ENDIF EXTDEBUG}
  352. if not (size in [OS_8, OS_S8, OS_16, OS_S16, OS_32, OS_S32, OS_64, OS_S64]) then
  353. internalerror(2002090902);
  354. if (lo(a) = 0) and (hi(a) <> 0) then begin
  355. { load only upper 32 bits, and shift }
  356. load32bitconstant(list, size, hi(a), reg);
  357. list.concat(taicpu.op_reg_reg_const(A_SLDI, reg, reg, 32));
  358. end else begin
  359. { load lower 32 bits }
  360. extendssign := load32bitconstant(list, size, lo(a), reg);
  361. if (extendssign) and (hi(a) = 0) then
  362. { if upper 32 bits are zero, but loading the lower 32 bit resulted in automatic
  363. sign extension, clear those bits }
  364. a_load_reg_reg(list, OS_32, OS_64, reg, reg)
  365. else if (not
  366. ((extendssign and (longint(hi(a)) = -1)) or
  367. ((not extendssign) and (hi(a)=0)))
  368. ) then begin
  369. { only load the upper 32 bits, if the automatic sign extension is not okay,
  370. that is, _not_ if
  371. - loading the lower 32 bits resulted in -1 in the upper 32 bits, and the upper
  372. 32 bits should contain -1
  373. - loading the lower 32 bits resulted in 0 in the upper 32 bits, and the upper
  374. 32 bits should contain 0 }
  375. load32bitconstantR0(list, size, hi(a), NR_R0);
  376. { combine both registers }
  377. list.concat(taicpu.op_reg_reg_const_const(A_RLDIMI, reg, NR_R0, 32, 0));
  378. end;
  379. end;
  380. end;
  381. procedure tcgppc.a_load_reg_ref(list: taasmoutput; fromsize, tosize: TCGSize;
  382. reg: tregister; const ref: treference);
  383. const
  384. StoreInstr: array[OS_8..OS_64, boolean, boolean] of TAsmOp =
  385. { indexed? updating?}
  386. (((A_STB, A_STBU), (A_STBX, A_STBUX)),
  387. ((A_STH, A_STHU), (A_STHX, A_STHUX)),
  388. ((A_STW, A_STWU), (A_STWX, A_STWUX)),
  389. ((A_STD, A_STDU), (A_STDX, A_STDUX))
  390. );
  391. var
  392. op: TAsmOp;
  393. ref2: TReference;
  394. begin
  395. ref2 := ref;
  396. fixref(list, ref2, tosize);
  397. if tosize in [OS_S8..OS_S64] then
  398. { storing is the same for signed and unsigned values }
  399. tosize := tcgsize(ord(tosize) - (ord(OS_S8) - ord(OS_8)));
  400. op := storeinstr[tcgsize2unsigned[tosize], ref2.index <> NR_NO, false];
  401. a_load_store(list, op, reg, ref2);
  402. end;
  403. procedure tcgppc.a_load_ref_reg(list: taasmoutput; fromsize, tosize: tcgsize;
  404. const ref: treference; reg: tregister);
  405. const
  406. LoadInstr: array[OS_8..OS_S64, boolean, boolean] of TAsmOp =
  407. { indexed? updating?}
  408. (((A_LBZ, A_LBZU), (A_LBZX, A_LBZUX)),
  409. ((A_LHZ, A_LHZU), (A_LHZX, A_LHZUX)),
  410. ((A_LWZ, A_LWZU), (A_LWZX, A_LWZUX)),
  411. ((A_LD, A_LDU), (A_LDX, A_LDUX)),
  412. { 128bit stuff too }
  413. ((A_NONE, A_NONE), (A_NONE, A_NONE)),
  414. { there's no load-byte-with-sign-extend :( }
  415. ((A_LBZ, A_LBZU), (A_LBZX, A_LBZUX)),
  416. ((A_LHA, A_LHAU), (A_LHAX, A_LHAUX)),
  417. { there's no load-word-arithmetic-indexed with update, simulate it in code :( }
  418. ((A_LWA, A_LWAU), (A_LWAX, A_LWAUX)),
  419. ((A_LD, A_LDU), (A_LDX, A_LDUX))
  420. );
  421. var
  422. op: tasmop;
  423. ref2: treference;
  424. begin
  425. { TODO: optimize/take into consideration fromsize/tosize. Will }
  426. { probably only matter for OS_S8 loads though }
  427. if not (fromsize in [OS_8, OS_S8, OS_16, OS_S16, OS_32, OS_S32, OS_64, OS_S64]) then
  428. internalerror(2002090902);
  429. ref2 := ref;
  430. fixref(list, ref2, tosize);
  431. { the caller is expected to have adjusted the reference already }
  432. { in this case }
  433. if (TCGSize2Size[fromsize] >= TCGSize2Size[tosize]) then
  434. fromsize := tosize;
  435. op := loadinstr[fromsize, ref2.index <> NR_NO, false];
  436. // there is no LWAU instruction, simulate using ADDI and LWA
  437. if (op = A_LWAU) then begin
  438. list.concat(taicpu.op_reg_reg_const(A_ADDI, reg, reg, ref2.offset));
  439. ref2.offset := 0;
  440. op := A_LWA;
  441. end;
  442. a_load_store(list, op, reg, ref2);
  443. // sign extend shortint if necessary, since there is no
  444. // load instruction that does that automatically (JM)
  445. if fromsize = OS_S8 then
  446. list.concat(taicpu.op_reg_reg(A_EXTSB, reg, reg));
  447. end;
  448. procedure tcgppc.a_load_reg_reg(list: taasmoutput; fromsize, tosize: tcgsize;
  449. reg1, reg2: tregister);
  450. const
  451. movemap : array[OS_8..OS_S128, OS_8..OS_S128] of tasmop = (
  452. { to -> OS_8 OS_16 OS_32 OS_64 OS_128 OS_S8 OS_S16 OS_S32 OS_S64 OS_S128 }
  453. { from }
  454. { OS_8 } (A_MR, A_RLDICL, A_RLDICL, A_RLDICL, A_NONE, A_RLDICL, A_RLDICL, A_RLDICL, A_RLDICL, A_NOP ),
  455. { OS_16 } (A_RLDICL, A_MR, A_RLDICL, A_RLDICL, A_NONE, A_RLDICL, A_RLDICL, A_RLDICL, A_RLDICL, A_NOP ),
  456. { OS_32 } (A_RLDICL, A_RLDICL, A_MR, A_RLDICL, A_NONE, A_RLDICL, A_RLDICL, A_RLDICL, A_RLDICL, A_NOP ),
  457. { OS_64 } (A_RLDICL, A_RLDICL, A_RLDICL, A_MR, A_NONE, A_RLDICL, A_RLDICL, A_RLDICL, A_RLDICL, A_NOP ),
  458. { OS_128 } (A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NOP ),
  459. { OS_S8 } (A_EXTSB, A_EXTSB, A_EXTSB, A_EXTSB, A_NONE, A_MR, A_EXTSB, A_EXTSB, A_EXTSB, A_NOP ),
  460. { OS_S16 } (A_RLDICL, A_EXTSH, A_EXTSH, A_EXTSH, A_NONE, A_EXTSB, A_MR, A_EXTSH, A_EXTSH, A_NOP ),
  461. { OS_S32 } (A_RLDICL, A_RLDICL, A_EXTSW, A_EXTSW, A_NONE, A_EXTSB, A_EXTSH, A_MR, A_EXTSW, A_NOP ),
  462. { OS_S64 } (A_RLDICL, A_RLDICL, A_RLDICL, A_MR, A_NONE, A_EXTSB, A_EXTSH, A_EXTSW, A_MR, A_NOP ),
  463. { OS_S128 } (A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NONE, A_NOP )
  464. );
  465. var
  466. instr: taicpu;
  467. op : tasmop;
  468. begin
  469. op := movemap[fromsize, tosize];
  470. case op of
  471. A_MR, A_EXTSB, A_EXTSH, A_EXTSW : instr := taicpu.op_reg_reg(op, reg2, reg1);
  472. A_RLDICL : instr := taicpu.op_reg_reg_const_const(A_RLDICL, reg2, reg1, 0, (8-tcgsize2size[fromsize])*8);
  473. else
  474. internalerror(2002090901);
  475. end;
  476. list.concat(instr);
  477. rg[R_INTREGISTER].add_move_instruction(instr);
  478. end;
  479. procedure tcgppc.a_loadfpu_reg_reg(list: taasmoutput; size: tcgsize; reg1, reg2:
  480. tregister);
  481. var
  482. instr: taicpu;
  483. begin
  484. instr := taicpu.op_reg_reg(A_FMR, reg2, reg1);
  485. list.concat(instr);
  486. rg[R_FPUREGISTER].add_move_instruction(instr);
  487. end;
  488. procedure tcgppc.a_loadfpu_ref_reg(list: taasmoutput; size: tcgsize; const ref:
  489. treference; reg: tregister);
  490. const
  491. FpuLoadInstr: array[OS_F32..OS_F64, boolean, boolean] of TAsmOp =
  492. { indexed? updating?}
  493. (((A_LFS, A_LFSU), (A_LFSX, A_LFSUX)),
  494. ((A_LFD, A_LFDU), (A_LFDX, A_LFDUX)));
  495. var
  496. op: tasmop;
  497. ref2: treference;
  498. begin
  499. { several functions call this procedure with OS_32 or OS_64 }
  500. { so this makes life easier (FK) }
  501. case size of
  502. OS_32, OS_F32:
  503. size := OS_F32;
  504. OS_64, OS_F64, OS_C64:
  505. size := OS_F64;
  506. else
  507. internalerror(200201121);
  508. end;
  509. ref2 := ref;
  510. fixref(list, ref2, size);
  511. op := fpuloadinstr[size, ref2.index <> NR_NO, false];
  512. a_load_store(list, op, reg, ref2);
  513. end;
  514. procedure tcgppc.a_loadfpu_reg_ref(list: taasmoutput; size: tcgsize; reg:
  515. tregister; const ref: treference);
  516. const
  517. FpuStoreInstr: array[OS_F32..OS_F64, boolean, boolean] of TAsmOp =
  518. { indexed? updating?}
  519. (((A_STFS, A_STFSU), (A_STFSX, A_STFSUX)),
  520. ((A_STFD, A_STFDU), (A_STFDX, A_STFDUX)));
  521. var
  522. op: tasmop;
  523. ref2: treference;
  524. begin
  525. if not (size in [OS_F32, OS_F64]) then
  526. internalerror(200201122);
  527. ref2 := ref;
  528. fixref(list, ref2, size);
  529. op := fpustoreinstr[size, ref2.index <> NR_NO, false];
  530. a_load_store(list, op, reg, ref2);
  531. end;
  532. procedure tcgppc.a_op_const_reg(list: taasmoutput; Op: TOpCG; size: TCGSize; a:
  533. aint; reg: TRegister);
  534. begin
  535. a_op_const_reg_reg(list, op, size, a, reg, reg);
  536. end;
  537. procedure tcgppc.a_op_reg_reg(list: taasmoutput; Op: TOpCG; size: TCGSize; src,
  538. dst: TRegister);
  539. begin
  540. a_op_reg_reg_reg(list, op, size, src, dst, dst);
  541. end;
  542. procedure tcgppc.a_op_const_reg_reg(list: taasmoutput; op: TOpCg;
  543. size: tcgsize; a: aint; src, dst: tregister);
  544. var
  545. l1, l2: longint;
  546. oplo, ophi: tasmop;
  547. scratchreg: tregister;
  548. useReg : boolean;
  549. shiftmask : longint;
  550. procedure do_lo_hi;
  551. begin
  552. usereg := false;
  553. if (size in [OS_64, OS_S64]) then begin
  554. // ts: use register method for 64 bit consts. Sloooooow
  555. usereg := true;
  556. end else if (size in [OS_32, OS_S32]) then begin
  557. list.concat(taicpu.op_reg_reg_const(oplo, dst, src, word(a)));
  558. list.concat(taicpu.op_reg_reg_const(ophi, dst, dst, word(a shr 16)));
  559. end else begin
  560. list.concat(taicpu.op_reg_reg_const(oplo, dst, src, word(a)));
  561. end;
  562. end;
  563. begin
  564. if op = OP_SUB then begin
  565. a_op_const_reg_reg(list, OP_ADD, size, -a, src, dst);
  566. exit;
  567. end;
  568. ophi := TOpCG2AsmOpConstHi[op];
  569. oplo := TOpCG2AsmOpConstLo[op];
  570. // peephole optimizations for AND, OR, XOR - can't this be done at
  571. // some higher level, independent of architecture?
  572. if (op in [OP_AND, OP_OR, OP_XOR]) then begin
  573. if (a = 0) then begin
  574. if op = OP_AND then
  575. list.concat(taicpu.op_reg_const(A_LI, dst, 0))
  576. else
  577. a_load_reg_reg(list, size, size, src, dst);
  578. exit;
  579. end else if (a = -1) then begin
  580. case op of
  581. OP_OR:
  582. list.concat(taicpu.op_reg_const(A_LI, dst, -1));
  583. OP_XOR:
  584. list.concat(taicpu.op_reg_reg(A_NOT, dst, src));
  585. OP_AND:
  586. a_load_reg_reg(list, size, size, src, dst);
  587. end;
  588. exit;
  589. end;
  590. { optimization for add }
  591. end else if (op = OP_ADD) then
  592. if a = 0 then begin
  593. a_load_reg_reg(list, size, size, src, dst);
  594. exit;
  595. end else if (a >= low(smallint)) and (a <= high(smallint)) then begin
  596. list.concat(taicpu.op_reg_reg_const(A_ADDI, dst, src, smallint(a)));
  597. exit;
  598. end;
  599. { otherwise, the instructions we can generate depend on the }
  600. { operation }
  601. useReg := false;
  602. case op of
  603. OP_DIV, OP_IDIV:
  604. if (a = 0) then
  605. internalerror(200208103)
  606. else if (a = 1) then begin
  607. a_load_reg_reg(list, OS_INT, OS_INT, src, dst);
  608. exit
  609. end else if false {and ispowerof2(a, l1)} then begin
  610. internalerror(200208103);
  611. case op of
  612. OP_DIV: begin
  613. list.concat(taicpu.op_reg_reg_const(A_SRDI, dst, src, l1));
  614. end;
  615. OP_IDIV:
  616. begin
  617. list.concat(taicpu.op_reg_reg_const(A_SRADI, dst, src, l1));
  618. list.concat(taicpu.op_reg_reg(A_ADDZE, dst, dst));
  619. end;
  620. end;
  621. exit;
  622. end else
  623. usereg := true;
  624. OP_IMUL, OP_MUL:
  625. if (a = 0) then begin
  626. list.concat(taicpu.op_reg_const(A_LI, dst, 0));
  627. exit
  628. end else if (a = -1) then begin
  629. list.concat(taicpu.op_reg_reg(A_NEG, dst, dst));
  630. end else if (a = 1) then begin
  631. a_load_reg_reg(list, OS_INT, OS_INT, src, dst);
  632. exit
  633. end else if ispowerof2(a, l1) then
  634. list.concat(taicpu.op_reg_reg_const(A_SLDI, dst, src, l1))
  635. else if (a >= low(smallint)) and (a <= high(smallint)) then
  636. list.concat(taicpu.op_reg_reg_const(A_MULLI, dst, src,
  637. smallint(a)))
  638. else
  639. usereg := true;
  640. OP_ADD:
  641. {$todo ts:optimize}
  642. useReg := true;
  643. OP_OR:
  644. do_lo_hi;
  645. OP_AND:
  646. useReg := true;
  647. OP_XOR:
  648. do_lo_hi;
  649. OP_SHL, OP_SHR, OP_SAR:
  650. begin
  651. {$note ts: cleanup todo, fix remaining bugs}
  652. if (size in [OS_64, OS_S64]) then begin
  653. if (a and 63) <> 0 then
  654. list.concat(taicpu.op_reg_reg_const(
  655. TShiftOpCG2AsmOpConst64[Op], dst, src, a and 63))
  656. else
  657. a_load_reg_reg(list, size, size, src, dst);
  658. if (a shr 6) <> 0 then
  659. internalError(68991);
  660. end else begin
  661. if (a and 31) <> 0 then
  662. list.concat(taicpu.op_reg_reg_const(
  663. TShiftOpCG2AsmOpConst32[Op], dst, src, a and 31))
  664. else
  665. a_load_reg_reg(list, size, size, src, dst);
  666. if (a shr 5) <> 0 then
  667. internalError(68991);
  668. end;
  669. end
  670. else
  671. internalerror(200109091);
  672. end;
  673. { if all else failed, load the constant in a register and then }
  674. { perform the operation }
  675. if useReg then begin
  676. scratchreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  677. a_load_const_reg(list, size, a, scratchreg);
  678. a_op_reg_reg_reg(list, op, size, scratchreg, src, dst);
  679. end;
  680. end;
  681. procedure tcgppc.a_op_reg_reg_reg(list: taasmoutput; op: TOpCg;
  682. size: tcgsize; src1, src2, dst: tregister);
  683. const
  684. op_reg_reg_opcg2asmop32: array[TOpCG] of tasmop =
  685. (A_NONE, A_ADD, A_AND, A_DIVWU, A_DIVW, A_MULLW, A_MULLW, A_NEG, A_NOT, A_OR,
  686. A_SRAW, A_SLW, A_SRW, A_SUB, A_XOR);
  687. op_reg_reg_opcg2asmop64: array[TOpCG] of tasmop =
  688. (A_NONE, A_ADD, A_AND, A_DIVDU, A_DIVD, A_MULLD, A_MULLD, A_NEG, A_NOT, A_OR,
  689. A_SRAD, A_SLD, A_SRD, A_SUB, A_XOR);
  690. begin
  691. case op of
  692. OP_NEG, OP_NOT:
  693. begin
  694. list.concat(taicpu.op_reg_reg(op_reg_reg_opcg2asmop64[op], dst, src1));
  695. if (op = OP_NOT) and
  696. not (size in [OS_64, OS_S64]) then
  697. { zero/sign extend result again, fromsize is not important here }
  698. a_load_reg_reg(list, OS_S64, size, dst, dst)
  699. end;
  700. else
  701. {$NOTE ts:testme}
  702. if (size in [OS_64, OS_S64]) then begin
  703. list.concat(taicpu.op_reg_reg_reg(op_reg_reg_opcg2asmop64[op], dst, src2,
  704. src1));
  705. end else begin
  706. list.concat(taicpu.op_reg_reg_reg(op_reg_reg_opcg2asmop32[op], dst, src2,
  707. src1));
  708. end;
  709. end;
  710. end;
  711. {*************** compare instructructions ****************}
  712. procedure tcgppc.a_cmp_const_reg_label(list: taasmoutput; size: tcgsize; cmp_op:
  713. topcmp; a: aint; reg: tregister;
  714. l: tasmlabel);
  715. var
  716. scratch_register: TRegister;
  717. signed: boolean;
  718. begin
  719. { todo: use 32 bit compares? }
  720. signed := cmp_op in [OC_GT, OC_LT, OC_GTE, OC_LTE];
  721. { in the following case, we generate more efficient code when }
  722. { signed is true }
  723. if (cmp_op in [OC_EQ, OC_NE]) and
  724. (aword(a) > $FFFF) then
  725. signed := true;
  726. if signed then
  727. if (a >= low(smallint)) and (a <= high(smallint)) then
  728. list.concat(taicpu.op_reg_reg_const(A_CMPDI, NR_CR0, reg, a))
  729. else begin
  730. scratch_register := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  731. a_load_const_reg(list, OS_64, a, scratch_register);
  732. list.concat(taicpu.op_reg_reg_reg(A_CMPD, NR_CR0, reg, scratch_register));
  733. end
  734. else if (aword(a) <= $FFFF) then
  735. list.concat(taicpu.op_reg_reg_const(A_CMPLDI, NR_CR0, reg, aword(a)))
  736. else begin
  737. scratch_register := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  738. a_load_const_reg(list, OS_64, a, scratch_register);
  739. list.concat(taicpu.op_reg_reg_reg(A_CMPLD, NR_CR0, reg,
  740. scratch_register));
  741. end;
  742. a_jmp(list, A_BC, TOpCmp2AsmCond[cmp_op], 0, l);
  743. end;
  744. procedure tcgppc.a_cmp_reg_reg_label(list: taasmoutput; size: tcgsize; cmp_op:
  745. topcmp;
  746. reg1, reg2: tregister; l: tasmlabel);
  747. var
  748. op: tasmop;
  749. begin
  750. if cmp_op in [OC_GT, OC_LT, OC_GTE, OC_LTE] then
  751. if (size in [OS_64, OS_S64]) then
  752. op := A_CMPD
  753. else
  754. op := A_CMPW
  755. else
  756. if (size in [OS_64, OS_S64]) then
  757. op := A_CMPLD
  758. else
  759. op := A_CMPLW;
  760. list.concat(taicpu.op_reg_reg_reg(op, NR_CR0, reg2, reg1));
  761. a_jmp(list, A_BC, TOpCmp2AsmCond[cmp_op], 0, l);
  762. end;
  763. procedure tcgppc.a_jmp_cond(list: taasmoutput; cond: TOpCmp; l: tasmlabel);
  764. begin
  765. a_jmp(list, A_BC, TOpCmp2AsmCond[cond], 0, l);
  766. end;
  767. procedure tcgppc.a_jmp_name(list: taasmoutput; const s: string);
  768. var
  769. p: taicpu;
  770. begin
  771. p := taicpu.op_sym(A_B, objectlibrary.newasmsymbol(s, AB_EXTERNAL,
  772. AT_LABEL));
  773. p.is_jmp := true;
  774. list.concat(p)
  775. end;
  776. procedure tcgppc.a_jmp_always(list: taasmoutput; l: tasmlabel);
  777. begin
  778. a_jmp(list, A_B, C_None, 0, l);
  779. end;
  780. procedure tcgppc.a_jmp_flags(list: taasmoutput; const f: TResFlags; l:
  781. tasmlabel);
  782. var
  783. c: tasmcond;
  784. begin
  785. c := flags_to_cond(f);
  786. a_jmp(list, A_BC, c.cond, c.cr - RS_CR0, l);
  787. end;
  788. procedure tcgppc.g_flags2reg(list: taasmoutput; size: TCgSize; const f:
  789. TResFlags; reg: TRegister);
  790. var
  791. testbit: byte;
  792. bitvalue: boolean;
  793. begin
  794. { get the bit to extract from the conditional register + its }
  795. { requested value (0 or 1) }
  796. testbit := ((f.cr - RS_CR0) * 4);
  797. case f.flag of
  798. F_EQ, F_NE:
  799. begin
  800. inc(testbit, 2);
  801. bitvalue := f.flag = F_EQ;
  802. end;
  803. F_LT, F_GE:
  804. begin
  805. bitvalue := f.flag = F_LT;
  806. end;
  807. F_GT, F_LE:
  808. begin
  809. inc(testbit);
  810. bitvalue := f.flag = F_GT;
  811. end;
  812. else
  813. internalerror(200112261);
  814. end;
  815. { load the conditional register in the destination reg }
  816. list.concat(taicpu.op_reg(A_MFCR, reg));
  817. { we will move the bit that has to be tested to bit 0 by rotating }
  818. { left }
  819. testbit := (testbit + 1) and 31;
  820. { extract bit }
  821. list.concat(taicpu.op_reg_reg_const_const_const(
  822. A_RLWINM,reg,reg,testbit,31,31));
  823. { if we need the inverse, xor with 1 }
  824. if not bitvalue then
  825. list.concat(taicpu.op_reg_reg_const(A_XORI, reg, reg, 1));
  826. end;
  827. { *********** entry/exit code and address loading ************ }
  828. procedure tcgppc.g_save_standard_registers(list: Taasmoutput);
  829. begin
  830. { this work is done in g_proc_entry }
  831. end;
  832. procedure tcgppc.g_restore_standard_registers(list: Taasmoutput);
  833. begin
  834. { this work is done in g_proc_exit }
  835. end;
  836. procedure tcgppc.calcFirstUsedFPR(out firstfpr : TSuperRegister; out fprcount : aint);
  837. var
  838. reg : TSuperRegister;
  839. begin
  840. fprcount := 0;
  841. firstfpr := RS_F31;
  842. if not (po_assembler in current_procinfo.procdef.procoptions) then begin
  843. for reg := RS_F14 to RS_F31 do begin
  844. if reg in rg[R_FPUREGISTER].used_in_proc then begin
  845. fprcount := ord(RS_F31)-ord(reg)+1;
  846. firstfpr := reg;
  847. break;
  848. end;
  849. end;
  850. end;
  851. end;
  852. procedure tcgppc.calcFirstUsedGPR(out firstgpr : TSuperRegister; out gprcount : aint);
  853. var
  854. reg : TSuperRegister;
  855. begin
  856. gprcount := 0;
  857. firstgpr := RS_R31;
  858. if not (po_assembler in current_procinfo.procdef.procoptions) then begin
  859. for reg := RS_R14 to RS_R31 do begin
  860. if reg in rg[R_INTREGISTER].used_in_proc then begin
  861. gprcount := ord(RS_R31)-ord(reg)+1;
  862. firstgpr := reg;
  863. break;
  864. end;
  865. end;
  866. end;
  867. end;
  868. procedure tcgppc.g_proc_entry(list: taasmoutput; localsize: longint;
  869. nostackframe: boolean);
  870. { generated the entry code of a procedure/function. Note: localsize is the }
  871. { sum of the size necessary for local variables and the maximum possible }
  872. { combined size of ALL the parameters of a procedure called by the current }
  873. { one. }
  874. { This procedure may be called before, as well as after g_return_from_proc }
  875. { is called. NOTE registers are not to be allocated through the register }
  876. { allocator here, because the register colouring has already occured !! }
  877. var
  878. firstregfpu, firstreggpr: TSuperRegister;
  879. href: treference;
  880. needslinkreg: boolean;
  881. regcount : TSuperRegister;
  882. fprcount, gprcount : aint;
  883. begin
  884. { CR and LR only have to be saved in case they are modified by the current }
  885. { procedure, but currently this isn't checked, so save them always }
  886. { following is the entry code as described in "Altivec Programming }
  887. { Interface Manual", bar the saving of AltiVec registers }
  888. a_reg_alloc(list, NR_STACK_POINTER_REG);
  889. a_reg_alloc(list, NR_R0);
  890. calcFirstUsedFPR(firstregfpu, fprcount);
  891. calcFirstUsedGPR(firstreggpr, gprcount);
  892. // calculate real stack frame size
  893. localsize := tppcprocinfo(current_procinfo).calc_stackframe_size(
  894. gprcount, fprcount);
  895. // determine whether we need to save the link register
  896. needslinkreg := ((not (po_assembler in current_procinfo.procdef.procoptions)) and
  897. (pi_do_call in current_procinfo.flags));
  898. // move link register to r0
  899. if (needslinkreg) then begin
  900. list.concat(taicpu.op_reg(A_MFLR, NR_R0));
  901. end;
  902. // save old stack frame pointer
  903. if (localsize > 0) then begin
  904. a_reg_alloc(list, NR_R12);
  905. list.concat(taicpu.op_reg_reg(A_MR, NR_R12, NR_STACK_POINTER_REG));
  906. end;
  907. // save registers, FPU first, then GPR
  908. reference_reset_base(href, NR_STACK_POINTER_REG, -8);
  909. if (fprcount > 0) then begin
  910. for regcount := RS_F31 downto firstregfpu do begin
  911. a_loadfpu_reg_ref(list, OS_FLOAT, newreg(R_FPUREGISTER, regcount,
  912. R_SUBNONE), href);
  913. dec(href.offset, tcgsize2size[OS_FLOAT]);
  914. end;
  915. end;
  916. if (gprcount > 0) then begin
  917. for regcount := RS_R31 downto firstreggpr do begin
  918. a_load_reg_ref(list, OS_INT, OS_INT, newreg(R_INTREGISTER, regcount,
  919. R_SUBNONE), href);
  920. dec(href.offset, tcgsize2size[OS_INT]);
  921. end;
  922. end;
  923. // VMX registers not supported by FPC atm
  924. // we may need to store R0 (=LR) ourselves
  925. if (needslinkreg) then begin
  926. reference_reset_base(href, NR_STACK_POINTER_REG, LA_LR_ELF);
  927. list.concat(taicpu.op_reg_ref(A_STD, NR_R0, href));
  928. end;
  929. // create stack frame
  930. if (not nostackframe) and (localsize > 0) then begin
  931. if (localsize <= high(smallint)) then begin
  932. reference_reset_base(href, NR_STACK_POINTER_REG, -localsize);
  933. a_load_store(list, A_STDU, NR_STACK_POINTER_REG, href);
  934. end else begin
  935. reference_reset_base(href, NR_NO, -localsize);
  936. // use R0 for loading the constant (which is definitely > 32k when entering
  937. // this branch)
  938. // inlined because it must not use temp registers because register allocations
  939. // have already been done :(
  940. { Code template:
  941. lis r0,ofs@highest
  942. ori r0,r0,ofs@higher
  943. sldi r0,r0,32
  944. oris r0,r0,ofs@h
  945. ori r0,r0,ofs@l
  946. }
  947. list.concat(taicpu.op_reg_const(A_LIS, NR_R0, word(href.offset shr 48)));
  948. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset shr 32)));
  949. list.concat(taicpu.op_reg_reg_const(A_SLDI, NR_R0, NR_R0, 32));
  950. list.concat(taicpu.op_reg_reg_const(A_ORIS, NR_R0, NR_R0, word(href.offset shr 16)));
  951. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset)));
  952. list.concat(taicpu.op_reg_reg_reg(A_STDUX, NR_R1, NR_R1, NR_R0));
  953. end;
  954. end;
  955. // CR register not used by FPC atm
  956. // keep R1 allocated???
  957. a_reg_dealloc(list, NR_R0);
  958. end;
  959. procedure tcgppc.g_proc_exit(list: taasmoutput; parasize: longint; nostackframe:
  960. boolean);
  961. { This procedure may be called before, as well as after g_stackframe_entry }
  962. { is called. NOTE registers are not to be allocated through the register }
  963. { allocator here, because the register colouring has already occured !! }
  964. var
  965. regcount, firstregfpu, firstreggpr: TSuperRegister;
  966. href: treference;
  967. needslinkreg : boolean;
  968. localsize,
  969. fprcount, gprcount: aint;
  970. begin
  971. calcFirstUsedFPR(firstregfpu, fprcount);
  972. calcFirstUsedGPR(firstreggpr, gprcount);
  973. // determine whether we need to restore the link register
  974. needslinkreg := ((not (po_assembler in current_procinfo.procdef.procoptions)) and
  975. (pi_do_call in current_procinfo.flags));
  976. // calculate stack frame
  977. localsize := tppcprocinfo(current_procinfo).calc_stackframe_size(
  978. gprcount, fprcount);
  979. // CR register not supported
  980. // restore stack pointer
  981. if (not nostackframe) and (localsize > 0) then begin
  982. if (localsize <= high(smallint)) then begin
  983. list.concat(taicpu.op_reg_reg_const(A_ADDI, NR_STACK_POINTER_REG, NR_STACK_POINTER_REG, localsize));
  984. end else begin
  985. reference_reset_base(href, NR_NO, localsize);
  986. // use R0 for loading the constant (which is definitely > 32k when entering
  987. // this branch)
  988. // inlined because it must not use temp registers because register allocations
  989. // have already been done :(
  990. { Code template:
  991. lis r0,ofs@highest
  992. ori r0,ofs@higher
  993. sldi r0,r0,32
  994. oris r0,r0,ofs@h
  995. ori r0,r0,ofs@l
  996. }
  997. list.concat(taicpu.op_reg_const(A_LIS, NR_R0, word(href.offset shr 48)));
  998. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset shr 32)));
  999. list.concat(taicpu.op_reg_reg_const(A_SLDI, NR_R0, NR_R0, 32));
  1000. list.concat(taicpu.op_reg_reg_const(A_ORIS, NR_R0, NR_R0, word(href.offset shr 16)));
  1001. list.concat(taicpu.op_reg_reg_const(A_ORI, NR_R0, NR_R0, word(href.offset)));
  1002. list.concat(taicpu.op_reg_reg_reg(A_ADD, NR_R1, NR_R1, NR_R0));
  1003. end;
  1004. end;
  1005. // load registers, FPR first, then GPR
  1006. {$note ts:todo change order of loading}
  1007. reference_reset_base(href, NR_STACK_POINTER_REG, -tcgsize2size[OS_FLOAT]);
  1008. if (fprcount > 0) then begin
  1009. for regcount := RS_F31 downto firstregfpu do begin
  1010. a_loadfpu_ref_reg(list, OS_FLOAT, href, newreg(R_FPUREGISTER, regcount,
  1011. R_SUBNONE));
  1012. dec(href.offset, tcgsize2size[OS_FLOAT]);
  1013. end;
  1014. end;
  1015. if (gprcount > 0) then begin
  1016. for regcount := RS_R31 downto firstreggpr do begin
  1017. a_load_ref_reg(list, OS_INT, OS_INT, href, newreg(R_INTREGISTER, regcount,
  1018. R_SUBNONE));
  1019. dec(href.offset, tcgsize2size[OS_INT]);
  1020. end;
  1021. end;
  1022. // VMX not supported...
  1023. // restore LR (if needed)
  1024. if (needslinkreg) then begin
  1025. reference_reset_base(href, NR_STACK_POINTER_REG, LA_LR_ELF);
  1026. list.concat(taicpu.op_reg_ref(A_LD, NR_R0, href));
  1027. list.concat(taicpu.op_reg(A_MTLR, NR_R0));
  1028. end;
  1029. // generate return instruction
  1030. list.concat(taicpu.op_none(A_BLR));
  1031. end;
  1032. procedure tcgppc.a_loadaddr_ref_reg(list: taasmoutput; const ref: treference; r:
  1033. tregister);
  1034. var
  1035. ref2, tmpref: treference;
  1036. // register used to construct address
  1037. tempreg : TRegister;
  1038. begin
  1039. ref2 := ref;
  1040. fixref(list, ref2, OS_64);
  1041. { load a symbol }
  1042. if assigned(ref2.symbol) or (hasLargeOffset(ref2)) then begin
  1043. { add the symbol's value to the base of the reference, and if the }
  1044. { reference doesn't have a base, create one }
  1045. reference_reset(tmpref);
  1046. tmpref.offset := ref2.offset;
  1047. tmpref.symbol := ref2.symbol;
  1048. tmpref.relsymbol := ref2.relsymbol;
  1049. // load 64 bit reference into r. If the reference already has a base register,
  1050. // first load the 64 bit value into a temp register, then add it to the result
  1051. // register rD
  1052. if (ref2.base <> NR_NO) then begin
  1053. // already have a base register, so allocate a new one
  1054. tempreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1055. end else begin
  1056. tempreg := r;
  1057. end;
  1058. // code for loading a reference from a symbol into a register rD.
  1059. (*
  1060. lis rX,SYM@highest
  1061. ori rX,SYM@higher
  1062. sldi rX,rX,32
  1063. oris rX,rX,SYM@h
  1064. ori rX,rX,SYM@l
  1065. *)
  1066. tmpref.refaddr := addr_highest;
  1067. list.concat(taicpu.op_reg_ref(A_LIS, tempreg, tmpref));
  1068. tmpref.refaddr := addr_higher;
  1069. list.concat(taicpu.op_reg_reg_ref(A_ORI, tempreg, tempreg, tmpref));
  1070. list.concat(taicpu.op_reg_reg_const(A_SLDI, tempreg, tempreg, 32));
  1071. tmpref.refaddr := addr_high;
  1072. list.concat(taicpu.op_reg_reg_ref(A_ORIS, tempreg, tempreg, tmpref));
  1073. tmpref.refaddr := addr_low;
  1074. list.concat(taicpu.op_reg_reg_ref(A_ORI, tempreg, tempreg, tmpref));
  1075. // if there's already a base register, add the temp register contents to
  1076. // the base register
  1077. if (ref2.base <> NR_NO) then begin
  1078. list.concat(taicpu.op_reg_reg_reg(A_ADD, r, tempreg, ref2.base));
  1079. end;
  1080. end else if ref2.offset <> 0 then begin
  1081. { no symbol, but offset <> 0 }
  1082. if ref2.base <> NR_NO then begin
  1083. a_op_const_reg_reg(list, OP_ADD, OS_64, ref2.offset, ref2.base, r)
  1084. { FixRef makes sure that "(ref.index <> R_NO) and (ref.offset <> 0)" never}
  1085. { occurs, so now only ref.offset has to be loaded }
  1086. end else begin
  1087. a_load_const_reg(list, OS_64, ref2.offset, r)
  1088. end;
  1089. end else if ref.index <> NR_NO then
  1090. list.concat(taicpu.op_reg_reg_reg(A_ADD, r, ref2.base, ref2.index))
  1091. else if (ref2.base <> NR_NO) and
  1092. (r <> ref2.base) then
  1093. a_load_reg_reg(list, OS_ADDR, OS_ADDR, ref2.base, r)
  1094. else begin
  1095. list.concat(taicpu.op_reg_const(A_LI, r, 0));
  1096. end;
  1097. end;
  1098. { ************* concatcopy ************ }
  1099. const
  1100. maxmoveunit = 8;
  1101. procedure tcgppc.g_concatcopy(list: taasmoutput; const source, dest: treference;
  1102. len: aint);
  1103. var
  1104. countreg, tempreg: TRegister;
  1105. src, dst: TReference;
  1106. lab: tasmlabel;
  1107. count, count2: longint;
  1108. size: tcgsize;
  1109. begin
  1110. {$IFDEF extdebug}
  1111. if len > high(aint) then
  1112. internalerror(2002072704);
  1113. {$ENDIF extdebug}
  1114. { make sure short loads are handled as optimally as possible }
  1115. if (len <= maxmoveunit) and
  1116. (byte(len) in [1, 2, 4, 8]) then
  1117. begin
  1118. if len < 8 then
  1119. begin
  1120. size := int_cgsize(len);
  1121. a_load_ref_ref(list, size, size, source, dest);
  1122. end
  1123. else
  1124. begin
  1125. a_reg_alloc(list, NR_F0);
  1126. a_loadfpu_ref_reg(list, OS_F64, source, NR_F0);
  1127. a_loadfpu_reg_ref(list, OS_F64, NR_F0, dest);
  1128. a_reg_dealloc(list, NR_F0);
  1129. end;
  1130. exit;
  1131. end;
  1132. count := len div maxmoveunit;
  1133. reference_reset(src);
  1134. reference_reset(dst);
  1135. { load the address of source into src.base }
  1136. if (count > 4) or
  1137. not issimpleref(source) or
  1138. ((source.index <> NR_NO) and
  1139. ((source.offset + len) > high(smallint))) then begin
  1140. src.base := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1141. a_loadaddr_ref_reg(list, source, src.base);
  1142. end else begin
  1143. src := source;
  1144. end;
  1145. { load the address of dest into dst.base }
  1146. if (count > 4) or
  1147. not issimpleref(dest) or
  1148. ((dest.index <> NR_NO) and
  1149. ((dest.offset + len) > high(smallint))) then begin
  1150. dst.base := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1151. a_loadaddr_ref_reg(list, dest, dst.base);
  1152. end else begin
  1153. dst := dest;
  1154. end;
  1155. { generate a loop }
  1156. if count > 4 then begin
  1157. { the offsets are zero after the a_loadaddress_ref_reg and just }
  1158. { have to be set to 8. I put an Inc there so debugging may be }
  1159. { easier (should offset be different from zero here, it will be }
  1160. { easy to notice in the generated assembler }
  1161. inc(dst.offset, 8);
  1162. inc(src.offset, 8);
  1163. list.concat(taicpu.op_reg_reg_const(A_SUBI, src.base, src.base, 8));
  1164. list.concat(taicpu.op_reg_reg_const(A_SUBI, dst.base, dst.base, 8));
  1165. countreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1166. a_load_const_reg(list, OS_32, count, countreg);
  1167. { explicitely allocate R_0 since it can be used safely here }
  1168. { (for holding date that's being copied) }
  1169. a_reg_alloc(list, NR_F0);
  1170. objectlibrary.getjumplabel(lab);
  1171. a_label(list, lab);
  1172. list.concat(taicpu.op_reg_reg_const(A_SUBIC_, countreg, countreg, 1));
  1173. list.concat(taicpu.op_reg_ref(A_LFDU, NR_F0, src));
  1174. list.concat(taicpu.op_reg_ref(A_STFDU, NR_F0, dst));
  1175. a_jmp(list, A_BC, C_NE, 0, lab);
  1176. a_reg_dealloc(list, NR_F0);
  1177. len := len mod 8;
  1178. end;
  1179. count := len div 8;
  1180. { unrolled loop }
  1181. if count > 0 then begin
  1182. a_reg_alloc(list, NR_F0);
  1183. for count2 := 1 to count do begin
  1184. a_loadfpu_ref_reg(list, OS_F64, src, NR_F0);
  1185. a_loadfpu_reg_ref(list, OS_F64, NR_F0, dst);
  1186. inc(src.offset, 8);
  1187. inc(dst.offset, 8);
  1188. end;
  1189. a_reg_dealloc(list, NR_F0);
  1190. len := len mod 8;
  1191. end;
  1192. if (len and 4) <> 0 then begin
  1193. a_reg_alloc(list, NR_R0);
  1194. a_load_ref_reg(list, OS_32, OS_32, src, NR_R0);
  1195. a_load_reg_ref(list, OS_32, OS_32, NR_R0, dst);
  1196. inc(src.offset, 4);
  1197. inc(dst.offset, 4);
  1198. a_reg_dealloc(list, NR_R0);
  1199. end;
  1200. { copy the leftovers }
  1201. if (len and 2) <> 0 then begin
  1202. a_reg_alloc(list, NR_R0);
  1203. a_load_ref_reg(list, OS_16, OS_16, src, NR_R0);
  1204. a_load_reg_ref(list, OS_16, OS_16, NR_R0, dst);
  1205. inc(src.offset, 2);
  1206. inc(dst.offset, 2);
  1207. a_reg_dealloc(list, NR_R0);
  1208. end;
  1209. if (len and 1) <> 0 then begin
  1210. a_reg_alloc(list, NR_R0);
  1211. a_load_ref_reg(list, OS_8, OS_8, src, NR_R0);
  1212. a_load_reg_ref(list, OS_8, OS_8, NR_R0, dst);
  1213. a_reg_dealloc(list, NR_R0);
  1214. end;
  1215. end;
  1216. procedure tcgppc.g_overflowcheck(list: taasmoutput; const l: tlocation; def:
  1217. tdef);
  1218. var
  1219. hl: tasmlabel;
  1220. flags : TResFlags;
  1221. begin
  1222. if not (cs_check_overflow in aktlocalswitches) then
  1223. exit;
  1224. objectlibrary.getjumplabel(hl);
  1225. if not ((def.deftype = pointerdef) or
  1226. ((def.deftype = orddef) and
  1227. (torddef(def).typ in [u64bit, u16bit, u32bit, u8bit, uchar,
  1228. bool8bit, bool16bit, bool32bit]))) then
  1229. begin
  1230. // ... instruction setting overflow flag ...
  1231. // mfxerf R0
  1232. // mtcrf 128, R0
  1233. // ble cr0, label
  1234. list.concat(taicpu.op_reg(A_MFXER, NR_R0));
  1235. list.concat(taicpu.op_const_reg(A_MTCRF, 128, NR_R0));
  1236. flags.cr := RS_CR0;
  1237. flags.flag := F_LE;
  1238. a_jmp_flags(list, flags, hl);
  1239. end else
  1240. a_jmp_cond(list, OC_AE, hl);
  1241. a_call_name(list, 'FPC_OVERFLOW');
  1242. a_label(list, hl);
  1243. end;
  1244. procedure tcgppc.g_intf_wrapper(list: TAAsmoutput; procdef: tprocdef; const
  1245. labelname: string; ioffset: longint);
  1246. procedure loadvmttor11;
  1247. var
  1248. href: treference;
  1249. begin
  1250. reference_reset_base(href, NR_R3, 0);
  1251. cg.a_load_ref_reg(list, OS_ADDR, OS_ADDR, href, NR_R11);
  1252. end;
  1253. procedure op_onr11methodaddr;
  1254. var
  1255. href: treference;
  1256. begin
  1257. if (procdef.extnumber = $FFFF) then
  1258. Internalerror(200006139);
  1259. { call/jmp vmtoffs(%eax) ; method offs }
  1260. reference_reset_base(href, NR_R11,
  1261. procdef._class.vmtmethodoffset(procdef.extnumber));
  1262. if not (hasLargeOffset(href)) then begin
  1263. list.concat(taicpu.op_reg_reg_const(A_ADDIS, NR_R11, NR_R11,
  1264. smallint((href.offset shr 16) + ord(smallint(href.offset and $FFFF) <
  1265. 0))));
  1266. href.offset := smallint(href.offset and $FFFF);
  1267. end else
  1268. { add support for offsets > 16 bit }
  1269. internalerror(200510201);
  1270. list.concat(taicpu.op_reg_ref(A_LD, NR_R11, href));
  1271. // the loaded reference is a function descriptor reference, so deref again
  1272. // (at ofs 0 there's the real pointer)
  1273. {$warning ts:TODO: update GOT reference}
  1274. reference_reset_base(href, NR_R11, 0);
  1275. list.concat(taicpu.op_reg_ref(A_LD, NR_R11, href));
  1276. list.concat(taicpu.op_reg(A_MTCTR, NR_R11));
  1277. list.concat(taicpu.op_none(A_BCTR));
  1278. // NOP needed for the linker...?
  1279. list.concat(taicpu.op_none(A_NOP));
  1280. end;
  1281. var
  1282. make_global: boolean;
  1283. begin
  1284. if (not (procdef.proctypeoption in [potype_function, potype_procedure])) then
  1285. Internalerror(200006137);
  1286. if not assigned(procdef._class) or
  1287. (procdef.procoptions * [po_classmethod, po_staticmethod,
  1288. po_methodpointer, po_interrupt, po_iocheck] <> []) then
  1289. Internalerror(200006138);
  1290. if procdef.owner.symtabletype <> objectsymtable then
  1291. Internalerror(200109191);
  1292. make_global := false;
  1293. if (not current_module.is_unit) or
  1294. (cs_create_smart in aktmoduleswitches) or
  1295. (procdef.owner.defowner.owner.symtabletype = globalsymtable) then
  1296. make_global := true;
  1297. if make_global then
  1298. List.concat(Tai_symbol.Createname_global(labelname, AT_FUNCTION, 0))
  1299. else
  1300. List.concat(Tai_symbol.Createname(labelname, AT_FUNCTION, 0));
  1301. { set param1 interface to self }
  1302. g_adjust_self_value(list, procdef, ioffset);
  1303. { case 4 }
  1304. if po_virtualmethod in procdef.procoptions then begin
  1305. loadvmttor11;
  1306. op_onr11methodaddr;
  1307. end { case 0 } else
  1308. {$note ts:todo add GOT change?? - think not needed :) }
  1309. list.concat(taicpu.op_sym(A_B,
  1310. objectlibrary.newasmsymbol('.' + procdef.mangledname, AB_EXTERNAL,
  1311. AT_FUNCTION)));
  1312. List.concat(Tai_symbol_end.Createname(labelname));
  1313. end;
  1314. {***************** This is private property, keep out! :) *****************}
  1315. function tcgppc.issimpleref(const ref: treference): boolean;
  1316. begin
  1317. if (ref.base = NR_NO) and
  1318. (ref.index <> NR_NO) then
  1319. internalerror(200208101);
  1320. result :=
  1321. not (assigned(ref.symbol)) and
  1322. (((ref.index = NR_NO) and
  1323. (ref.offset >= low(smallint)) and
  1324. (ref.offset <= high(smallint))) or
  1325. ((ref.index <> NR_NO) and
  1326. (ref.offset = 0)));
  1327. end;
  1328. function tcgppc.fixref(list: taasmoutput; var ref: treference; const size : TCgsize): boolean;
  1329. var
  1330. tmpreg: tregister;
  1331. needsAlign : boolean;
  1332. begin
  1333. result := false;
  1334. needsAlign := size in [OS_S32, OS_64, OS_S64];
  1335. if (ref.base = NR_NO) then begin
  1336. ref.base := ref.index;
  1337. ref.index := NR_NO;
  1338. end;
  1339. if (ref.base <> NR_NO) and (ref.index <> NR_NO) and
  1340. ((ref.offset <> 0) or assigned(ref.symbol)) then begin
  1341. result := true;
  1342. tmpreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1343. a_op_reg_reg_reg(list, OP_ADD, size, ref.base, ref.index, tmpreg);
  1344. ref.index := NR_NO;
  1345. ref.base := tmpreg;
  1346. end;
  1347. end;
  1348. procedure tcgppc.a_load_store(list: taasmoutput; op: tasmop; reg: tregister;
  1349. ref: treference);
  1350. var
  1351. tmpreg, tmpreg2: tregister;
  1352. tmpref: treference;
  1353. largeOffset: Boolean;
  1354. begin
  1355. { at this point there must not be a combination of values in the ref treference
  1356. which is not possible to directly map to instructions of the PowerPC architecture }
  1357. if (ref.index <> NR_NO) and ((ref.offset <> 0) or (assigned(ref.symbol))) then
  1358. internalerror(200310131);
  1359. { for some instructions we need to check that the offset is divisible by at
  1360. least four. If not, add the bytes which are "off" to the base register and
  1361. adjust the offset accordingly }
  1362. case op of
  1363. A_LD, A_LDU, A_STD, A_STDU, A_LWA, A_LWAU :
  1364. if ((ref.offset mod 4) <> 0) then begin
  1365. tmpreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1366. if (ref.base <> NR_NO) then begin
  1367. a_op_const_reg_reg(list, OP_ADD, OS_ADDR, ref.offset mod 4, ref.base, tmpreg);
  1368. ref.base := tmpreg;
  1369. end else begin
  1370. list.concat(taicpu.op_reg_const(A_LI, tmpreg, ref.offset mod 4));
  1371. ref.base := tmpreg;
  1372. end;
  1373. ref.offset := (ref.offset div 4) * 4;
  1374. end;
  1375. end;
  1376. { if we have to load/store from a symbol or large addresses, use a temporary register
  1377. containing the address }
  1378. if assigned(ref.symbol) or (hasLargeOffset(ref)) then begin
  1379. tmpreg := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1380. if (hasLargeOffset(ref) and (ref.base = NR_NO)) then begin
  1381. ref.base := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1382. a_load_const_reg(list, OS_ADDR, ref.offset, ref.base);
  1383. ref.offset := 0;
  1384. end;
  1385. reference_reset(tmpref);
  1386. tmpref.symbol := ref.symbol;
  1387. tmpref.relsymbol := ref.relsymbol;
  1388. tmpref.offset := ref.offset;
  1389. if (ref.base <> NR_NO) then begin
  1390. { As long as the TOC isn't working we try to achieve highest speed (in this
  1391. case by allowing instructions execute in parallel) as possible at the cost
  1392. of using another temporary register. So the code template when there is
  1393. a base register and an offset is the following:
  1394. lis rT1, SYM+offs@highest
  1395. ori rT1, rT1, SYM+offs@higher
  1396. lis rT2, SYM+offs@hi
  1397. ori rT2, SYM+offs@lo
  1398. rldimi rT2, rT1, 32
  1399. <op>X reg, base, rT2
  1400. }
  1401. tmpreg2 := rg[R_INTREGISTER].getregister(list, R_SUBWHOLE);
  1402. tmpref.refaddr := addr_highest;
  1403. list.concat(taicpu.op_reg_ref(A_LIS, tmpreg, tmpref));
  1404. tmpref.refaddr := addr_higher;
  1405. list.concat(taicpu.op_reg_reg_ref(A_ORI, tmpreg, tmpreg, tmpref));
  1406. tmpref.refaddr := addr_high;
  1407. list.concat(taicpu.op_reg_ref(A_LIS, tmpreg2, tmpref));
  1408. tmpref.refaddr := addr_low;
  1409. list.concat(taicpu.op_reg_reg_ref(A_ORI, tmpreg2, tmpreg2, tmpref));
  1410. list.concat(taicpu.op_reg_reg_const_const(A_RLDIMI, tmpreg2, tmpreg, 32, 0));
  1411. reference_reset(tmpref);
  1412. tmpref.base := ref.base;
  1413. tmpref.index := tmpreg2;
  1414. case op of
  1415. { the code generator doesn't generate update instructions anyway }
  1416. A_LBZ : op := A_LBZX;
  1417. A_LHZ : op := A_LHZX;
  1418. A_LWZ : op := A_LWZX;
  1419. A_LD : op := A_LDX;
  1420. A_LHA : op := A_LHAX;
  1421. A_LWA : op := A_LWAX;
  1422. A_LFS : op := A_LFSX;
  1423. A_LFD : op := A_LFDX;
  1424. A_STB : op := A_STBX;
  1425. A_STH : op := A_STHX;
  1426. A_STW : op := A_STWX;
  1427. A_STD : op := A_STDX;
  1428. A_STFS : op := A_STFSX;
  1429. A_STFD : op := A_STFDX;
  1430. else
  1431. { unknown load/store opcode }
  1432. internalerror(2005101302);
  1433. end;
  1434. list.concat(taicpu.op_reg_ref(op, reg, tmpref));
  1435. end else begin
  1436. { when accessing value from a reference without a base register, use the
  1437. following code template:
  1438. lis rT,SYM+offs@highesta
  1439. ori rT,SYM+offs@highera
  1440. sldi rT,rT,32
  1441. oris rT,rT,SYM+offs@ha
  1442. ld rD,SYM+offs@l(rT)
  1443. }
  1444. tmpref.refaddr := addr_highesta;
  1445. list.concat(taicpu.op_reg_ref(A_LIS, tmpreg, tmpref));
  1446. tmpref.refaddr := addr_highera;
  1447. list.concat(taicpu.op_reg_reg_ref(A_ORI, tmpreg, tmpreg, tmpref));
  1448. list.concat(taicpu.op_reg_reg_const(A_SLDI, tmpreg, tmpreg, 32));
  1449. tmpref.refaddr := addr_higha;
  1450. list.concat(taicpu.op_reg_reg_ref(A_ORIS, tmpreg, tmpreg, tmpref));
  1451. tmpref.base := tmpreg;
  1452. tmpref.refaddr := addr_low;
  1453. list.concat(taicpu.op_reg_ref(op, reg, tmpref));
  1454. end;
  1455. end else begin
  1456. list.concat(taicpu.op_reg_ref(op, reg, ref));
  1457. end;
  1458. end;
  1459. procedure tcgppc.a_jmp(list: taasmoutput; op: tasmop; c: tasmcondflag;
  1460. crval: longint; l: tasmlabel);
  1461. var
  1462. p: taicpu;
  1463. begin
  1464. p := taicpu.op_sym(op, objectlibrary.newasmsymbol(l.name, AB_EXTERNAL,
  1465. AT_LABEL));
  1466. if op <> A_B then
  1467. create_cond_norm(c, crval, p.condition);
  1468. p.is_jmp := true;
  1469. list.concat(p)
  1470. end;
  1471. function tcgppc.hasLargeOffset(const ref : TReference) : Boolean;
  1472. begin
  1473. { this rather strange calculation is required because offsets of TReferences are unsigned }
  1474. result := aword(ref.offset-low(smallint)) > high(smallint)-low(smallint);
  1475. end;
  1476. begin
  1477. cg := tcgppc.create;
  1478. end.