cgcpu.pas 71 KB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151115211531154115511561157115811591160116111621163116411651166116711681169117011711172117311741175117611771178117911801181118211831184118511861187118811891190119111921193119411951196119711981199120012011202120312041205120612071208120912101211121212131214121512161217121812191220122112221223122412251226122712281229123012311232123312341235123612371238123912401241124212431244124512461247124812491250125112521253125412551256125712581259126012611262126312641265126612671268126912701271127212731274127512761277127812791280128112821283128412851286128712881289129012911292129312941295129612971298129913001301130213031304130513061307130813091310131113121313131413151316131713181319132013211322132313241325132613271328132913301331133213331334133513361337133813391340134113421343134413451346134713481349135013511352135313541355135613571358135913601361136213631364136513661367136813691370137113721373137413751376137713781379138013811382138313841385138613871388138913901391139213931394139513961397139813991400140114021403140414051406140714081409141014111412141314141415141614171418141914201421142214231424142514261427142814291430143114321433143414351436143714381439144014411442144314441445144614471448144914501451145214531454145514561457145814591460146114621463146414651466146714681469147014711472147314741475147614771478147914801481148214831484148514861487148814891490149114921493149414951496149714981499150015011502150315041505150615071508150915101511151215131514151515161517151815191520152115221523152415251526152715281529153015311532153315341535153615371538153915401541154215431544154515461547154815491550155115521553155415551556155715581559156015611562156315641565156615671568156915701571157215731574157515761577157815791580158115821583158415851586158715881589159015911592159315941595159615971598159916001601160216031604160516061607160816091610161116121613161416151616161716181619162016211622162316241625162616271628162916301631163216331634163516361637163816391640164116421643164416451646164716481649165016511652165316541655165616571658165916601661166216631664166516661667166816691670167116721673167416751676167716781679168016811682168316841685168616871688168916901691169216931694169516961697169816991700170117021703170417051706170717081709171017111712171317141715171617171718171917201721172217231724172517261727172817291730173117321733173417351736173717381739174017411742174317441745174617471748174917501751175217531754175517561757175817591760176117621763176417651766176717681769177017711772177317741775177617771778177917801781178217831784178517861787178817891790179117921793179417951796179717981799180018011802180318041805180618071808180918101811181218131814181518161817181818191820182118221823182418251826182718281829183018311832183318341835183618371838183918401841184218431844184518461847184818491850185118521853185418551856185718581859186018611862186318641865186618671868186918701871187218731874187518761877187818791880188118821883188418851886188718881889189018911892189318941895189618971898189919001901190219031904190519061907190819091910191119121913191419151916191719181919192019211922192319241925192619271928192919301931193219331934193519361937193819391940194119421943194419451946194719481949195019511952195319541955195619571958195919601961196219631964196519661967196819691970197119721973197419751976197719781979198019811982198319841985198619871988198919901991199219931994199519961997199819992000200120022003200420052006200720082009201020112012201320142015201620172018201920202021202220232024202520262027202820292030203120322033203420352036203720382039204020412042204320442045204620472048204920502051205220532054205520562057205820592060206120622063206420652066206720682069207020712072207320742075207620772078207920802081
  1. {
  2. Copyright (c) 1998-2012 by Florian Klaempfl and David Zhang
  3. This unit implements the code generator for MIPS
  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, parabase,
  22. cgbase, cgutils, cgobj,
  23. {$ifndef mips64}
  24. cg64f32,
  25. {$endif mips64}
  26. cpupara,
  27. aasmbase, aasmtai, aasmcpu, aasmdata,
  28. cpubase, cpuinfo,
  29. node, symconst, SymType, symdef,
  30. rgcpu;
  31. type
  32. TCGMIPS = class(tcg)
  33. public
  34. procedure init_register_allocators; override;
  35. procedure done_register_allocators; override;
  36. /// { needed by cg64 }
  37. procedure make_simple_ref(list: tasmlist; var ref: treference);
  38. procedure handle_reg_const_reg(list: tasmlist; op: Tasmop; src: tregister; a: tcgint; dst: tregister);
  39. procedure maybeadjustresult(list: TAsmList; op: TOpCg; size: tcgsize; dst: tregister);
  40. procedure overflowcheck_internal(list: TAsmList; arg1, arg2: TRegister);
  41. { parameter }
  42. procedure a_loadfpu_reg_cgpara(list: tasmlist; size: tcgsize; const r: tregister; const paraloc: TCGPara); override;
  43. procedure a_loadfpu_ref_cgpara(list: tasmlist; size: tcgsize; const ref: treference; const paraloc: TCGPara); override;
  44. procedure a_call_name(list: tasmlist; const s: string; weak : boolean); override;
  45. procedure a_call_reg(list: tasmlist; Reg: TRegister); override;
  46. procedure a_call_sym_pic(list: tasmlist; sym: tasmsymbol);
  47. { General purpose instructions }
  48. procedure a_op_const_reg(list: tasmlist; Op: TOpCG; size: tcgsize; a: tcgint; reg: TRegister); override;
  49. procedure a_op_reg_reg(list: tasmlist; Op: TOpCG; size: TCGSize; src, dst: TRegister); override;
  50. procedure a_op_const_reg_reg(list: tasmlist; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister); override;
  51. procedure a_op_reg_reg_reg(list: tasmlist; op: TOpCg; size: tcgsize; src1, src2, dst: tregister); override;
  52. procedure a_op_const_reg_reg_checkoverflow(list: tasmlist; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister; setflags: boolean; var ovloc: tlocation); override;
  53. procedure a_op_reg_reg_reg_checkoverflow(list: tasmlist; op: TOpCg; size: tcgsize; src1, src2, dst: tregister; setflags: boolean; var ovloc: tlocation); override;
  54. { move instructions }
  55. procedure a_load_const_reg(list: tasmlist; size: tcgsize; a: tcgint; reg: tregister); override;
  56. procedure a_load_const_ref(list: tasmlist; size: tcgsize; a: tcgint; const ref: TReference); override;
  57. procedure a_load_reg_ref(list: tasmlist; FromSize, ToSize: TCgSize; reg: TRegister; const ref: TReference); override;
  58. procedure a_load_ref_reg(list: tasmlist; FromSize, ToSize: TCgSize; const ref: TReference; reg: tregister); override;
  59. procedure a_load_reg_reg(list: tasmlist; FromSize, ToSize: TCgSize; reg1, reg2: tregister); override;
  60. procedure a_loadaddr_ref_reg(list: tasmlist; const ref: TReference; r: tregister); override;
  61. { fpu move instructions }
  62. procedure a_loadfpu_reg_reg(list: tasmlist; fromsize, tosize: tcgsize; reg1, reg2: tregister); override;
  63. procedure a_loadfpu_ref_reg(list: tasmlist; fromsize, tosize: tcgsize; const ref: TReference; reg: tregister); override;
  64. procedure a_loadfpu_reg_ref(list: tasmlist; fromsize, tosize: tcgsize; reg: tregister; const ref: TReference); override;
  65. { comparison operations }
  66. procedure a_cmp_const_reg_label(list: tasmlist; size: tcgsize; cmp_op: topcmp; a: tcgint; reg: tregister; l: tasmlabel); override;
  67. procedure a_cmp_reg_reg_label(list: tasmlist; size: tcgsize; cmp_op: topcmp; reg1, reg2: tregister; l: tasmlabel); override;
  68. procedure a_jmp_flags(list: tasmlist; const f: TResFlags; l: tasmlabel); override;
  69. procedure g_flags2reg(list: tasmlist; size: TCgSize; const f: TResFlags; reg: tregister); override;
  70. procedure a_jmp_always(List: tasmlist; l: TAsmLabel); override;
  71. procedure a_jmp_name(list: tasmlist; const s: string); override;
  72. procedure a_mul_reg_reg_pair(list: tasmlist; size: tcgsize; src1,src2,dstlo,dsthi: tregister); override;
  73. procedure g_overflowCheck(List: tasmlist; const Loc: TLocation; def: TDef); override;
  74. procedure g_overflowCheck_loc(List: tasmlist; const Loc: TLocation; def: TDef; ovloc: tlocation); override;
  75. procedure g_proc_entry(list: tasmlist; localsize: longint; nostackframe: boolean); override;
  76. procedure g_proc_exit(list: tasmlist; parasize: longint; nostackframe: boolean); override;
  77. procedure g_concatcopy(list: tasmlist; const Source, dest: treference; len: tcgint); override;
  78. procedure g_concatcopy_unaligned(list: tasmlist; const Source, dest: treference; len: tcgint); override;
  79. procedure g_concatcopy_move(list: tasmlist; const Source, dest: treference; len: tcgint);
  80. procedure g_adjust_self_value(list:TAsmList;procdef: tprocdef;ioffset: tcgint); override;
  81. procedure g_profilecode(list: TAsmList);override;
  82. end;
  83. {$ifndef mips64}
  84. TCg64MPSel = class(tcg64f32)
  85. public
  86. procedure a_load64_reg_ref(list: tasmlist; reg: tregister64; const ref: treference); override;
  87. procedure a_load64_ref_reg(list: tasmlist; const ref: treference; reg: tregister64); override;
  88. procedure a_load64_ref_cgpara(list: tasmlist; const r: treference; const paraloc: tcgpara); override;
  89. procedure a_op64_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; regsrc, regdst: TRegister64); override;
  90. procedure a_op64_const_reg(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regdst: TRegister64); override;
  91. procedure a_op64_const_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regsrc, regdst: tregister64); override;
  92. procedure a_op64_reg_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; regsrc1, regsrc2, regdst: tregister64); override;
  93. procedure a_op64_const_reg_reg_checkoverflow(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regsrc, regdst: tregister64; setflags: boolean; var ovloc: tlocation); override;
  94. procedure a_op64_reg_reg_reg_checkoverflow(list: tasmlist; op: TOpCG; size: tcgsize; regsrc1, regsrc2, regdst: tregister64; setflags: boolean; var ovloc: tlocation); override;
  95. end;
  96. {$endif mips64}
  97. procedure create_codegen;
  98. const
  99. TOpCmp2AsmCond : array[topcmp] of TAsmCond=(C_NONE,
  100. C_EQ,C_GT,C_LT,C_GE,C_LE,C_NE,C_LEU,C_LTU,C_GEU,C_GTU
  101. );
  102. implementation
  103. uses
  104. globals, verbose, systems, cutils,
  105. paramgr, fmodule,
  106. symtable, symsym,
  107. tgobj,
  108. procinfo, cpupi;
  109. const
  110. TOpcg2AsmOp: array[TOpCg] of TAsmOp = (
  111. A_NONE,A_NONE,A_ADDU,A_AND,A_NONE,A_NONE,A_MULT,A_MULTU,A_NONE,A_NONE,
  112. A_OR,A_SRAV,A_SLLV,A_SRLV,A_SUBU,A_XOR,A_NONE,A_NONE
  113. );
  114. procedure TCGMIPS.make_simple_ref(list: tasmlist; var ref: treference);
  115. var
  116. tmpreg, tmpreg1: tregister;
  117. tmpref: treference;
  118. base_replaced: boolean;
  119. begin
  120. { Enforce some discipline for callers:
  121. - gp is always implicit
  122. - reference is processed only once }
  123. if (ref.base=NR_GP) or (ref.index=NR_GP) then
  124. InternalError(2013022801);
  125. if (ref.refaddr<>addr_no) then
  126. InternalError(2013022802);
  127. { fixup base/index, if both are present then add them together }
  128. base_replaced:=false;
  129. tmpreg:=ref.base;
  130. if (tmpreg=NR_NO) then
  131. tmpreg:=ref.index
  132. else if (ref.index<>NR_NO) then
  133. begin
  134. tmpreg:=getintregister(list,OS_ADDR);
  135. list.concat(taicpu.op_reg_reg_reg(A_ADDU,tmpreg,ref.base,ref.index));
  136. base_replaced:=true;
  137. end;
  138. ref.base:=tmpreg;
  139. ref.index:=NR_NO;
  140. if (ref.symbol=nil) and
  141. (ref.offset>=simm16lo) and
  142. (ref.offset<=simm16hi-sizeof(pint)) then
  143. exit;
  144. { Symbol present or offset > 16bits }
  145. if assigned(ref.symbol) then
  146. begin
  147. ref.base:=getintregister(list,OS_ADDR);
  148. reference_reset_symbol(tmpref,ref.symbol,ref.offset,ref.alignment,ref.volatility);
  149. if (cs_create_pic in current_settings.moduleswitches) then
  150. begin
  151. if not (pi_needs_got in current_procinfo.flags) then
  152. InternalError(2013060102);
  153. { For PIC global symbols offset must be handled separately.
  154. Otherwise (non-PIC or local symbols) offset can be encoded
  155. into relocation even if exceeds 16 bits. }
  156. if (ref.symbol.bind<>AB_LOCAL) then
  157. tmpref.offset:=0;
  158. tmpref.refaddr:=addr_pic;
  159. tmpref.base:=NR_GP;
  160. list.concat(taicpu.op_reg_ref(A_LW,ref.base,tmpref));
  161. end
  162. else
  163. begin
  164. tmpref.refaddr:=addr_high;
  165. list.concat(taicpu.op_reg_ref(A_LUI,ref.base,tmpref));
  166. end;
  167. { Add original base/index, if any. }
  168. if (tmpreg<>NR_NO) then
  169. list.concat(taicpu.op_reg_reg_reg(A_ADDU,ref.base,tmpreg,ref.base));
  170. if (ref.symbol.bind=AB_LOCAL) or
  171. not (cs_create_pic in current_settings.moduleswitches) then
  172. begin
  173. ref.refaddr:=addr_low;
  174. exit;
  175. end;
  176. { PIC global symbol }
  177. ref.symbol:=nil;
  178. if (ref.offset>=simm16lo) and
  179. (ref.offset<=simm16hi-sizeof(pint)) then
  180. exit;
  181. { fallthrough to the case of large offset }
  182. end;
  183. tmpreg1:=getintregister(list,OS_INT);
  184. a_load_const_reg(list,OS_INT,ref.offset,tmpreg1);
  185. if (ref.base=NR_NO) then
  186. ref.base:=tmpreg1 { offset alone, weird but possible }
  187. else
  188. begin
  189. tmpreg:=ref.base;
  190. if (not base_replaced) then
  191. ref.base:=getintregister(list,OS_ADDR);
  192. list.concat(taicpu.op_reg_reg_reg(A_ADDU,ref.base,tmpreg,tmpreg1))
  193. end;
  194. ref.offset:=0;
  195. end;
  196. procedure TCGMIPS.handle_reg_const_reg(list: tasmlist; op: Tasmop; src: tregister; a: tcgint; dst: tregister);
  197. var
  198. tmpreg: tregister;
  199. op2: Tasmop;
  200. negate: boolean;
  201. begin
  202. case op of
  203. A_ADD,A_SUB:
  204. op2:=A_ADDI;
  205. A_ADDU,A_SUBU:
  206. op2:=A_ADDIU;
  207. else
  208. InternalError(2013052001);
  209. end;
  210. negate:=op in [A_SUB,A_SUBU];
  211. { subtraction is actually addition of negated value, so possible range is
  212. off by one (-32767..32768) }
  213. if (a < simm16lo+ord(negate)) or
  214. (a > simm16hi+ord(negate)) then
  215. begin
  216. tmpreg := GetIntRegister(list, OS_INT);
  217. a_load_const_reg(list, OS_INT, a, tmpreg);
  218. list.concat(taicpu.op_reg_reg_reg(op, dst, src, tmpreg));
  219. end
  220. else
  221. begin
  222. if negate then
  223. a:=-a;
  224. list.concat(taicpu.op_reg_reg_const(op2, dst, src, a));
  225. end;
  226. end;
  227. {****************************************************************************
  228. Assembler code
  229. ****************************************************************************}
  230. procedure TCGMIPS.init_register_allocators;
  231. begin
  232. inherited init_register_allocators;
  233. { Keep RS_R25, i.e. $t9 for PIC call }
  234. if (cs_create_pic in current_settings.moduleswitches) and assigned(current_procinfo) and
  235. (pi_needs_got in current_procinfo.flags) then
  236. begin
  237. current_procinfo.got := NR_GP;
  238. rg[R_INTREGISTER] := Trgintcpu.Create(R_INTREGISTER, R_SUBD,
  239. [RS_R2,RS_R3,RS_R4,RS_R5,RS_R6,RS_R7,RS_R8,RS_R9,
  240. RS_R10,RS_R11,RS_R12,RS_R13,RS_R14,RS_R15,RS_R16,RS_R17,RS_R18,RS_R19,
  241. RS_R20,RS_R21,RS_R22,RS_R23,RS_R24{,RS_R25}],
  242. first_int_imreg, []);
  243. end
  244. else
  245. rg[R_INTREGISTER] := trgintcpu.Create(R_INTREGISTER, R_SUBD,
  246. [RS_R2,RS_R3,RS_R4,RS_R5,RS_R6,RS_R7,RS_R8,RS_R9,
  247. RS_R10,RS_R11,RS_R12,RS_R13,RS_R14,RS_R15,RS_R16,RS_R17,RS_R18,RS_R19,
  248. RS_R20,RS_R21,RS_R22,RS_R23,RS_R24{,RS_R25}],
  249. first_int_imreg, []);
  250. {
  251. rg[R_FPUREGISTER] := trgcpu.Create(R_FPUREGISTER, R_SUBFS,
  252. [RS_F0,RS_F1,RS_F2,RS_F3,RS_F4,RS_F5,RS_F6,RS_F7,
  253. RS_F8,RS_F9,RS_F10,RS_F11,RS_F12,RS_F13,RS_F14,RS_F15,
  254. RS_F16,RS_F17,RS_F18,RS_F19,RS_F20,RS_F21,RS_F22,RS_F23,
  255. RS_F24,RS_F25,RS_F26,RS_F27,RS_F28,RS_F29,RS_F30,RS_F31],
  256. first_fpu_imreg, []);
  257. }
  258. rg[R_FPUREGISTER] := trgcpu.Create(R_FPUREGISTER, R_SUBFS,
  259. [RS_F0,RS_F2,RS_F4,RS_F6, RS_F8,RS_F10,RS_F12,RS_F14,
  260. RS_F16,RS_F18,RS_F20,RS_F22, RS_F24,RS_F26,RS_F28,RS_F30],
  261. first_fpu_imreg, []);
  262. end;
  263. procedure TCGMIPS.done_register_allocators;
  264. begin
  265. rg[R_INTREGISTER].Free;
  266. rg[R_FPUREGISTER].Free;
  267. inherited done_register_allocators;
  268. end;
  269. procedure TCGMIPS.a_loadfpu_ref_cgpara(list: tasmlist; size: tcgsize; const ref: treference; const paraloc: TCGPara);
  270. var
  271. href, href2: treference;
  272. hloc: pcgparalocation;
  273. begin
  274. { TODO: inherited cannot deal with individual locations for each of OS_32 registers.
  275. Must change parameter management to allocate a single 64-bit register pair,
  276. then this method can be removed. }
  277. href := ref;
  278. hloc := paraloc.location;
  279. while assigned(hloc) do
  280. begin
  281. paramanager.allocparaloc(list,hloc);
  282. case hloc^.loc of
  283. LOC_REGISTER:
  284. a_load_ref_reg(list, hloc^.size, hloc^.size, href, hloc^.Register);
  285. LOC_FPUREGISTER,LOC_CFPUREGISTER :
  286. a_loadfpu_ref_reg(list,hloc^.size,hloc^.size,href,hloc^.register);
  287. LOC_REFERENCE:
  288. begin
  289. paraloc.check_simple_location;
  290. reference_reset_base(href2,paraloc.location^.reference.index,paraloc.location^.reference.offset,ctempposinvalid,paraloc.alignment,[]);
  291. { concatcopy should choose the best way to copy the data }
  292. g_concatcopy(list,ref,href2,tcgsize2size[size]);
  293. end;
  294. else
  295. internalerror(200408241);
  296. end;
  297. Inc(href.offset, tcgsize2size[hloc^.size]);
  298. hloc := hloc^.Next;
  299. end;
  300. end;
  301. procedure TCGMIPS.a_loadfpu_reg_cgpara(list: tasmlist; size: tcgsize; const r: tregister; const paraloc: TCGPara);
  302. var
  303. href: treference;
  304. begin
  305. if paraloc.Location^.next=nil then
  306. begin
  307. inherited a_loadfpu_reg_cgpara(list,size,r,paraloc);
  308. exit;
  309. end;
  310. tg.GetTemp(list, TCGSize2Size[size], TCGSize2Size[size], tt_normal, href);
  311. a_loadfpu_reg_ref(list, size, size, r, href);
  312. a_loadfpu_ref_cgpara(list, size, href, paraloc);
  313. tg.Ungettemp(list, href);
  314. end;
  315. procedure TCGMIPS.a_call_sym_pic(list: tasmlist; sym: tasmsymbol);
  316. var
  317. href: treference;
  318. begin
  319. reference_reset_symbol(href,sym,0,sizeof(aint),[]);
  320. if (sym.bind=AB_LOCAL) then
  321. href.refaddr:=addr_pic
  322. else
  323. href.refaddr:=addr_pic_call16;
  324. href.base:=NR_GP;
  325. list.concat(taicpu.op_reg_ref(A_LW,NR_PIC_FUNC,href));
  326. if (sym.bind=AB_LOCAL) then
  327. begin
  328. href.refaddr:=addr_low;
  329. href.base:=NR_NO;
  330. list.concat(taicpu.op_reg_ref(A_ADDIU,NR_PIC_FUNC,href));
  331. end;
  332. list.concat(taicpu.op_reg(A_JALR,NR_PIC_FUNC));
  333. { Delay slot }
  334. list.concat(taicpu.op_none(A_NOP));
  335. { Restore GP if in PIC mode }
  336. if (cs_create_pic in current_settings.moduleswitches) then
  337. begin
  338. if tcpuprocinfo(current_procinfo).save_gp_ref.offset=0 then
  339. InternalError(2013071001);
  340. list.concat(taicpu.op_reg_ref(A_LW,NR_GP,tcpuprocinfo(current_procinfo).save_gp_ref));
  341. end;
  342. end;
  343. procedure TCGMIPS.a_call_name(list: tasmlist; const s: string; weak: boolean);
  344. var
  345. sym: tasmsymbol;
  346. begin
  347. if assigned(current_procinfo) and
  348. not (pi_do_call in current_procinfo.flags) then
  349. InternalError(2013022101);
  350. if weak then
  351. sym:=current_asmdata.WeakRefAsmSymbol(s,AT_FUNCTION)
  352. else
  353. sym:=current_asmdata.RefAsmSymbol(s,AT_FUNCTION);
  354. if (cs_create_pic in current_settings.moduleswitches) then
  355. a_call_sym_pic(list,sym)
  356. else
  357. begin
  358. list.concat(taicpu.op_sym(A_JAL,sym));
  359. { Delay slot }
  360. list.concat(taicpu.op_none(A_NOP));
  361. end;
  362. end;
  363. procedure TCGMIPS.a_call_reg(list: tasmlist; Reg: TRegister);
  364. begin
  365. if assigned(current_procinfo) and
  366. not (pi_do_call in current_procinfo.flags) then
  367. InternalError(2013022102);
  368. if (Reg <> NR_PIC_FUNC) then
  369. list.concat(taicpu.op_reg_reg(A_MOVE,NR_PIC_FUNC,reg));
  370. list.concat(taicpu.op_reg(A_JALR,NR_PIC_FUNC));
  371. { Delay slot }
  372. list.concat(taicpu.op_none(A_NOP));
  373. { Restore GP if in PIC mode }
  374. if (cs_create_pic in current_settings.moduleswitches) then
  375. begin
  376. if tcpuprocinfo(current_procinfo).save_gp_ref.offset=0 then
  377. InternalError(2013071002);
  378. list.concat(taicpu.op_reg_ref(A_LW,NR_GP,tcpuprocinfo(current_procinfo).save_gp_ref));
  379. end;
  380. end;
  381. {********************** load instructions ********************}
  382. procedure TCGMIPS.a_load_const_reg(list: tasmlist; size: TCGSize; a: tcgint; reg: TRegister);
  383. begin
  384. if (a = 0) then
  385. a_load_reg_reg(list, OS_INT, OS_INT, NR_R0, reg)
  386. else if (a >= simm16lo) and (a <= simm16hi) then
  387. list.concat(taicpu.op_reg_reg_const(A_ADDIU, reg, NR_R0, a))
  388. else if (a>=0) and (a <= 65535) then
  389. list.concat(taicpu.op_reg_reg_const(A_ORI, reg, NR_R0, a))
  390. {$ifdef mips32}
  391. else
  392. {$else}
  393. else if (a>=0) and (a <= high(dword)) then
  394. {$endif}
  395. begin
  396. list.concat(taicpu.op_reg_const(A_LUI, reg, aint(a) shr 16));
  397. if (a and aint($FFFF))<>0 then
  398. list.concat(taicpu.op_reg_reg_const(A_ORI,reg,reg,a and aint($FFFF)));
  399. {$ifdef mips64}
  400. end
  401. else
  402. begin
  403. list.concat(taicpu.op_reg_const(A_LUI, reg, aint(a) shr 48));
  404. if ((a shr 32) and aint($FFFF))<>0 then
  405. list.concat(taicpu.op_reg_reg_const(A_ORI,reg,reg,(a shr 32) and aint($FFFF)));
  406. list.concat(taicpu.op_reg_reg_const(A_SLL, reg, reg, 16));
  407. if ((a shr 16) and aint($FFFF))<>0 then
  408. list.concat(taicpu.op_reg_reg_const(A_ORI,reg,reg,(a shr 16) and aint($FFFF)));
  409. list.concat(taicpu.op_reg_reg_const(A_SLL, reg, reg, 16));
  410. if (a and aint($FFFF))<>0 then
  411. list.concat(taicpu.op_reg_reg_const(A_ORI,reg,reg,a and aint($FFFF)));
  412. {$endif mips64}
  413. end;
  414. end;
  415. procedure TCGMIPS.a_load_const_ref(list: tasmlist; size: tcgsize; a: tcgint; const ref: TReference);
  416. begin
  417. if a = 0 then
  418. a_load_reg_ref(list, size, size, NR_R0, ref)
  419. else
  420. inherited a_load_const_ref(list, size, a, ref);
  421. end;
  422. procedure TCGMIPS.a_load_reg_ref(list: tasmlist; FromSize, ToSize: TCGSize; reg: tregister; const Ref: TReference);
  423. var
  424. op: tasmop;
  425. href: treference;
  426. begin
  427. if (TCGSize2Size[fromsize] < TCGSize2Size[tosize]) then
  428. a_load_reg_reg(list,fromsize,tosize,reg,reg);
  429. if (ref.alignment<>0) and
  430. (ref.alignment<tcgsize2size[tosize]) then
  431. begin
  432. a_load_reg_ref_unaligned(list,FromSize,ToSize,reg,ref);
  433. exit;
  434. end;
  435. case tosize of
  436. OS_8,
  437. OS_S8:
  438. Op := A_SB;
  439. OS_16,
  440. OS_S16:
  441. Op := A_SH;
  442. OS_32,
  443. OS_S32:
  444. Op := A_SW;
  445. OS_64,
  446. OS_S64:
  447. Op := A_SD;
  448. else
  449. InternalError(2002122100);
  450. end;
  451. href:=ref;
  452. make_simple_ref(list,href);
  453. list.concat(taicpu.op_reg_ref(op,reg,href));
  454. end;
  455. procedure TCGMIPS.a_load_ref_reg(list: tasmlist; FromSize, ToSize: TCgSize; const ref: TReference; reg: tregister);
  456. var
  457. op: tasmop;
  458. href: treference;
  459. begin
  460. if (TCGSize2Size[fromsize] >= TCGSize2Size[tosize]) then
  461. fromsize := tosize;
  462. if (ref.alignment<>0) and
  463. (ref.alignment<min(tcgsize2size[fromsize],sizeof(aint))) then
  464. begin
  465. a_load_ref_reg_unaligned(list,FromSize,ToSize,ref,reg);
  466. exit;
  467. end;
  468. case fromsize of
  469. OS_S8:
  470. Op := A_LB;{Load Signed Byte}
  471. OS_8:
  472. Op := A_LBU;{Load Unsigned Byte}
  473. OS_S16:
  474. Op := A_LH;{Load Signed Halfword}
  475. OS_16:
  476. Op := A_LHU;{Load Unsigned Halfword}
  477. OS_S32:
  478. Op := A_LW;{Load Word}
  479. OS_32:
  480. Op := A_LW;//A_LWU;{Load Unsigned Word}
  481. OS_S64,
  482. OS_64:
  483. Op := A_LD;{Load a Long Word}
  484. else
  485. InternalError(2002122101);
  486. end;
  487. href:=ref;
  488. make_simple_ref(list,href);
  489. list.concat(taicpu.op_reg_ref(op,reg,href));
  490. if (fromsize=OS_S8) and (tosize=OS_16) then
  491. a_load_reg_reg(list,fromsize,tosize,reg,reg);
  492. end;
  493. procedure TCGMIPS.a_load_reg_reg(list: tasmlist; fromsize, tosize: tcgsize; reg1, reg2: tregister);
  494. var
  495. instr: taicpu;
  496. done: boolean;
  497. begin
  498. if (tcgsize2size[tosize] < tcgsize2size[fromsize]) or
  499. (
  500. (tcgsize2size[tosize] = tcgsize2size[fromsize]) and (tosize <> fromsize)
  501. ) or ((fromsize = OS_S8) and
  502. (tosize = OS_16)) then
  503. begin
  504. done:=true;
  505. case tosize of
  506. OS_8:
  507. list.concat(taicpu.op_reg_reg_const(A_ANDI, reg2, reg1, $ff));
  508. OS_16:
  509. list.concat(taicpu.op_reg_reg_const(A_ANDI, reg2, reg1, $ffff));
  510. {$ifdef cpu64bitalu}
  511. OS_64,
  512. OS_S64,
  513. {$endif cpu64bitalu}
  514. OS_32,
  515. OS_S32:
  516. done:=false;
  517. OS_S8:
  518. begin
  519. if (CPUMIPS_HAS_ISA32R2 in cpu_capabilities[current_settings.cputype]) then
  520. list.concat(taicpu.op_reg_reg(A_SEB,reg2,reg1))
  521. else
  522. begin
  523. list.concat(taicpu.op_reg_reg_const(A_SLL, reg2, reg1, 24));
  524. list.concat(taicpu.op_reg_reg_const(A_SRA, reg2, reg2, 24));
  525. end;
  526. end;
  527. OS_S16:
  528. begin
  529. if (CPUMIPS_HAS_ISA32R2 in cpu_capabilities[current_settings.cputype]) then
  530. list.concat(taicpu.op_reg_reg(A_SEH,reg2,reg1))
  531. else
  532. begin
  533. list.concat(taicpu.op_reg_reg_const(A_SLL, reg2, reg1, 16));
  534. list.concat(taicpu.op_reg_reg_const(A_SRA, reg2, reg2, 16));
  535. end;
  536. end;
  537. else
  538. internalerror(2002090901);
  539. end;
  540. end
  541. else
  542. done:=false;
  543. if (not done) and (reg1 <> reg2) then
  544. begin
  545. { same size, only a register mov required }
  546. instr := taicpu.op_reg_reg(A_MOVE, reg2, reg1);
  547. list.Concat(instr);
  548. { Notify the register allocator that we have written a move instruction so
  549. it can try to eliminate it. }
  550. add_move_instruction(instr);
  551. end;
  552. end;
  553. procedure TCGMIPS.a_loadaddr_ref_reg(list: tasmlist; const ref: TReference; r: tregister);
  554. var
  555. href: treference;
  556. hreg: tregister;
  557. begin
  558. { Enforce some discipline for callers:
  559. - reference must be a "raw" one and not use gp }
  560. if (ref.base=NR_GP) or (ref.index=NR_GP) then
  561. InternalError(2013022803);
  562. if (ref.refaddr<>addr_no) then
  563. InternalError(2013022804);
  564. if (ref.base=NR_NO) and (ref.index<>NR_NO) then
  565. InternalError(200306171);
  566. if (ref.symbol=nil) then
  567. begin
  568. if (ref.base<>NR_NO) then
  569. begin
  570. if (ref.offset<simm16lo) or (ref.offset>simm16hi) then
  571. begin
  572. hreg:=getintregister(list,OS_INT);
  573. a_load_const_reg(list,OS_INT,ref.offset,hreg);
  574. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,ref.base,hreg));
  575. end
  576. else if (ref.offset<>0) then
  577. list.concat(taicpu.op_reg_reg_const(A_ADDIU,r,ref.base,ref.offset))
  578. else
  579. a_load_reg_reg(list,OS_INT,OS_INT,ref.base,r); { emit optimizable move }
  580. if (ref.index<>NR_NO) then
  581. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,ref.index));
  582. end
  583. else
  584. a_load_const_reg(list,OS_INT,ref.offset,r);
  585. exit;
  586. end;
  587. reference_reset_symbol(href,ref.symbol,ref.offset,ref.alignment,ref.volatility);
  588. if (cs_create_pic in current_settings.moduleswitches) then
  589. begin
  590. if not (pi_needs_got in current_procinfo.flags) then
  591. InternalError(2013060104);
  592. { For PIC global symbols offset must be handled separately.
  593. Otherwise (non-PIC or local symbols) offset can be encoded
  594. into relocation even if exceeds 16 bits. }
  595. if (href.symbol.bind<>AB_LOCAL) then
  596. href.offset:=0;
  597. href.refaddr:=addr_pic;
  598. href.base:=NR_GP;
  599. list.concat(taicpu.op_reg_ref(A_LW,r,href));
  600. end
  601. else
  602. begin
  603. href.refaddr:=addr_high;
  604. list.concat(taicpu.op_reg_ref(A_LUI,r,href));
  605. end;
  606. { Add original base/index, if any. }
  607. if (ref.base<>NR_NO) then
  608. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,ref.base));
  609. if (ref.index<>NR_NO) then
  610. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,ref.index));
  611. { add low part if necessary }
  612. if (ref.symbol.bind=AB_LOCAL) or
  613. not (cs_create_pic in current_settings.moduleswitches) then
  614. begin
  615. href.refaddr:=addr_low;
  616. href.base:=NR_NO;
  617. list.concat(taicpu.op_reg_reg_ref(A_ADDIU,r,r,href));
  618. exit;
  619. end;
  620. if (ref.offset<simm16lo) or (ref.offset>simm16hi) then
  621. begin
  622. hreg:=getintregister(list,OS_INT);
  623. a_load_const_reg(list,OS_INT,ref.offset,hreg);
  624. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,hreg));
  625. end
  626. else if (ref.offset<>0) then
  627. list.concat(taicpu.op_reg_reg_const(A_ADDIU,r,r,ref.offset));
  628. end;
  629. procedure TCGMIPS.a_loadfpu_reg_reg(list: tasmlist; fromsize, tosize: tcgsize; reg1, reg2: tregister);
  630. const
  631. FpuMovInstr: array[OS_F32..OS_F64,OS_F32..OS_F64] of TAsmOp =
  632. ((A_MOV_S, A_CVT_D_S),(A_CVT_S_D,A_MOV_D));
  633. var
  634. instr: taicpu;
  635. begin
  636. if (reg1 <> reg2) or (fromsize<>tosize) then
  637. begin
  638. instr := taicpu.op_reg_reg(fpumovinstr[fromsize,tosize], reg2, reg1);
  639. list.Concat(instr);
  640. { Notify the register allocator that we have written a move instruction so
  641. it can try to eliminate it. }
  642. if (fromsize=tosize) then
  643. add_move_instruction(instr);
  644. end;
  645. end;
  646. procedure TCGMIPS.a_loadfpu_ref_reg(list: tasmlist; fromsize, tosize: tcgsize; const ref: TReference; reg: tregister);
  647. var
  648. href: TReference;
  649. begin
  650. href:=ref;
  651. make_simple_ref(list,href);
  652. case fromsize of
  653. OS_F32:
  654. list.concat(taicpu.op_reg_ref(A_LWC1,reg,href));
  655. OS_F64:
  656. list.concat(taicpu.op_reg_ref(A_LDC1,reg,href));
  657. else
  658. InternalError(2007042701);
  659. end;
  660. if tosize<>fromsize then
  661. a_loadfpu_reg_reg(list,fromsize,tosize,reg,reg);
  662. end;
  663. procedure TCGMIPS.a_loadfpu_reg_ref(list: tasmlist; fromsize, tosize: tcgsize; reg: tregister; const ref: TReference);
  664. var
  665. href: TReference;
  666. begin
  667. if tosize<>fromsize then
  668. a_loadfpu_reg_reg(list,fromsize,tosize,reg,reg);
  669. href:=ref;
  670. make_simple_ref(list,href);
  671. case tosize of
  672. OS_F32:
  673. list.concat(taicpu.op_reg_ref(A_SWC1,reg,href));
  674. OS_F64:
  675. list.concat(taicpu.op_reg_ref(A_SDC1,reg,href));
  676. else
  677. InternalError(2007042702);
  678. end;
  679. end;
  680. procedure TCGMIPS.maybeadjustresult(list: TAsmList; op: TOpCg; size: tcgsize; dst: tregister);
  681. const
  682. overflowops = [OP_MUL,OP_SHL,OP_ADD,OP_SUB,OP_NOT,OP_NEG];
  683. begin
  684. if (op in overflowops) and
  685. (size in [OS_8,OS_S8,OS_16,OS_S16]) then
  686. a_load_reg_reg(list,OS_32,size,dst,dst);
  687. end;
  688. procedure TCGMIPS.overflowcheck_internal(list: tasmlist; arg1, arg2: tregister);
  689. var
  690. carry, hreg: tregister;
  691. begin
  692. if (arg1=arg2) then
  693. InternalError(2013050501);
  694. carry:=GetIntRegister(list,OS_INT);
  695. hreg:=GetIntRegister(list,OS_INT);
  696. list.concat(taicpu.op_reg_reg_reg(A_SLTU,carry,arg1,arg2));
  697. { if carry<>0, this will cause hardware overflow interrupt }
  698. a_load_const_reg(list,OS_INT,$80000000,hreg);
  699. list.concat(taicpu.op_reg_reg_reg(A_SUB,hreg,hreg,carry));
  700. end;
  701. const
  702. ops_add: array[boolean] of TAsmOp = (A_ADDU, A_ADD);
  703. ops_sub: array[boolean] of TAsmOp = (A_SUBU, A_SUB);
  704. ops_slt: array[boolean] of TAsmOp = (A_SLTU, A_SLT);
  705. ops_slti: array[boolean] of TAsmOp = (A_SLTIU, A_SLTI);
  706. ops_and: array[boolean] of TAsmOp = (A_AND, A_ANDI);
  707. ops_or: array[boolean] of TAsmOp = (A_OR, A_ORI);
  708. ops_xor: array[boolean] of TasmOp = (A_XOR, A_XORI);
  709. procedure TCGMIPS.a_op_const_reg(list: tasmlist; Op: TOpCG; size: tcgsize; a: tcgint; reg: TRegister);
  710. begin
  711. optimize_op_const(size,op,a);
  712. case op of
  713. OP_NONE:
  714. exit;
  715. OP_MOVE:
  716. a_load_const_reg(list,size,a,reg);
  717. OP_NEG,OP_NOT:
  718. internalerror(200306011);
  719. else
  720. a_op_const_reg_reg(list,op,size,a,reg,reg);
  721. end;
  722. end;
  723. procedure TCGMIPS.a_op_reg_reg(list: tasmlist; Op: TOpCG; size: TCGSize; src, dst: TRegister);
  724. begin
  725. case Op of
  726. OP_NEG:
  727. list.concat(taicpu.op_reg_reg_reg(A_SUBU, dst, NR_R0, src));
  728. OP_NOT:
  729. list.concat(taicpu.op_reg_reg_reg(A_NOR, dst, NR_R0, src));
  730. OP_IMUL,OP_MUL:
  731. begin
  732. list.concat(taicpu.op_reg_reg(TOpcg2AsmOp[op], dst, src));
  733. list.concat(taicpu.op_reg(A_MFLO, dst));
  734. end;
  735. else
  736. a_op_reg_reg_reg(list, op, size, src, dst, dst);
  737. exit;
  738. end;
  739. maybeadjustresult(list,op,size,dst);
  740. end;
  741. procedure TCGMIPS.a_op_const_reg_reg(list: tasmlist; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister);
  742. var
  743. l: TLocation;
  744. begin
  745. a_op_const_reg_reg_checkoverflow(list, op, size, a, src, dst, false, l);
  746. end;
  747. procedure TCGMIPS.a_op_reg_reg_reg(list: tasmlist; op: TOpCg; size: tcgsize; src1, src2, dst: tregister);
  748. begin
  749. if (TOpcg2AsmOp[op]=A_NONE) then
  750. InternalError(2013070305);
  751. if (op=OP_SAR) then
  752. begin
  753. if (size in [OS_S8,OS_S16]) then
  754. begin
  755. { Sign-extend before shiting }
  756. list.concat(taicpu.op_reg_reg_const(A_SLL, dst, src2, 32-(tcgsize2size[size]*8)));
  757. list.concat(taicpu.op_reg_reg_const(A_SRA, dst, dst, 32-(tcgsize2size[size]*8)));
  758. src2:=dst;
  759. end
  760. else if not (size in [OS_32,OS_S32]) then
  761. InternalError(2013070306);
  762. end;
  763. list.concat(taicpu.op_reg_reg_reg(TOpCG2AsmOp[op], dst, src2, src1));
  764. maybeadjustresult(list,op,size,dst);
  765. end;
  766. procedure TCGMIPS.a_op_const_reg_reg_checkoverflow(list: tasmlist; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister; setflags: boolean; var ovloc: tlocation);
  767. var
  768. signed,immed: boolean;
  769. hreg: TRegister;
  770. asmop: TAsmOp;
  771. begin
  772. a:=aint(a);
  773. ovloc.loc := LOC_VOID;
  774. optimize_op_const(size,op,a);
  775. signed:=(size in [OS_S8,OS_S16,OS_S32]);
  776. if (setflags and (not signed) and (src=dst) and (op in [OP_ADD,OP_SUB])) then
  777. hreg:=GetIntRegister(list,OS_INT)
  778. else
  779. hreg:=dst;
  780. case op of
  781. OP_NONE:
  782. a_load_reg_reg(list,size,size,src,dst);
  783. OP_MOVE:
  784. a_load_const_reg(list,size,a,dst);
  785. OP_ADD:
  786. begin
  787. handle_reg_const_reg(list,ops_add[setflags and signed],src,a,hreg);
  788. if setflags and (not signed) then
  789. overflowcheck_internal(list,hreg,src);
  790. { does nothing if hreg=dst }
  791. a_load_reg_reg(list,OS_INT,OS_INT,hreg,dst);
  792. end;
  793. OP_SUB:
  794. begin
  795. handle_reg_const_reg(list,ops_sub[setflags and signed],src,a,hreg);
  796. if setflags and (not signed) then
  797. overflowcheck_internal(list,src,hreg);
  798. a_load_reg_reg(list,OS_INT,OS_INT,hreg,dst);
  799. end;
  800. OP_MUL,OP_IMUL:
  801. begin
  802. hreg:=GetIntRegister(list,OS_INT);
  803. a_load_const_reg(list,OS_INT,a,hreg);
  804. a_op_reg_reg_reg_checkoverflow(list,op,size,src,hreg,dst,setflags,ovloc);
  805. exit;
  806. end;
  807. OP_AND,OP_OR,OP_XOR:
  808. begin
  809. { logical operations zero-extend, not sign-extend, the immediate }
  810. immed:=(a>=0) and (a<=65535);
  811. case op of
  812. OP_AND: asmop:=ops_and[immed];
  813. OP_OR: asmop:=ops_or[immed];
  814. OP_XOR: asmop:=ops_xor[immed];
  815. else
  816. InternalError(2013050401);
  817. end;
  818. if immed then
  819. list.concat(taicpu.op_reg_reg_const(asmop,dst,src,a))
  820. else
  821. begin
  822. hreg:=GetIntRegister(list,OS_INT);
  823. a_load_const_reg(list,OS_INT,a,hreg);
  824. list.concat(taicpu.op_reg_reg_reg(asmop,dst,src,hreg));
  825. end;
  826. end;
  827. OP_SHL:
  828. list.concat(taicpu.op_reg_reg_const(A_SLL,dst,src,a));
  829. OP_SHR:
  830. list.concat(taicpu.op_reg_reg_const(A_SRL,dst,src,a));
  831. OP_SAR:
  832. begin
  833. if (size in [OS_S8,OS_S16]) then
  834. begin
  835. list.concat(taicpu.op_reg_reg_const(A_SLL,dst,src,32-(tcgsize2size[size]*8)));
  836. inc(a,32-tcgsize2size[size]*8);
  837. src:=dst;
  838. end
  839. {$ifdef MIPS64}
  840. else if (size in [OS_64,OS_S64]) then
  841. list.concat(taicpu.op_reg_reg_const(A_DSRA,dst,src,a))
  842. {$endif MIPS64}
  843. else if not (size in [OS_32,OS_S32]) then
  844. InternalError(2013070303);
  845. list.concat(taicpu.op_reg_reg_const(A_SRA,dst,src,a));
  846. end;
  847. else
  848. internalerror(2007012601);
  849. end;
  850. maybeadjustresult(list,op,size,dst);
  851. end;
  852. procedure TCGMIPS.a_op_reg_reg_reg_checkoverflow(list: tasmlist; op: TOpCg; size: tcgsize; src1, src2, dst: tregister; setflags: boolean; var ovloc: tlocation);
  853. var
  854. signed: boolean;
  855. hreg,hreg2: TRegister;
  856. hl: tasmlabel;
  857. begin
  858. ovloc.loc := LOC_VOID;
  859. signed:=(size in [OS_S8,OS_S16,OS_S32]);
  860. if (setflags and (not signed) and (src2=dst) and (op in [OP_ADD,OP_SUB])) then
  861. hreg:=GetIntRegister(list,OS_INT)
  862. else
  863. hreg:=dst;
  864. case op of
  865. OP_ADD:
  866. begin
  867. list.concat(taicpu.op_reg_reg_reg(ops_add[setflags and signed], hreg, src2, src1));
  868. if setflags and (not signed) then
  869. overflowcheck_internal(list, hreg, src2);
  870. a_load_reg_reg(list, OS_INT, OS_INT, hreg, dst);
  871. end;
  872. OP_SUB:
  873. begin
  874. list.concat(taicpu.op_reg_reg_reg(ops_sub[setflags and signed], hreg, src2, src1));
  875. if setflags and (not signed) then
  876. overflowcheck_internal(list, src2, hreg);
  877. a_load_reg_reg(list, OS_INT, OS_INT, hreg, dst);
  878. end;
  879. OP_MUL,OP_IMUL:
  880. begin
  881. if (CPUMIPS_HAS_ISA32R2 in cpu_capabilities[current_settings.cputype]) and
  882. (not setflags) then
  883. { NOTE: MUL is actually mips32r1 instruction; on older cores it is handled as macro }
  884. list.concat(taicpu.op_reg_reg_reg(A_MUL,dst,src2,src1))
  885. else
  886. begin
  887. list.concat(taicpu.op_reg_reg(TOpCg2AsmOp[op], src2, src1));
  888. list.concat(taicpu.op_reg(A_MFLO, dst));
  889. if setflags then
  890. begin
  891. current_asmdata.getjumplabel(hl);
  892. hreg:=GetIntRegister(list,OS_INT);
  893. list.concat(taicpu.op_reg(A_MFHI,hreg));
  894. if (op=OP_IMUL) then
  895. begin
  896. hreg2:=GetIntRegister(list,OS_INT);
  897. list.concat(taicpu.op_reg_reg_const(A_SRA,hreg2,dst,31));
  898. a_cmp_reg_reg_label(list,OS_INT,OC_EQ,hreg2,hreg,hl);
  899. end
  900. else
  901. a_cmp_reg_reg_label(list,OS_INT,OC_EQ,hreg,NR_R0,hl);
  902. list.concat(taicpu.op_const(A_BREAK,6));
  903. a_label(list,hl);
  904. end;
  905. end;
  906. end;
  907. OP_AND,OP_OR,OP_XOR:
  908. begin
  909. list.concat(taicpu.op_reg_reg_reg(TOpCG2AsmOp[op], dst, src2, src1));
  910. end;
  911. else
  912. internalerror(2007012602);
  913. end;
  914. maybeadjustresult(list,op,size,dst);
  915. end;
  916. {*************** compare instructructions ****************}
  917. procedure TCGMIPS.a_cmp_const_reg_label(list: tasmlist; size: tcgsize; cmp_op: topcmp; a: tcgint; reg: tregister; l: tasmlabel);
  918. var
  919. tmpreg: tregister;
  920. begin
  921. if a = 0 then
  922. a_cmp_reg_reg_label(list,size,cmp_op,NR_R0,reg,l)
  923. else
  924. begin
  925. tmpreg := GetIntRegister(list,OS_INT);
  926. if (a>=simm16lo) and (a<=simm16hi) and
  927. (cmp_op in [OC_LT,OC_B,OC_GTE,OC_AE]) then
  928. begin
  929. list.concat(taicpu.op_reg_reg_const(ops_slti[cmp_op in [OC_LT,OC_GTE]],tmpreg,reg,a));
  930. if cmp_op in [OC_LT,OC_B] then
  931. a_cmp_reg_reg_label(list,size,OC_NE,NR_R0,tmpreg,l)
  932. else
  933. a_cmp_reg_reg_label(list,size,OC_EQ,NR_R0,tmpreg,l);
  934. end
  935. else
  936. begin
  937. a_load_const_reg(list,OS_INT,a,tmpreg);
  938. a_cmp_reg_reg_label(list, size, cmp_op, tmpreg, reg, l);
  939. end;
  940. end;
  941. end;
  942. const
  943. TOpCmp2AsmCond_z : array[OC_GT..OC_LTE] of TAsmCond=(
  944. C_GTZ,C_LTZ,C_GEZ,C_LEZ
  945. );
  946. TOpCmp2AsmCond_eqne: array[topcmp] of TAsmCond = (C_NONE,
  947. { eq gt lt gte lte ne }
  948. C_NONE, C_NE, C_NE, C_EQ, C_EQ, C_NONE,
  949. { be b ae a }
  950. C_EQ, C_NE, C_EQ, C_NE
  951. );
  952. procedure TCGMIPS.a_cmp_reg_reg_label(list: tasmlist; size: tcgsize; cmp_op: topcmp; reg1, reg2: tregister; l: tasmlabel);
  953. var
  954. ai : Taicpu;
  955. op: TAsmOp;
  956. hreg: TRegister;
  957. begin
  958. if not (cmp_op in [OC_EQ,OC_NE]) then
  959. begin
  960. if ((reg1=NR_R0) or (reg2=NR_R0)) and (cmp_op in [OC_GT,OC_LT,OC_GTE,OC_LTE]) then
  961. begin
  962. if (reg2=NR_R0) then
  963. begin
  964. ai:=taicpu.op_reg_sym(A_BC,reg1,l);
  965. ai.setcondition(TOpCmp2AsmCond_z[swap_opcmp(cmp_op)]);
  966. end
  967. else
  968. begin
  969. ai:=taicpu.op_reg_sym(A_BC,reg2,l);
  970. ai.setcondition(TOpCmp2AsmCond_z[cmp_op]);
  971. end;
  972. end
  973. else
  974. begin
  975. hreg:=GetIntRegister(list,OS_INT);
  976. op:=ops_slt[cmp_op in [OC_LT,OC_LTE,OC_GT,OC_GTE]];
  977. if (cmp_op in [OC_LTE,OC_GT,OC_BE,OC_A]) then { swap operands }
  978. list.concat(taicpu.op_reg_reg_reg(op,hreg,reg1,reg2))
  979. else
  980. list.concat(taicpu.op_reg_reg_reg(op,hreg,reg2,reg1));
  981. if (TOpCmp2AsmCond_eqne[cmp_op]=C_NONE) then
  982. InternalError(2013051501);
  983. ai:=taicpu.op_reg_reg_sym(A_BC,hreg,NR_R0,l);
  984. ai.SetCondition(TOpCmp2AsmCond_eqne[cmp_op]);
  985. end;
  986. end
  987. else
  988. begin
  989. ai:=taicpu.op_reg_reg_sym(A_BC,reg2,reg1,l);
  990. ai.SetCondition(TOpCmp2AsmCond[cmp_op]);
  991. end;
  992. list.concat(ai);
  993. { Delay slot }
  994. list.Concat(TAiCpu.Op_none(A_NOP));
  995. end;
  996. procedure TCGMIPS.a_jmp_always(List: tasmlist; l: TAsmLabel);
  997. var
  998. ai : Taicpu;
  999. begin
  1000. ai := taicpu.op_sym(A_BA, l);
  1001. list.concat(ai);
  1002. { Delay slot }
  1003. list.Concat(TAiCpu.Op_none(A_NOP));
  1004. end;
  1005. procedure TCGMIPS.a_jmp_name(list: tasmlist; const s: string);
  1006. begin
  1007. List.Concat(TAiCpu.op_sym(A_BA, current_asmdata.RefAsmSymbol(s,AT_FUNCTION)));
  1008. { Delay slot }
  1009. list.Concat(TAiCpu.Op_none(A_NOP));
  1010. end;
  1011. procedure TCGMIPS.a_jmp_flags(list: tasmlist; const f: TResFlags; l: tasmlabel);
  1012. var
  1013. ai: taicpu;
  1014. begin
  1015. case f.reg1 of
  1016. NR_FCC0..NR_FCC7:
  1017. begin
  1018. if (f.reg1=NR_FCC0) then
  1019. ai:=taicpu.op_sym(A_BC,l)
  1020. else
  1021. ai:=taicpu.op_reg_sym(A_BC,f.reg1,l);
  1022. list.concat(ai);
  1023. { delay slot }
  1024. list.concat(taicpu.op_none(A_NOP));
  1025. case f.cond of
  1026. OC_NE: ai.SetCondition(C_COP1TRUE);
  1027. OC_EQ: ai.SetCondition(C_COP1FALSE);
  1028. else
  1029. InternalError(2014082901);
  1030. end;
  1031. exit;
  1032. end;
  1033. else
  1034. ;
  1035. end;
  1036. if f.use_const then
  1037. a_cmp_const_reg_label(list,OS_INT,f.cond,f.value,f.reg1,l)
  1038. else
  1039. a_cmp_reg_reg_label(list,OS_INT,f.cond,f.reg2,f.reg1,l);
  1040. end;
  1041. procedure TCGMIPS.g_flags2reg(list: tasmlist; size: tcgsize; const f: tresflags; reg: tregister);
  1042. var
  1043. left,right: tregister;
  1044. unsigned: boolean;
  1045. hl: tasmlabel;
  1046. begin
  1047. case f.reg1 of
  1048. NR_FCC0..NR_FCC7:
  1049. begin
  1050. if (current_settings.cputype>=cpu_mips4) then
  1051. begin
  1052. a_load_const_reg(list,size,1,reg);
  1053. case f.cond of
  1054. OC_NE: list.concat(taicpu.op_reg_reg_reg(A_MOVF,reg,NR_R0,f.reg1));
  1055. OC_EQ: list.concat(taicpu.op_reg_reg_reg(A_MOVT,reg,NR_R0,f.reg1));
  1056. else
  1057. InternalError(2014082902);
  1058. end;
  1059. end
  1060. else
  1061. begin
  1062. { TODO: still possible to do branchless by extracting appropriate bit from FCSR? }
  1063. current_asmdata.getjumplabel(hl);
  1064. a_load_const_reg(list,size,1,reg);
  1065. a_jmp_flags(list,f,hl);
  1066. a_load_const_reg(list,size,0,reg);
  1067. a_label(list,hl);
  1068. end;
  1069. exit;
  1070. end;
  1071. else
  1072. ;
  1073. end;
  1074. if (f.cond in [OC_EQ,OC_NE]) then
  1075. begin
  1076. left:=reg;
  1077. if f.use_const and (f.value>=0) and (f.value<=65535) then
  1078. begin
  1079. if (f.value<>0) then
  1080. list.concat(taicpu.op_reg_reg_const(A_XORI,reg,f.reg1,f.value))
  1081. else
  1082. left:=f.reg1;
  1083. end
  1084. else
  1085. begin
  1086. if f.use_const then
  1087. begin
  1088. right:=GetIntRegister(list,OS_INT);
  1089. a_load_const_reg(list,OS_INT,f.value,right);
  1090. end
  1091. else
  1092. right:=f.reg2;
  1093. list.concat(taicpu.op_reg_reg_reg(A_XOR,reg,f.reg1,right));
  1094. end;
  1095. if f.cond=OC_EQ then
  1096. list.concat(taicpu.op_reg_reg_const(A_SLTIU,reg,left,1))
  1097. else
  1098. list.concat(taicpu.op_reg_reg_reg(A_SLTU,reg,NR_R0,left));
  1099. end
  1100. else
  1101. begin
  1102. {
  1103. sle x,a,b --> slt x,b,a; xori x,x,1 immediate not possible (or must be at left)
  1104. sgt x,a,b --> slt x,b,a likewise
  1105. sge x,a,b --> slt x,a,b; xori x,x,1
  1106. slt x,a,b --> unchanged
  1107. }
  1108. unsigned:=f.cond in [OC_GT,OC_LT,OC_GTE,OC_LTE];
  1109. if (f.cond in [OC_GTE,OC_LT,OC_B,OC_AE]) and
  1110. f.use_const and
  1111. (f.value>=simm16lo) and
  1112. (f.value<=simm16hi) then
  1113. list.Concat(taicpu.op_reg_reg_const(ops_slti[unsigned],reg,f.reg1,f.value))
  1114. else
  1115. begin
  1116. if f.use_const then
  1117. begin
  1118. if (f.value=0) then
  1119. right:=NR_R0
  1120. else
  1121. begin
  1122. right:=GetIntRegister(list,OS_INT);
  1123. a_load_const_reg(list,OS_INT,f.value,right);
  1124. end;
  1125. end
  1126. else
  1127. right:=f.reg2;
  1128. if (f.cond in [OC_LTE,OC_GT,OC_BE,OC_A]) then
  1129. list.Concat(taicpu.op_reg_reg_reg(ops_slt[unsigned],reg,right,f.reg1))
  1130. else
  1131. list.Concat(taicpu.op_reg_reg_reg(ops_slt[unsigned],reg,f.reg1,right));
  1132. end;
  1133. if (f.cond in [OC_LTE,OC_GTE,OC_BE,OC_AE]) then
  1134. list.Concat(taicpu.op_reg_reg_const(A_XORI,reg,reg,1));
  1135. end;
  1136. end;
  1137. procedure TCGMIPS.a_mul_reg_reg_pair(list: tasmlist; size: tcgsize; src1,src2,dstlo,dsthi: tregister);
  1138. var
  1139. asmop: tasmop;
  1140. begin
  1141. case size of
  1142. OS_32: asmop:=A_MULTU;
  1143. OS_S32: asmop:=A_MULT;
  1144. {$ifdef cpu64bitalu}
  1145. OS_64: asmop:=A_DMULTU;
  1146. OS_S64: asmop:=A_DMULT;
  1147. {$endif cpu64bitalu}
  1148. else
  1149. InternalError(2022020901);
  1150. end;
  1151. list.concat(taicpu.op_reg_reg(asmop,src1,src2));
  1152. if (dstlo<>NR_NO) then
  1153. list.concat(taicpu.op_reg(A_MFLO,dstlo));
  1154. if (dsthi<>NR_NO) then
  1155. list.concat(taicpu.op_reg(A_MFHI,dsthi));
  1156. end;
  1157. procedure TCGMIPS.g_overflowCheck(List: tasmlist; const Loc: TLocation; def: TDef);
  1158. begin
  1159. // this is an empty procedure
  1160. end;
  1161. procedure TCGMIPS.g_overflowCheck_loc(List: tasmlist; const Loc: TLocation; def: TDef; ovloc: tlocation);
  1162. begin
  1163. // this is an empty procedure
  1164. end;
  1165. { *********** entry/exit code and address loading ************ }
  1166. procedure FixupOffsets(p:TObject;arg:pointer);
  1167. var
  1168. sym: tabstractnormalvarsym absolute p;
  1169. begin
  1170. if (tsym(p).typ=paravarsym) and
  1171. (sym.localloc.loc=LOC_REFERENCE) and
  1172. (sym.localloc.reference.base=NR_FRAME_POINTER_REG) then
  1173. begin
  1174. sym.localloc.reference.base:=NR_STACK_POINTER_REG;
  1175. Inc(sym.localloc.reference.offset,PLongint(arg)^);
  1176. end;
  1177. end;
  1178. procedure TCGMIPS.g_proc_entry(list: tasmlist; localsize: longint; nostackframe: boolean);
  1179. var
  1180. lastintoffset,lastfpuoffset,
  1181. nextoffset : aint;
  1182. i : longint;
  1183. ra_save,framesave : taicpu;
  1184. fmask,mask : dword;
  1185. saveregs : tcpuregisterset;
  1186. href: treference;
  1187. reg : Tsuperregister;
  1188. helplist : TAsmList;
  1189. largeoffs : boolean;
  1190. begin
  1191. list.concat(tai_directive.create(asd_ent,current_procinfo.procdef.mangledname));
  1192. if nostackframe then
  1193. begin
  1194. list.concat(taicpu.op_none(A_P_SET_NOMIPS16));
  1195. list.concat(taicpu.op_none(A_P_SET_NOREORDER));
  1196. exit;
  1197. end;
  1198. helplist:=TAsmList.Create;
  1199. reference_reset(href,0,[]);
  1200. href.base:=NR_STACK_POINTER_REG;
  1201. fmask:=0;
  1202. nextoffset:=tcpuprocinfo(current_procinfo).floatregstart;
  1203. lastfpuoffset:=LocalSize;
  1204. for reg := RS_F0 to RS_F31 do { to check: what if F30 is double? }
  1205. begin
  1206. if reg in (rg[R_FPUREGISTER].used_in_proc-paramanager.get_volatile_registers_fpu(pocall_stdcall)) then
  1207. begin
  1208. fmask:=fmask or (longword(1) shl ord(reg));
  1209. href.offset:=nextoffset;
  1210. lastfpuoffset:=nextoffset;
  1211. helplist.concat(taicpu.op_reg_ref(A_SWC1,newreg(R_FPUREGISTER,reg,R_SUBFS),href));
  1212. inc(nextoffset,4);
  1213. { IEEE Double values are stored in floating point
  1214. register pairs f2X/f2X+1,
  1215. as the f2X+1 register is not correctly marked as used for now,
  1216. we simply assume it is also used if f2X is used
  1217. Should be fixed by a proper inclusion of f2X+1 into used_in_proc }
  1218. if (ord(reg)-ord(RS_F0)) mod 2 = 0 then
  1219. include(rg[R_FPUREGISTER].used_in_proc,succ(reg));
  1220. end;
  1221. end;
  1222. mask:=0;
  1223. nextoffset:=tcpuprocinfo(current_procinfo).intregstart;
  1224. saveregs:=rg[R_INTREGISTER].used_in_proc-paramanager.get_volatile_registers_int(pocall_stdcall);
  1225. if (current_procinfo.flags*[pi_do_call,pi_is_assembler]<>[]) then
  1226. include(saveregs,RS_R31);
  1227. if (pi_needs_stackframe in current_procinfo.flags) then
  1228. include(saveregs,RS_FRAME_POINTER_REG);
  1229. lastintoffset:=LocalSize;
  1230. framesave:=nil;
  1231. ra_save:=nil;
  1232. for reg:=RS_R1 to RS_R31 do
  1233. begin
  1234. if reg in saveregs then
  1235. begin
  1236. mask:=mask or (longword(1) shl ord(reg));
  1237. href.offset:=nextoffset;
  1238. lastintoffset:=nextoffset;
  1239. if (reg=RS_FRAME_POINTER_REG) then
  1240. framesave:=taicpu.op_reg_ref(A_SW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href)
  1241. else if (reg=RS_R31) then
  1242. ra_save:=taicpu.op_reg_ref(A_SW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href)
  1243. else
  1244. helplist.concat(taicpu.op_reg_ref(A_SW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href));
  1245. inc(nextoffset,4);
  1246. end;
  1247. end;
  1248. //list.concat(Taicpu.Op_reg_reg_const(A_ADDIU,NR_FRAME_POINTER_REG,NR_STACK_POINTER_REG,current_procinfo.para_stack_size));
  1249. list.concat(Taicpu.op_none(A_P_SET_NOMIPS16));
  1250. list.concat(Taicpu.op_reg_const_reg(A_P_FRAME,current_procinfo.framepointer,LocalSize,NR_R31));
  1251. list.concat(Taicpu.op_const_const(A_P_MASK,aint(mask),-(LocalSize-lastintoffset)));
  1252. list.concat(Taicpu.op_const_const(A_P_FMASK,aint(Fmask),-(LocalSize-lastfpuoffset)));
  1253. list.concat(Taicpu.op_none(A_P_SET_NOREORDER));
  1254. if tcpuprocinfo(current_procinfo).setnoat then
  1255. list.concat(Taicpu.op_none(A_P_SET_NOAT));
  1256. if (cs_create_pic in current_settings.moduleswitches) and
  1257. (pi_needs_got in current_procinfo.flags) then
  1258. begin
  1259. list.concat(Taicpu.op_reg(A_P_CPLOAD,NR_PIC_FUNC));
  1260. end;
  1261. if (-LocalSize >= simm16lo) and (-LocalSize <= simm16hi) then
  1262. begin
  1263. list.concat(Taicpu.op_none(A_P_SET_NOMACRO));
  1264. list.concat(Taicpu.Op_reg_reg_const(A_ADDIU,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,-LocalSize));
  1265. if assigned(ra_save) then
  1266. list.concat(ra_save);
  1267. if assigned(framesave) then
  1268. begin
  1269. list.concat(framesave);
  1270. list.concat(Taicpu.op_reg_reg_const(A_ADDIU,NR_FRAME_POINTER_REG,
  1271. NR_STACK_POINTER_REG,LocalSize));
  1272. end;
  1273. end
  1274. else
  1275. begin
  1276. a_load_const_reg(list,OS_32,-LocalSize,NR_R9);
  1277. list.concat(Taicpu.Op_reg_reg_reg(A_ADDU,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,NR_R9));
  1278. if assigned(ra_save) then
  1279. list.concat(ra_save);
  1280. if assigned(framesave) then
  1281. begin
  1282. list.concat(framesave);
  1283. list.concat(Taicpu.op_reg_reg_reg(A_SUBU,NR_FRAME_POINTER_REG,
  1284. NR_STACK_POINTER_REG,NR_R9));
  1285. end;
  1286. { The instructions before are macros that can extend to multiple instructions,
  1287. the settings of R9 to -LocalSize surely does,
  1288. but the saving of RA and FP also might, and might
  1289. even use AT register, which is why we use R9 instead of AT here for -LocalSize }
  1290. list.concat(Taicpu.op_none(A_P_SET_NOMACRO));
  1291. end;
  1292. if (cs_create_pic in current_settings.moduleswitches) and
  1293. (pi_needs_got in current_procinfo.flags) then
  1294. begin
  1295. largeoffs:=(tcpuprocinfo(current_procinfo).save_gp_ref.offset>simm16hi);
  1296. if largeoffs then
  1297. list.concat(Taicpu.op_none(A_P_SET_MACRO));
  1298. list.concat(Taicpu.op_const(A_P_CPRESTORE,tcpuprocinfo(current_procinfo).save_gp_ref.offset));
  1299. if largeoffs then
  1300. list.concat(Taicpu.op_none(A_P_SET_NOMACRO));
  1301. end;
  1302. href.base:=NR_STACK_POINTER_REG;
  1303. for i:=0 to MIPS_MAX_REGISTERS_USED_IN_CALL-1 do
  1304. if tcpuprocinfo(current_procinfo).register_used[i] then
  1305. begin
  1306. reg:=parasupregs[i];
  1307. href.offset:=i*sizeof(aint)+LocalSize;
  1308. list.concat(taicpu.op_reg_ref(A_SW, newreg(R_INTREGISTER,reg,R_SUBWHOLE), href));
  1309. end;
  1310. list.concatList(helplist);
  1311. helplist.Free;
  1312. if current_procinfo.has_nestedprocs then
  1313. current_procinfo.procdef.parast.SymList.ForEachCall(@FixupOffsets,@LocalSize);
  1314. end;
  1315. procedure TCGMIPS.g_proc_exit(list: tasmlist; parasize: longint; nostackframe: boolean);
  1316. var
  1317. href : treference;
  1318. stacksize : aint;
  1319. saveregs : tcpuregisterset;
  1320. nextoffset : aint;
  1321. reg : Tsuperregister;
  1322. begin
  1323. stacksize:=current_procinfo.calc_stackframe_size;
  1324. if nostackframe then
  1325. begin
  1326. list.concat(taicpu.op_reg(A_JR, NR_R31));
  1327. list.concat(Taicpu.op_none(A_NOP));
  1328. list.concat(Taicpu.op_none(A_P_SET_MACRO));
  1329. list.concat(Taicpu.op_none(A_P_SET_REORDER));
  1330. end
  1331. else
  1332. begin
  1333. if tcpuprocinfo(current_procinfo).save_gp_ref.offset<>0 then
  1334. tg.ungettemp(list,tcpuprocinfo(current_procinfo).save_gp_ref);
  1335. reference_reset(href,0,[]);
  1336. href.base:=NR_STACK_POINTER_REG;
  1337. nextoffset:=tcpuprocinfo(current_procinfo).floatregstart;
  1338. for reg := RS_F0 to RS_F31 do
  1339. begin
  1340. if reg in (rg[R_FPUREGISTER].used_in_proc-paramanager.get_volatile_registers_fpu(pocall_stdcall)) then
  1341. begin
  1342. href.offset:=nextoffset;
  1343. list.concat(taicpu.op_reg_ref(A_LWC1,newreg(R_FPUREGISTER,reg,R_SUBFS),href));
  1344. inc(nextoffset,4);
  1345. end;
  1346. end;
  1347. nextoffset:=tcpuprocinfo(current_procinfo).intregstart;
  1348. saveregs:=rg[R_INTREGISTER].used_in_proc-paramanager.get_volatile_registers_int(pocall_stdcall);
  1349. if (current_procinfo.flags*[pi_do_call,pi_is_assembler]<>[]) then
  1350. include(saveregs,RS_R31);
  1351. if (pi_needs_stackframe in current_procinfo.flags) then
  1352. include(saveregs,RS_FRAME_POINTER_REG);
  1353. // GP does not need to be restored on exit
  1354. for reg:=RS_R1 to RS_R31 do
  1355. begin
  1356. if reg in saveregs then
  1357. begin
  1358. href.offset:=nextoffset;
  1359. list.concat(taicpu.op_reg_ref(A_LW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href));
  1360. inc(nextoffset,sizeof(aint));
  1361. end;
  1362. end;
  1363. if (-stacksize >= simm16lo) and (-stacksize <= simm16hi) then
  1364. begin
  1365. list.concat(taicpu.op_reg(A_JR, NR_R31));
  1366. { correct stack pointer in the delay slot }
  1367. list.concat(Taicpu.Op_reg_reg_const(A_ADDIU, NR_STACK_POINTER_REG, NR_STACK_POINTER_REG, stacksize));
  1368. end
  1369. else
  1370. begin
  1371. a_load_const_reg(list,OS_32,stacksize,NR_R1);
  1372. list.concat(taicpu.op_reg(A_JR, NR_R31));
  1373. { correct stack pointer in the delay slot }
  1374. list.concat(taicpu.op_reg_reg_reg(A_ADD,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,NR_R1));
  1375. tcpuprocinfo(current_procinfo).setnoat:=true;
  1376. end;
  1377. list.concat(Taicpu.op_none(A_P_SET_MACRO));
  1378. list.concat(Taicpu.op_none(A_P_SET_REORDER));
  1379. end;
  1380. list.concat(tai_directive.create(asd_ent_end,current_procinfo.procdef.mangledname));
  1381. end;
  1382. { ************* concatcopy ************ }
  1383. procedure TCGMIPS.g_concatcopy_move(list: tasmlist; const Source, dest: treference; len: tcgint);
  1384. var
  1385. paraloc1, paraloc2, paraloc3: TCGPara;
  1386. pd: tprocdef;
  1387. begin
  1388. pd:=search_system_proc('MOVE');
  1389. paraloc1.init;
  1390. paraloc2.init;
  1391. paraloc3.init;
  1392. paramanager.getcgtempparaloc(list, pd, 1, paraloc1);
  1393. paramanager.getcgtempparaloc(list, pd, 2, paraloc2);
  1394. paramanager.getcgtempparaloc(list, pd, 3, paraloc3);
  1395. a_load_const_cgpara(list, OS_SINT, len, paraloc3);
  1396. a_loadaddr_ref_cgpara(list, dest, paraloc2);
  1397. a_loadaddr_ref_cgpara(list, Source, paraloc1);
  1398. paramanager.freecgpara(list, paraloc3);
  1399. paramanager.freecgpara(list, paraloc2);
  1400. paramanager.freecgpara(list, paraloc1);
  1401. alloccpuregisters(list, R_INTREGISTER, paramanager.get_volatile_registers_int(pocall_default));
  1402. alloccpuregisters(list, R_FPUREGISTER, paramanager.get_volatile_registers_fpu(pocall_default));
  1403. a_call_name(list, 'FPC_MOVE', false);
  1404. dealloccpuregisters(list, R_FPUREGISTER, paramanager.get_volatile_registers_fpu(pocall_default));
  1405. dealloccpuregisters(list, R_INTREGISTER, paramanager.get_volatile_registers_int(pocall_default));
  1406. paraloc3.done;
  1407. paraloc2.done;
  1408. paraloc1.done;
  1409. end;
  1410. procedure TCGMIPS.g_concatcopy(list: tasmlist; const Source, dest: treference; len: tcgint);
  1411. var
  1412. tmpreg1, hreg, countreg: TRegister;
  1413. src, dst: TReference;
  1414. lab: tasmlabel;
  1415. Count, count2: aint;
  1416. function reference_is_reusable(const ref: treference): boolean;
  1417. begin
  1418. result:=(ref.base<>NR_NO) and (ref.index=NR_NO) and
  1419. (ref.symbol=nil) and
  1420. (ref.offset>=simm16lo) and (ref.offset+len<=simm16hi);
  1421. end;
  1422. begin
  1423. if len > high(longint) then
  1424. internalerror(2002072704);
  1425. { A call (to FPC_MOVE) requires the outgoing parameter area to be properly
  1426. allocated on stack. This can only be done before tcpuprocinfo.set_first_temp_offset,
  1427. i.e. before secondpass. Other internal procedures request correct stack frame
  1428. by setting pi_do_call during firstpass, but for this particular one it is impossible.
  1429. Therefore, if the current procedure is a leaf one, we have to leave it that way. }
  1430. { anybody wants to determine a good value here :)? }
  1431. if (len > 100) and
  1432. assigned(current_procinfo) and
  1433. (pi_do_call in current_procinfo.flags) then
  1434. g_concatcopy_move(list, Source, dest, len)
  1435. else if ((source.alignment<>0) and (source.alignment<4)) or
  1436. ((dest.alignment<>0) and (dest.alignment<4)) then
  1437. g_concatcopy_unaligned(list, Source, dest, len)
  1438. else
  1439. begin
  1440. Count := len div 4;
  1441. if (count<=4) and reference_is_reusable(source) then
  1442. src:=source
  1443. else
  1444. begin
  1445. reference_reset(src,sizeof(aint),source.volatility);
  1446. { load the address of source into src.base }
  1447. src.base := GetAddressRegister(list);
  1448. a_loadaddr_ref_reg(list, Source, src.base);
  1449. end;
  1450. if (count<=4) and reference_is_reusable(dest) then
  1451. dst:=dest
  1452. else
  1453. begin
  1454. reference_reset(dst,sizeof(aint),dest.volatility);
  1455. { load the address of dest into dst.base }
  1456. dst.base := GetAddressRegister(list);
  1457. a_loadaddr_ref_reg(list, dest, dst.base);
  1458. end;
  1459. { generate a loop }
  1460. if Count > 4 then
  1461. begin
  1462. countreg := GetIntRegister(list, OS_INT);
  1463. tmpreg1 := GetIntRegister(list, OS_INT);
  1464. a_load_const_reg(list, OS_INT, Count, countreg);
  1465. current_asmdata.getjumplabel(lab);
  1466. a_label(list, lab);
  1467. list.concat(taicpu.op_reg_ref(A_LW, tmpreg1, src));
  1468. list.concat(taicpu.op_reg_ref(A_SW, tmpreg1, dst));
  1469. list.concat(taicpu.op_reg_reg_const(A_ADDIU, src.base, src.base, 4));
  1470. list.concat(taicpu.op_reg_reg_const(A_ADDIU, dst.base, dst.base, 4));
  1471. list.concat(taicpu.op_reg_reg_const(A_ADDIU, countreg, countreg, -1));
  1472. a_cmp_reg_reg_label(list,OS_INT,OC_GT,NR_R0,countreg,lab);
  1473. len := len mod 4;
  1474. end;
  1475. { unrolled loop }
  1476. Count := len div 4;
  1477. if Count > 0 then
  1478. begin
  1479. tmpreg1 := GetIntRegister(list, OS_INT);
  1480. count2:=1;
  1481. while count2 <= Count do
  1482. begin
  1483. list.concat(taicpu.op_reg_ref(A_LW, tmpreg1, src));
  1484. list.concat(taicpu.op_reg_ref(A_SW, tmpreg1, dst));
  1485. Inc(src.offset, 4);
  1486. Inc(dst.offset, 4);
  1487. Inc(count2);
  1488. end;
  1489. len := len mod 4;
  1490. end;
  1491. if (len and 4) <> 0 then
  1492. begin
  1493. hreg := GetIntRegister(list, OS_INT);
  1494. a_load_ref_reg(list, OS_32, OS_32, src, hreg);
  1495. a_load_reg_ref(list, OS_32, OS_32, hreg, dst);
  1496. Inc(src.offset, 4);
  1497. Inc(dst.offset, 4);
  1498. end;
  1499. { copy the leftovers }
  1500. if (len and 2) <> 0 then
  1501. begin
  1502. hreg := GetIntRegister(list, OS_INT);
  1503. a_load_ref_reg(list, OS_16, OS_16, src, hreg);
  1504. a_load_reg_ref(list, OS_16, OS_16, hreg, dst);
  1505. Inc(src.offset, 2);
  1506. Inc(dst.offset, 2);
  1507. end;
  1508. if (len and 1) <> 0 then
  1509. begin
  1510. hreg := GetIntRegister(list, OS_INT);
  1511. a_load_ref_reg(list, OS_8, OS_8, src, hreg);
  1512. a_load_reg_ref(list, OS_8, OS_8, hreg, dst);
  1513. end;
  1514. end;
  1515. end;
  1516. procedure TCGMIPS.g_concatcopy_unaligned(list: tasmlist; const Source, dest: treference; len: tcgint);
  1517. var
  1518. src, dst: TReference;
  1519. tmpreg1, countreg: TRegister;
  1520. i: aint;
  1521. lab: tasmlabel;
  1522. begin
  1523. if (len > 31) and
  1524. { see comment in g_concatcopy }
  1525. assigned(current_procinfo) and
  1526. (pi_do_call in current_procinfo.flags) then
  1527. g_concatcopy_move(list, Source, dest, len)
  1528. else
  1529. begin
  1530. reference_reset(src,sizeof(aint),source.volatility);
  1531. reference_reset(dst,sizeof(aint),dest.volatility);
  1532. { load the address of source into src.base }
  1533. src.base := GetAddressRegister(list);
  1534. a_loadaddr_ref_reg(list, Source, src.base);
  1535. { load the address of dest into dst.base }
  1536. dst.base := GetAddressRegister(list);
  1537. a_loadaddr_ref_reg(list, dest, dst.base);
  1538. { generate a loop }
  1539. if len > 4 then
  1540. begin
  1541. countreg := GetIntRegister(list, OS_INT);
  1542. tmpreg1 := GetIntRegister(list, OS_INT);
  1543. a_load_const_reg(list, OS_INT, len, countreg);
  1544. current_asmdata.getjumplabel(lab);
  1545. a_label(list, lab);
  1546. list.concat(taicpu.op_reg_ref(A_LBU, tmpreg1, src));
  1547. list.concat(taicpu.op_reg_ref(A_SB, tmpreg1, dst));
  1548. list.concat(taicpu.op_reg_reg_const(A_ADDIU, src.base, src.base, 1));
  1549. list.concat(taicpu.op_reg_reg_const(A_ADDIU, dst.base, dst.base, 1));
  1550. list.concat(taicpu.op_reg_reg_const(A_ADDIU, countreg, countreg, -1));
  1551. a_cmp_reg_reg_label(list,OS_INT,OC_GT,NR_R0,countreg,lab);
  1552. end
  1553. else
  1554. begin
  1555. { unrolled loop }
  1556. tmpreg1 := GetIntRegister(list, OS_INT);
  1557. i := 1;
  1558. while i <= len do
  1559. begin
  1560. list.concat(taicpu.op_reg_ref(A_LBU, tmpreg1, src));
  1561. list.concat(taicpu.op_reg_ref(A_SB, tmpreg1, dst));
  1562. Inc(src.offset);
  1563. Inc(dst.offset);
  1564. Inc(i);
  1565. end;
  1566. end;
  1567. end;
  1568. end;
  1569. procedure TCGMIPS.g_profilecode(list:TAsmList);
  1570. var
  1571. href: treference;
  1572. begin
  1573. if not (cs_create_pic in current_settings.moduleswitches) then
  1574. begin
  1575. reference_reset_symbol(href,current_asmdata.RefAsmSymbol('_gp',AT_DATA),0,sizeof(pint),[]);
  1576. a_loadaddr_ref_reg(list,href,NR_GP);
  1577. end;
  1578. list.concat(taicpu.op_reg_reg(A_MOVE,NR_R1,NR_RA));
  1579. list.concat(taicpu.op_reg_reg_const(A_ADDIU,NR_SP,NR_SP,-8));
  1580. a_call_sym_pic(list,current_asmdata.RefAsmSymbol('_mcount',AT_FUNCTION));
  1581. tcpuprocinfo(current_procinfo).setnoat:=true;
  1582. end;
  1583. procedure TCGMIPS.g_adjust_self_value(list:TAsmList;procdef: tprocdef;ioffset: tcgint);
  1584. begin
  1585. { This method is integrated into g_intf_wrapper and shouldn't be called separately }
  1586. InternalError(2013020102);
  1587. end;
  1588. {$ifndef mips64}
  1589. {****************************************************************************
  1590. TCG64_MIPSel
  1591. ****************************************************************************}
  1592. procedure TCg64MPSel.a_load64_reg_ref(list: tasmlist; reg: tregister64; const ref: treference);
  1593. var
  1594. tmpref: treference;
  1595. tmpreg: tregister;
  1596. incr: shortint;
  1597. begin
  1598. tmpref := ref;
  1599. tcgmips(cg).make_simple_ref(list,tmpref);
  1600. if (ref.alignment <4) then
  1601. begin
  1602. if target_info.endian = endian_big then
  1603. begin
  1604. inc(tmpref.offset,7);
  1605. incr:=-1;
  1606. end
  1607. else
  1608. incr:=1;
  1609. list.concat(taicpu.op_reg_ref(A_SB,reg.reglo,tmpref));
  1610. Inc(tmpref.offset,incr);
  1611. list.concat(taicpu.op_reg_reg_const(A_SRL,reg.reglo,reg.reglo,8));
  1612. list.concat(taicpu.op_reg_ref(A_SB,reg.reglo,tmpref));
  1613. Inc(tmpref.offset,incr);
  1614. list.concat(taicpu.op_reg_reg_const(A_SRL,reg.reglo,reg.reglo,8));
  1615. list.concat(taicpu.op_reg_ref(A_SB,reg.reglo,tmpref));
  1616. Inc(tmpref.offset,incr);
  1617. list.concat(taicpu.op_reg_reg_const(A_SRL,reg.reglo,reg.reglo,8));
  1618. list.concat(taicpu.op_reg_ref(A_SB,reg.reglo,tmpref));
  1619. Inc(tmpref.offset,incr);
  1620. list.concat(taicpu.op_reg_ref(A_SB,reg.reghi,tmpref));
  1621. Inc(tmpref.offset,incr);
  1622. list.concat(taicpu.op_reg_reg_const(A_SRL,reg.reghi,reg.reghi,8));
  1623. list.concat(taicpu.op_reg_ref(A_SB,reg.reghi,tmpref));
  1624. Inc(tmpref.offset,incr);
  1625. list.concat(taicpu.op_reg_reg_const(A_SRL,reg.reghi,reg.reghi,8));
  1626. list.concat(taicpu.op_reg_ref(A_SB,reg.reghi,tmpref));
  1627. Inc(tmpref.offset,incr);
  1628. list.concat(taicpu.op_reg_reg_const(A_SRL,reg.reghi,reg.reghi,8));
  1629. list.concat(taicpu.op_reg_ref(A_SB,reg.reghi,tmpref));
  1630. end
  1631. else
  1632. begin
  1633. if target_info.endian = endian_big then
  1634. begin
  1635. tmpreg := reg.reglo;
  1636. reg.reglo := reg.reghi;
  1637. reg.reghi := tmpreg;
  1638. end;
  1639. list.concat(taicpu.op_reg_ref(A_SW,reg.reglo,tmpref));
  1640. Inc(tmpref.offset, 4);
  1641. list.concat(taicpu.op_reg_ref(A_SW,reg.reghi,tmpref));
  1642. end;
  1643. end;
  1644. procedure TCg64MPSel.a_load64_ref_reg(list: tasmlist; const ref: treference; reg: tregister64);
  1645. var
  1646. tmpref: treference;
  1647. tmpreg: tregister;
  1648. incr: shortint;
  1649. begin
  1650. tmpref := ref;
  1651. tcgmips(cg).make_simple_ref(list,tmpref);
  1652. if (ref.alignment <4) then
  1653. begin
  1654. tmpreg:=cg.getintregister(list,OS_INT);
  1655. if target_info.endian = endian_little then
  1656. begin
  1657. inc(tmpref.offset,7);
  1658. incr:=-1;
  1659. end
  1660. else
  1661. incr:=1;
  1662. list.concat(taicpu.op_reg_ref(A_LBU,reg.reghi,tmpref));
  1663. Inc(tmpref.offset,incr);
  1664. list.concat(taicpu.op_reg_reg_const(A_SLL,reg.reghi,reg.reghi,8));
  1665. list.concat(taicpu.op_reg_ref(A_LBU,tmpreg,tmpref));
  1666. list.concat(taicpu.op_reg_reg_reg(A_ADDU,reg.reghi,reg.reghi,tmpreg));
  1667. Inc(tmpref.offset,incr);
  1668. list.concat(taicpu.op_reg_reg_const(A_SLL,reg.reghi,reg.reghi,8));
  1669. list.concat(taicpu.op_reg_ref(A_LBU,tmpreg,tmpref));
  1670. list.concat(taicpu.op_reg_reg_reg(A_ADDU,reg.reghi,reg.reghi,tmpreg));
  1671. Inc(tmpref.offset,incr);
  1672. list.concat(taicpu.op_reg_reg_const(A_SLL,reg.reghi,reg.reghi,8));
  1673. list.concat(taicpu.op_reg_ref(A_LBU,tmpreg,tmpref));
  1674. list.concat(taicpu.op_reg_reg_reg(A_ADDU,reg.reghi,reg.reghi,tmpreg));
  1675. Inc(tmpref.offset,incr);
  1676. list.concat(taicpu.op_reg_ref(A_LBU,reg.reglo,tmpref));
  1677. Inc(tmpref.offset,incr);
  1678. list.concat(taicpu.op_reg_reg_const(A_SLL,reg.reglo,reg.reglo,8));
  1679. list.concat(taicpu.op_reg_ref(A_LBU,tmpreg,tmpref));
  1680. list.concat(taicpu.op_reg_reg_reg(A_ADDU,reg.reglo,reg.reglo,tmpreg));
  1681. Inc(tmpref.offset,incr);
  1682. list.concat(taicpu.op_reg_reg_const(A_SLL,reg.reglo,reg.reglo,8));
  1683. list.concat(taicpu.op_reg_ref(A_LBU,tmpreg,tmpref));
  1684. list.concat(taicpu.op_reg_reg_reg(A_ADDU,reg.reglo,reg.reglo,tmpreg));
  1685. Inc(tmpref.offset,incr);
  1686. list.concat(taicpu.op_reg_reg_const(A_SLL,reg.reglo,reg.reglo,8));
  1687. list.concat(taicpu.op_reg_ref(A_LBU,tmpreg,tmpref));
  1688. list.concat(taicpu.op_reg_reg_reg(A_ADDU,reg.reglo,reg.reglo,tmpreg));
  1689. Inc(tmpref.offset,incr);
  1690. end
  1691. else
  1692. begin
  1693. if target_info.endian = endian_big then
  1694. begin
  1695. tmpreg := reg.reglo;
  1696. reg.reglo := reg.reghi;
  1697. reg.reghi := tmpreg;
  1698. end;
  1699. list.concat(taicpu.op_reg_ref(A_LW,reg.reglo,tmpref));
  1700. Inc(tmpref.offset, 4);
  1701. list.concat(taicpu.op_reg_ref(A_LW,reg.reghi,tmpref));
  1702. end;
  1703. end;
  1704. procedure TCg64MPSel.a_load64_ref_cgpara(list: tasmlist; const r: treference; const paraloc: tcgpara);
  1705. var
  1706. hreg64: tregister64;
  1707. begin
  1708. { Override this function to prevent loading the reference twice.
  1709. Use here some extra registers, but those are optimized away by the RA }
  1710. hreg64.reglo := cg.GetIntRegister(list, OS_S32);
  1711. hreg64.reghi := cg.GetIntRegister(list, OS_S32);
  1712. a_load64_ref_reg(list, r, hreg64);
  1713. a_load64_reg_cgpara(list, hreg64, paraloc);
  1714. end;
  1715. procedure TCg64MPSel.a_op64_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; regsrc, regdst: TRegister64);
  1716. var
  1717. tmpreg1: TRegister;
  1718. begin
  1719. case op of
  1720. OP_NEG:
  1721. begin
  1722. tmpreg1 := cg.GetIntRegister(list, OS_INT);
  1723. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reglo, NR_R0, regsrc.reglo));
  1724. list.concat(taicpu.op_reg_reg_reg(A_SLTU, tmpreg1, NR_R0, regdst.reglo));
  1725. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reghi, NR_R0, regsrc.reghi));
  1726. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reghi, regdst.reghi, tmpreg1));
  1727. end;
  1728. OP_NOT:
  1729. begin
  1730. list.concat(taicpu.op_reg_reg_reg(A_NOR, regdst.reglo, NR_R0, regsrc.reglo));
  1731. list.concat(taicpu.op_reg_reg_reg(A_NOR, regdst.reghi, NR_R0, regsrc.reghi));
  1732. end;
  1733. else
  1734. a_op64_reg_reg_reg(list,op,size,regsrc,regdst,regdst);
  1735. end;
  1736. end;
  1737. procedure TCg64MPSel.a_op64_const_reg(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regdst: TRegister64);
  1738. begin
  1739. a_op64_const_reg_reg(list, op, size, value, regdst, regdst);
  1740. end;
  1741. procedure TCg64MPSel.a_op64_const_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regsrc, regdst: tregister64);
  1742. var
  1743. l: tlocation;
  1744. begin
  1745. a_op64_const_reg_reg_checkoverflow(list, op, size, Value, regsrc, regdst, False, l);
  1746. end;
  1747. procedure TCg64MPSel.a_op64_reg_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; regsrc1, regsrc2, regdst: tregister64);
  1748. var
  1749. l: tlocation;
  1750. begin
  1751. a_op64_reg_reg_reg_checkoverflow(list, op, size, regsrc1, regsrc2, regdst, False, l);
  1752. end;
  1753. procedure TCg64MPSel.a_op64_const_reg_reg_checkoverflow(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regsrc, regdst: tregister64; setflags: boolean; var ovloc: tlocation);
  1754. var
  1755. tmplo,carry: TRegister;
  1756. hisize: tcgsize;
  1757. begin
  1758. carry:=NR_NO;
  1759. if (size in [OS_S64]) then
  1760. hisize:=OS_S32
  1761. else
  1762. hisize:=OS_32;
  1763. case op of
  1764. OP_AND,OP_OR,OP_XOR:
  1765. begin
  1766. cg.a_op_const_reg_reg(list,op,OS_32,aint(lo(value)),regsrc.reglo,regdst.reglo);
  1767. cg.a_op_const_reg_reg(list,op,OS_32,aint(hi(value)),regsrc.reghi,regdst.reghi);
  1768. end;
  1769. OP_ADD:
  1770. begin
  1771. if lo(value)<>0 then
  1772. begin
  1773. tmplo:=cg.GetIntRegister(list,OS_32);
  1774. carry:=cg.GetIntRegister(list,OS_32);
  1775. tcgmips(cg).handle_reg_const_reg(list,A_ADDU,regsrc.reglo,aint(lo(value)),tmplo);
  1776. list.concat(taicpu.op_reg_reg_reg(A_SLTU,carry,tmplo,regsrc.reglo));
  1777. cg.a_load_reg_reg(list,OS_32,OS_32,tmplo,regdst.reglo);
  1778. end
  1779. else
  1780. cg.a_load_reg_reg(list,OS_32,OS_32,regsrc.reglo,regdst.reglo);
  1781. { With overflow checking and unsigned args, this generates slighly suboptimal code
  1782. ($80000000 constant loaded twice). Other cases are fine. Getting it perfect does not
  1783. look worth the effort. }
  1784. cg.a_op_const_reg_reg_checkoverflow(list,OP_ADD,hisize,aint(hi(value)),regsrc.reghi,regdst.reghi,setflags,ovloc);
  1785. if carry<>NR_NO then
  1786. cg.a_op_reg_reg_reg_checkoverflow(list,OP_ADD,hisize,carry,regdst.reghi,regdst.reghi,setflags,ovloc);
  1787. end;
  1788. OP_SUB:
  1789. begin
  1790. carry:=NR_NO;
  1791. if lo(value)<>0 then
  1792. begin
  1793. tmplo:=cg.GetIntRegister(list,OS_32);
  1794. carry:=cg.GetIntRegister(list,OS_32);
  1795. tcgmips(cg).handle_reg_const_reg(list,A_SUBU,regsrc.reglo,aint(lo(value)),tmplo);
  1796. list.concat(taicpu.op_reg_reg_reg(A_SLTU,carry,regsrc.reglo,tmplo));
  1797. cg.a_load_reg_reg(list,OS_32,OS_32,tmplo,regdst.reglo);
  1798. end
  1799. else
  1800. cg.a_load_reg_reg(list,OS_32,OS_32,regsrc.reglo,regdst.reglo);
  1801. cg.a_op_const_reg_reg_checkoverflow(list,OP_SUB,hisize,aint(hi(value)),regsrc.reghi,regdst.reghi,setflags,ovloc);
  1802. if carry<>NR_NO then
  1803. cg.a_op_reg_reg_reg_checkoverflow(list,OP_SUB,hisize,carry,regdst.reghi,regdst.reghi,setflags,ovloc);
  1804. end;
  1805. else
  1806. InternalError(2013050301);
  1807. end;
  1808. end;
  1809. procedure TCg64MPSel.a_op64_reg_reg_reg_checkoverflow(list: tasmlist; op: TOpCG; size: tcgsize; regsrc1, regsrc2, regdst: tregister64; setflags: boolean; var ovloc: tlocation);
  1810. var
  1811. tmplo,tmphi,carry,hreg: TRegister;
  1812. signed: boolean;
  1813. begin
  1814. case op of
  1815. OP_ADD:
  1816. begin
  1817. signed:=(size in [OS_S64]);
  1818. tmplo := cg.GetIntRegister(list,OS_S32);
  1819. carry := cg.GetIntRegister(list,OS_S32);
  1820. // destreg.reglo could be regsrc1.reglo or regsrc2.reglo
  1821. list.concat(taicpu.op_reg_reg_reg(A_ADDU, tmplo, regsrc2.reglo, regsrc1.reglo));
  1822. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, tmplo, regsrc2.reglo));
  1823. cg.a_load_reg_reg(list,OS_INT,OS_INT,tmplo,regdst.reglo);
  1824. if signed or (not setflags) then
  1825. begin
  1826. list.concat(taicpu.op_reg_reg_reg(ops_add[setflags and signed], regdst.reghi, regsrc2.reghi, regsrc1.reghi));
  1827. list.concat(taicpu.op_reg_reg_reg(ops_add[setflags and signed], regdst.reghi, regdst.reghi, carry));
  1828. end
  1829. else
  1830. begin
  1831. tmphi:=cg.GetIntRegister(list,OS_INT);
  1832. hreg:=cg.GetIntRegister(list,OS_INT);
  1833. cg.a_load_const_reg(list,OS_INT,$80000000,hreg);
  1834. // first add carry to one of the addends
  1835. list.concat(taicpu.op_reg_reg_reg(A_ADDU, tmphi, regsrc2.reghi, carry));
  1836. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, tmphi, regsrc2.reghi));
  1837. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1838. // then add another addend
  1839. list.concat(taicpu.op_reg_reg_reg(A_ADDU, regdst.reghi, tmphi, regsrc1.reghi));
  1840. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, regdst.reghi, tmphi));
  1841. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1842. end;
  1843. end;
  1844. OP_SUB:
  1845. begin
  1846. signed:=(size in [OS_S64]);
  1847. tmplo := cg.GetIntRegister(list,OS_S32);
  1848. carry := cg.GetIntRegister(list,OS_S32);
  1849. // destreg.reglo could be regsrc1.reglo or regsrc2.reglo
  1850. list.concat(taicpu.op_reg_reg_reg(A_SUBU, tmplo, regsrc2.reglo, regsrc1.reglo));
  1851. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, regsrc2.reglo,tmplo));
  1852. cg.a_load_reg_reg(list,OS_INT,OS_INT,tmplo,regdst.reglo);
  1853. if signed or (not setflags) then
  1854. begin
  1855. list.concat(taicpu.op_reg_reg_reg(ops_sub[setflags and signed], regdst.reghi, regsrc2.reghi, regsrc1.reghi));
  1856. list.concat(taicpu.op_reg_reg_reg(ops_sub[setflags and signed], regdst.reghi, regdst.reghi, carry));
  1857. end
  1858. else
  1859. begin
  1860. tmphi:=cg.GetIntRegister(list,OS_INT);
  1861. hreg:=cg.GetIntRegister(list,OS_INT);
  1862. cg.a_load_const_reg(list,OS_INT,$80000000,hreg);
  1863. // first subtract the carry...
  1864. list.concat(taicpu.op_reg_reg_reg(A_SUBU, tmphi, regsrc2.reghi, carry));
  1865. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, regsrc2.reghi, tmphi));
  1866. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1867. // ...then the subtrahend
  1868. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reghi, tmphi, regsrc1.reghi));
  1869. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, tmphi, regdst.reghi));
  1870. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1871. end;
  1872. end;
  1873. OP_AND,OP_OR,OP_XOR:
  1874. begin
  1875. cg.a_op_reg_reg_reg(list,op,size,regsrc1.reglo,regsrc2.reglo,regdst.reglo);
  1876. cg.a_op_reg_reg_reg(list,op,size,regsrc1.reghi,regsrc2.reghi,regdst.reghi);
  1877. end;
  1878. else
  1879. internalerror(200306017);
  1880. end;
  1881. end;
  1882. {$endif mips64}
  1883. procedure create_codegen;
  1884. begin
  1885. cg:=TCGMIPS.Create;
  1886. {$ifdef mips64}
  1887. cg128:=tcg128.create;
  1888. {$else mips64}
  1889. cg64:=TCg64MPSel.Create;
  1890. {$endif mips64}
  1891. end;
  1892. end.