cgcpu.pas 66 KB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151115211531154115511561157115811591160116111621163116411651166116711681169117011711172117311741175117611771178117911801181118211831184118511861187118811891190119111921193119411951196119711981199120012011202120312041205120612071208120912101211121212131214121512161217121812191220122112221223122412251226122712281229123012311232123312341235123612371238123912401241124212431244124512461247124812491250125112521253125412551256125712581259126012611262126312641265126612671268126912701271127212731274127512761277127812791280128112821283128412851286128712881289129012911292129312941295129612971298129913001301130213031304130513061307130813091310131113121313131413151316131713181319132013211322132313241325132613271328132913301331133213331334133513361337133813391340134113421343134413451346134713481349135013511352135313541355135613571358135913601361136213631364136513661367136813691370137113721373137413751376137713781379138013811382138313841385138613871388138913901391139213931394139513961397139813991400140114021403140414051406140714081409141014111412141314141415141614171418141914201421142214231424142514261427142814291430143114321433143414351436143714381439144014411442144314441445144614471448144914501451145214531454145514561457145814591460146114621463146414651466146714681469147014711472147314741475147614771478147914801481148214831484148514861487148814891490149114921493149414951496149714981499150015011502150315041505150615071508150915101511151215131514151515161517151815191520152115221523152415251526152715281529153015311532153315341535153615371538153915401541154215431544154515461547154815491550155115521553155415551556155715581559156015611562156315641565156615671568156915701571157215731574157515761577157815791580158115821583158415851586158715881589159015911592159315941595159615971598159916001601160216031604160516061607160816091610161116121613161416151616161716181619162016211622162316241625162616271628162916301631163216331634163516361637163816391640164116421643164416451646164716481649165016511652165316541655165616571658165916601661166216631664166516661667166816691670167116721673167416751676167716781679168016811682168316841685168616871688168916901691169216931694169516961697169816991700170117021703170417051706170717081709171017111712171317141715171617171718171917201721172217231724172517261727172817291730173117321733173417351736173717381739174017411742174317441745174617471748174917501751175217531754175517561757175817591760176117621763176417651766176717681769177017711772177317741775177617771778177917801781178217831784178517861787178817891790179117921793179417951796179717981799180018011802180318041805180618071808180918101811181218131814181518161817181818191820182118221823182418251826182718281829183018311832183318341835183618371838183918401841184218431844184518461847184818491850185118521853185418551856185718581859186018611862186318641865186618671868186918701871187218731874187518761877187818791880188118821883188418851886188718881889189018911892189318941895189618971898189919001901190219031904190519061907190819091910191119121913191419151916191719181919192019211922192319241925192619271928192919301931193219331934193519361937193819391940194119421943194419451946194719481949195019511952195319541955195619571958195919601961196219631964196519661967196819691970197119721973197419751976
  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. else
  391. begin
  392. list.concat(taicpu.op_reg_const(A_LUI, reg, aint(a) shr 16));
  393. if (a and aint($FFFF))<>0 then
  394. list.concat(taicpu.op_reg_reg_const(A_ORI,reg,reg,a and aint($FFFF)));
  395. end;
  396. end;
  397. procedure TCGMIPS.a_load_const_ref(list: tasmlist; size: tcgsize; a: tcgint; const ref: TReference);
  398. begin
  399. if a = 0 then
  400. a_load_reg_ref(list, size, size, NR_R0, ref)
  401. else
  402. inherited a_load_const_ref(list, size, a, ref);
  403. end;
  404. procedure TCGMIPS.a_load_reg_ref(list: tasmlist; FromSize, ToSize: TCGSize; reg: tregister; const Ref: TReference);
  405. var
  406. op: tasmop;
  407. href: treference;
  408. begin
  409. if (TCGSize2Size[fromsize] < TCGSize2Size[tosize]) then
  410. a_load_reg_reg(list,fromsize,tosize,reg,reg);
  411. if (ref.alignment<>0) and
  412. (ref.alignment<tcgsize2size[tosize]) then
  413. begin
  414. a_load_reg_ref_unaligned(list,FromSize,ToSize,reg,ref);
  415. exit;
  416. end;
  417. case tosize of
  418. OS_8,
  419. OS_S8:
  420. Op := A_SB;
  421. OS_16,
  422. OS_S16:
  423. Op := A_SH;
  424. OS_32,
  425. OS_S32:
  426. Op := A_SW;
  427. OS_64,
  428. OS_S64:
  429. Op := A_SD;
  430. else
  431. InternalError(2002122100);
  432. end;
  433. href:=ref;
  434. make_simple_ref(list,href);
  435. list.concat(taicpu.op_reg_ref(op,reg,href));
  436. end;
  437. procedure TCGMIPS.a_load_ref_reg(list: tasmlist; FromSize, ToSize: TCgSize; const ref: TReference; reg: tregister);
  438. var
  439. op: tasmop;
  440. href: treference;
  441. begin
  442. if (TCGSize2Size[fromsize] >= TCGSize2Size[tosize]) then
  443. fromsize := tosize;
  444. if (ref.alignment<>0) and
  445. (ref.alignment<tcgsize2size[fromsize]) then
  446. begin
  447. a_load_ref_reg_unaligned(list,FromSize,ToSize,ref,reg);
  448. exit;
  449. end;
  450. case fromsize of
  451. OS_S8:
  452. Op := A_LB;{Load Signed Byte}
  453. OS_8:
  454. Op := A_LBU;{Load Unsigned Byte}
  455. OS_S16:
  456. Op := A_LH;{Load Signed Halfword}
  457. OS_16:
  458. Op := A_LHU;{Load Unsigned Halfword}
  459. OS_S32:
  460. Op := A_LW;{Load Word}
  461. OS_32:
  462. Op := A_LW;//A_LWU;{Load Unsigned Word}
  463. OS_S64,
  464. OS_64:
  465. Op := A_LD;{Load a Long Word}
  466. else
  467. InternalError(2002122101);
  468. end;
  469. href:=ref;
  470. make_simple_ref(list,href);
  471. list.concat(taicpu.op_reg_ref(op,reg,href));
  472. if (fromsize=OS_S8) and (tosize=OS_16) then
  473. a_load_reg_reg(list,fromsize,tosize,reg,reg);
  474. end;
  475. procedure TCGMIPS.a_load_reg_reg(list: tasmlist; fromsize, tosize: tcgsize; reg1, reg2: tregister);
  476. var
  477. instr: taicpu;
  478. done: boolean;
  479. begin
  480. if (tcgsize2size[tosize] < tcgsize2size[fromsize]) or
  481. (
  482. (tcgsize2size[tosize] = tcgsize2size[fromsize]) and (tosize <> fromsize)
  483. ) or ((fromsize = OS_S8) and
  484. (tosize = OS_16)) then
  485. begin
  486. done:=true;
  487. case tosize of
  488. OS_8:
  489. list.concat(taicpu.op_reg_reg_const(A_ANDI, reg2, reg1, $ff));
  490. OS_16:
  491. list.concat(taicpu.op_reg_reg_const(A_ANDI, reg2, reg1, $ffff));
  492. {$ifdef cpu64bitalu}
  493. OS_64,
  494. OS_S64,
  495. {$endif cpu64bitalu}
  496. OS_32,
  497. OS_S32:
  498. done:=false;
  499. OS_S8:
  500. begin
  501. if (CPUMIPS_HAS_ISA32R2 in cpu_capabilities[current_settings.cputype]) then
  502. list.concat(taicpu.op_reg_reg(A_SEB,reg2,reg1))
  503. else
  504. begin
  505. list.concat(taicpu.op_reg_reg_const(A_SLL, reg2, reg1, 24));
  506. list.concat(taicpu.op_reg_reg_const(A_SRA, reg2, reg2, 24));
  507. end;
  508. end;
  509. OS_S16:
  510. begin
  511. if (CPUMIPS_HAS_ISA32R2 in cpu_capabilities[current_settings.cputype]) then
  512. list.concat(taicpu.op_reg_reg(A_SEH,reg2,reg1))
  513. else
  514. begin
  515. list.concat(taicpu.op_reg_reg_const(A_SLL, reg2, reg1, 16));
  516. list.concat(taicpu.op_reg_reg_const(A_SRA, reg2, reg2, 16));
  517. end;
  518. end;
  519. else
  520. internalerror(2002090901);
  521. end;
  522. end
  523. else
  524. done:=false;
  525. if (not done) and (reg1 <> reg2) then
  526. begin
  527. { same size, only a register mov required }
  528. instr := taicpu.op_reg_reg(A_MOVE, reg2, reg1);
  529. list.Concat(instr);
  530. { Notify the register allocator that we have written a move instruction so
  531. it can try to eliminate it. }
  532. add_move_instruction(instr);
  533. end;
  534. end;
  535. procedure TCGMIPS.a_loadaddr_ref_reg(list: tasmlist; const ref: TReference; r: tregister);
  536. var
  537. href: treference;
  538. hreg: tregister;
  539. begin
  540. { Enforce some discipline for callers:
  541. - reference must be a "raw" one and not use gp }
  542. if (ref.base=NR_GP) or (ref.index=NR_GP) then
  543. InternalError(2013022803);
  544. if (ref.refaddr<>addr_no) then
  545. InternalError(2013022804);
  546. if (ref.base=NR_NO) and (ref.index<>NR_NO) then
  547. InternalError(200306171);
  548. if (ref.symbol=nil) then
  549. begin
  550. if (ref.base<>NR_NO) then
  551. begin
  552. if (ref.offset<simm16lo) or (ref.offset>simm16hi) then
  553. begin
  554. hreg:=getintregister(list,OS_INT);
  555. a_load_const_reg(list,OS_INT,ref.offset,hreg);
  556. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,ref.base,hreg));
  557. end
  558. else if (ref.offset<>0) then
  559. list.concat(taicpu.op_reg_reg_const(A_ADDIU,r,ref.base,ref.offset))
  560. else
  561. a_load_reg_reg(list,OS_INT,OS_INT,ref.base,r); { emit optimizable move }
  562. if (ref.index<>NR_NO) then
  563. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,ref.index));
  564. end
  565. else
  566. a_load_const_reg(list,OS_INT,ref.offset,r);
  567. exit;
  568. end;
  569. reference_reset_symbol(href,ref.symbol,ref.offset,ref.alignment,ref.volatility);
  570. if (cs_create_pic in current_settings.moduleswitches) then
  571. begin
  572. if not (pi_needs_got in current_procinfo.flags) then
  573. InternalError(2013060104);
  574. { For PIC global symbols offset must be handled separately.
  575. Otherwise (non-PIC or local symbols) offset can be encoded
  576. into relocation even if exceeds 16 bits. }
  577. if (href.symbol.bind<>AB_LOCAL) then
  578. href.offset:=0;
  579. href.refaddr:=addr_pic;
  580. href.base:=NR_GP;
  581. list.concat(taicpu.op_reg_ref(A_LW,r,href));
  582. end
  583. else
  584. begin
  585. href.refaddr:=addr_high;
  586. list.concat(taicpu.op_reg_ref(A_LUI,r,href));
  587. end;
  588. { Add original base/index, if any. }
  589. if (ref.base<>NR_NO) then
  590. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,ref.base));
  591. if (ref.index<>NR_NO) then
  592. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,ref.index));
  593. { add low part if necessary }
  594. if (ref.symbol.bind=AB_LOCAL) or
  595. not (cs_create_pic in current_settings.moduleswitches) then
  596. begin
  597. href.refaddr:=addr_low;
  598. href.base:=NR_NO;
  599. list.concat(taicpu.op_reg_reg_ref(A_ADDIU,r,r,href));
  600. exit;
  601. end;
  602. if (ref.offset<simm16lo) or (ref.offset>simm16hi) then
  603. begin
  604. hreg:=getintregister(list,OS_INT);
  605. a_load_const_reg(list,OS_INT,ref.offset,hreg);
  606. list.concat(taicpu.op_reg_reg_reg(A_ADDU,r,r,hreg));
  607. end
  608. else if (ref.offset<>0) then
  609. list.concat(taicpu.op_reg_reg_const(A_ADDIU,r,r,ref.offset));
  610. end;
  611. procedure TCGMIPS.a_loadfpu_reg_reg(list: tasmlist; fromsize, tosize: tcgsize; reg1, reg2: tregister);
  612. const
  613. FpuMovInstr: array[OS_F32..OS_F64,OS_F32..OS_F64] of TAsmOp =
  614. ((A_MOV_S, A_CVT_D_S),(A_CVT_S_D,A_MOV_D));
  615. var
  616. instr: taicpu;
  617. begin
  618. if (reg1 <> reg2) or (fromsize<>tosize) then
  619. begin
  620. instr := taicpu.op_reg_reg(fpumovinstr[fromsize,tosize], reg2, reg1);
  621. list.Concat(instr);
  622. { Notify the register allocator that we have written a move instruction so
  623. it can try to eliminate it. }
  624. if (fromsize=tosize) then
  625. add_move_instruction(instr);
  626. end;
  627. end;
  628. procedure TCGMIPS.a_loadfpu_ref_reg(list: tasmlist; fromsize, tosize: tcgsize; const ref: TReference; reg: tregister);
  629. var
  630. href: TReference;
  631. begin
  632. href:=ref;
  633. make_simple_ref(list,href);
  634. case fromsize of
  635. OS_F32:
  636. list.concat(taicpu.op_reg_ref(A_LWC1,reg,href));
  637. OS_F64:
  638. list.concat(taicpu.op_reg_ref(A_LDC1,reg,href));
  639. else
  640. InternalError(2007042701);
  641. end;
  642. if tosize<>fromsize then
  643. a_loadfpu_reg_reg(list,fromsize,tosize,reg,reg);
  644. end;
  645. procedure TCGMIPS.a_loadfpu_reg_ref(list: tasmlist; fromsize, tosize: tcgsize; reg: tregister; const ref: TReference);
  646. var
  647. href: TReference;
  648. begin
  649. if tosize<>fromsize then
  650. a_loadfpu_reg_reg(list,fromsize,tosize,reg,reg);
  651. href:=ref;
  652. make_simple_ref(list,href);
  653. case tosize of
  654. OS_F32:
  655. list.concat(taicpu.op_reg_ref(A_SWC1,reg,href));
  656. OS_F64:
  657. list.concat(taicpu.op_reg_ref(A_SDC1,reg,href));
  658. else
  659. InternalError(2007042702);
  660. end;
  661. end;
  662. procedure TCGMIPS.maybeadjustresult(list: TAsmList; op: TOpCg; size: tcgsize; dst: tregister);
  663. const
  664. overflowops = [OP_MUL,OP_SHL,OP_ADD,OP_SUB,OP_NOT,OP_NEG];
  665. begin
  666. if (op in overflowops) and
  667. (size in [OS_8,OS_S8,OS_16,OS_S16]) then
  668. a_load_reg_reg(list,OS_32,size,dst,dst);
  669. end;
  670. procedure TCGMIPS.overflowcheck_internal(list: tasmlist; arg1, arg2: tregister);
  671. var
  672. carry, hreg: tregister;
  673. begin
  674. if (arg1=arg2) then
  675. InternalError(2013050501);
  676. carry:=GetIntRegister(list,OS_INT);
  677. hreg:=GetIntRegister(list,OS_INT);
  678. list.concat(taicpu.op_reg_reg_reg(A_SLTU,carry,arg1,arg2));
  679. { if carry<>0, this will cause hardware overflow interrupt }
  680. a_load_const_reg(list,OS_INT,$80000000,hreg);
  681. list.concat(taicpu.op_reg_reg_reg(A_SUB,hreg,hreg,carry));
  682. end;
  683. const
  684. ops_add: array[boolean] of TAsmOp = (A_ADDU, A_ADD);
  685. ops_sub: array[boolean] of TAsmOp = (A_SUBU, A_SUB);
  686. ops_slt: array[boolean] of TAsmOp = (A_SLTU, A_SLT);
  687. ops_slti: array[boolean] of TAsmOp = (A_SLTIU, A_SLTI);
  688. ops_and: array[boolean] of TAsmOp = (A_AND, A_ANDI);
  689. ops_or: array[boolean] of TAsmOp = (A_OR, A_ORI);
  690. ops_xor: array[boolean] of TasmOp = (A_XOR, A_XORI);
  691. procedure TCGMIPS.a_op_const_reg(list: tasmlist; Op: TOpCG; size: tcgsize; a: tcgint; reg: TRegister);
  692. begin
  693. optimize_op_const(size,op,a);
  694. case op of
  695. OP_NONE:
  696. exit;
  697. OP_MOVE:
  698. a_load_const_reg(list,size,a,reg);
  699. OP_NEG,OP_NOT:
  700. internalerror(200306011);
  701. else
  702. a_op_const_reg_reg(list,op,size,a,reg,reg);
  703. end;
  704. end;
  705. procedure TCGMIPS.a_op_reg_reg(list: tasmlist; Op: TOpCG; size: TCGSize; src, dst: TRegister);
  706. begin
  707. case Op of
  708. OP_NEG:
  709. list.concat(taicpu.op_reg_reg_reg(A_SUBU, dst, NR_R0, src));
  710. OP_NOT:
  711. list.concat(taicpu.op_reg_reg_reg(A_NOR, dst, NR_R0, src));
  712. OP_IMUL,OP_MUL:
  713. begin
  714. list.concat(taicpu.op_reg_reg(TOpcg2AsmOp[op], dst, src));
  715. list.concat(taicpu.op_reg(A_MFLO, dst));
  716. end;
  717. else
  718. a_op_reg_reg_reg(list, op, size, src, dst, dst);
  719. exit;
  720. end;
  721. maybeadjustresult(list,op,size,dst);
  722. end;
  723. procedure TCGMIPS.a_op_const_reg_reg(list: tasmlist; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister);
  724. var
  725. l: TLocation;
  726. begin
  727. a_op_const_reg_reg_checkoverflow(list, op, size, a, src, dst, false, l);
  728. end;
  729. procedure TCGMIPS.a_op_reg_reg_reg(list: tasmlist; op: TOpCg; size: tcgsize; src1, src2, dst: tregister);
  730. begin
  731. if (TOpcg2AsmOp[op]=A_NONE) then
  732. InternalError(2013070305);
  733. if (op=OP_SAR) then
  734. begin
  735. if (size in [OS_S8,OS_S16]) then
  736. begin
  737. { Sign-extend before shiting }
  738. list.concat(taicpu.op_reg_reg_const(A_SLL, dst, src2, 32-(tcgsize2size[size]*8)));
  739. list.concat(taicpu.op_reg_reg_const(A_SRA, dst, dst, 32-(tcgsize2size[size]*8)));
  740. src2:=dst;
  741. end
  742. else if not (size in [OS_32,OS_S32]) then
  743. InternalError(2013070306);
  744. end;
  745. list.concat(taicpu.op_reg_reg_reg(TOpCG2AsmOp[op], dst, src2, src1));
  746. maybeadjustresult(list,op,size,dst);
  747. end;
  748. procedure TCGMIPS.a_op_const_reg_reg_checkoverflow(list: tasmlist; op: TOpCg; size: tcgsize; a: tcgint; src, dst: tregister; setflags: boolean; var ovloc: tlocation);
  749. var
  750. signed,immed: boolean;
  751. hreg: TRegister;
  752. asmop: TAsmOp;
  753. begin
  754. a:=aint(a);
  755. ovloc.loc := LOC_VOID;
  756. optimize_op_const(size,op,a);
  757. signed:=(size in [OS_S8,OS_S16,OS_S32]);
  758. if (setflags and (not signed) and (src=dst) and (op in [OP_ADD,OP_SUB])) then
  759. hreg:=GetIntRegister(list,OS_INT)
  760. else
  761. hreg:=dst;
  762. case op of
  763. OP_NONE:
  764. a_load_reg_reg(list,size,size,src,dst);
  765. OP_MOVE:
  766. a_load_const_reg(list,size,a,dst);
  767. OP_ADD:
  768. begin
  769. handle_reg_const_reg(list,ops_add[setflags and signed],src,a,hreg);
  770. if setflags and (not signed) then
  771. overflowcheck_internal(list,hreg,src);
  772. { does nothing if hreg=dst }
  773. a_load_reg_reg(list,OS_INT,OS_INT,hreg,dst);
  774. end;
  775. OP_SUB:
  776. begin
  777. handle_reg_const_reg(list,ops_sub[setflags and signed],src,a,hreg);
  778. if setflags and (not signed) then
  779. overflowcheck_internal(list,src,hreg);
  780. a_load_reg_reg(list,OS_INT,OS_INT,hreg,dst);
  781. end;
  782. OP_MUL,OP_IMUL:
  783. begin
  784. hreg:=GetIntRegister(list,OS_INT);
  785. a_load_const_reg(list,OS_INT,a,hreg);
  786. a_op_reg_reg_reg_checkoverflow(list,op,size,src,hreg,dst,setflags,ovloc);
  787. exit;
  788. end;
  789. OP_AND,OP_OR,OP_XOR:
  790. begin
  791. { logical operations zero-extend, not sign-extend, the immediate }
  792. immed:=(a>=0) and (a<=65535);
  793. case op of
  794. OP_AND: asmop:=ops_and[immed];
  795. OP_OR: asmop:=ops_or[immed];
  796. OP_XOR: asmop:=ops_xor[immed];
  797. else
  798. InternalError(2013050401);
  799. end;
  800. if immed then
  801. list.concat(taicpu.op_reg_reg_const(asmop,dst,src,a))
  802. else
  803. begin
  804. hreg:=GetIntRegister(list,OS_INT);
  805. a_load_const_reg(list,OS_INT,a,hreg);
  806. list.concat(taicpu.op_reg_reg_reg(asmop,dst,src,hreg));
  807. end;
  808. end;
  809. OP_SHL:
  810. list.concat(taicpu.op_reg_reg_const(A_SLL,dst,src,a));
  811. OP_SHR:
  812. list.concat(taicpu.op_reg_reg_const(A_SRL,dst,src,a));
  813. OP_SAR:
  814. begin
  815. if (size in [OS_S8,OS_S16]) then
  816. begin
  817. list.concat(taicpu.op_reg_reg_const(A_SLL,dst,src,32-(tcgsize2size[size]*8)));
  818. inc(a,32-tcgsize2size[size]*8);
  819. src:=dst;
  820. end
  821. else if not (size in [OS_32,OS_S32]) then
  822. InternalError(2013070303);
  823. list.concat(taicpu.op_reg_reg_const(A_SRA,dst,src,a));
  824. end;
  825. else
  826. internalerror(2007012601);
  827. end;
  828. maybeadjustresult(list,op,size,dst);
  829. end;
  830. procedure TCGMIPS.a_op_reg_reg_reg_checkoverflow(list: tasmlist; op: TOpCg; size: tcgsize; src1, src2, dst: tregister; setflags: boolean; var ovloc: tlocation);
  831. var
  832. signed: boolean;
  833. hreg,hreg2: TRegister;
  834. hl: tasmlabel;
  835. begin
  836. ovloc.loc := LOC_VOID;
  837. signed:=(size in [OS_S8,OS_S16,OS_S32]);
  838. if (setflags and (not signed) and (src2=dst) and (op in [OP_ADD,OP_SUB])) then
  839. hreg:=GetIntRegister(list,OS_INT)
  840. else
  841. hreg:=dst;
  842. case op of
  843. OP_ADD:
  844. begin
  845. list.concat(taicpu.op_reg_reg_reg(ops_add[setflags and signed], hreg, src2, src1));
  846. if setflags and (not signed) then
  847. overflowcheck_internal(list, hreg, src2);
  848. a_load_reg_reg(list, OS_INT, OS_INT, hreg, dst);
  849. end;
  850. OP_SUB:
  851. begin
  852. list.concat(taicpu.op_reg_reg_reg(ops_sub[setflags and signed], hreg, src2, src1));
  853. if setflags and (not signed) then
  854. overflowcheck_internal(list, src2, hreg);
  855. a_load_reg_reg(list, OS_INT, OS_INT, hreg, dst);
  856. end;
  857. OP_MUL,OP_IMUL:
  858. begin
  859. if (CPUMIPS_HAS_ISA32R2 in cpu_capabilities[current_settings.cputype]) and
  860. (not setflags) then
  861. { NOTE: MUL is actually mips32r1 instruction; on older cores it is handled as macro }
  862. list.concat(taicpu.op_reg_reg_reg(A_MUL,dst,src2,src1))
  863. else
  864. begin
  865. list.concat(taicpu.op_reg_reg(TOpCg2AsmOp[op], src2, src1));
  866. list.concat(taicpu.op_reg(A_MFLO, dst));
  867. if setflags then
  868. begin
  869. current_asmdata.getjumplabel(hl);
  870. hreg:=GetIntRegister(list,OS_INT);
  871. list.concat(taicpu.op_reg(A_MFHI,hreg));
  872. if (op=OP_IMUL) then
  873. begin
  874. hreg2:=GetIntRegister(list,OS_INT);
  875. list.concat(taicpu.op_reg_reg_const(A_SRA,hreg2,dst,31));
  876. a_cmp_reg_reg_label(list,OS_INT,OC_EQ,hreg2,hreg,hl);
  877. end
  878. else
  879. a_cmp_reg_reg_label(list,OS_INT,OC_EQ,hreg,NR_R0,hl);
  880. list.concat(taicpu.op_const(A_BREAK,6));
  881. a_label(list,hl);
  882. end;
  883. end;
  884. end;
  885. OP_AND,OP_OR,OP_XOR:
  886. begin
  887. list.concat(taicpu.op_reg_reg_reg(TOpCG2AsmOp[op], dst, src2, src1));
  888. end;
  889. else
  890. internalerror(2007012602);
  891. end;
  892. maybeadjustresult(list,op,size,dst);
  893. end;
  894. {*************** compare instructructions ****************}
  895. procedure TCGMIPS.a_cmp_const_reg_label(list: tasmlist; size: tcgsize; cmp_op: topcmp; a: tcgint; reg: tregister; l: tasmlabel);
  896. var
  897. tmpreg: tregister;
  898. begin
  899. if a = 0 then
  900. a_cmp_reg_reg_label(list,size,cmp_op,NR_R0,reg,l)
  901. else
  902. begin
  903. tmpreg := GetIntRegister(list,OS_INT);
  904. if (a>=simm16lo) and (a<=simm16hi) and
  905. (cmp_op in [OC_LT,OC_B,OC_GTE,OC_AE]) then
  906. begin
  907. list.concat(taicpu.op_reg_reg_const(ops_slti[cmp_op in [OC_LT,OC_GTE]],tmpreg,reg,a));
  908. if cmp_op in [OC_LT,OC_B] then
  909. a_cmp_reg_reg_label(list,size,OC_NE,NR_R0,tmpreg,l)
  910. else
  911. a_cmp_reg_reg_label(list,size,OC_EQ,NR_R0,tmpreg,l);
  912. end
  913. else
  914. begin
  915. a_load_const_reg(list,OS_INT,a,tmpreg);
  916. a_cmp_reg_reg_label(list, size, cmp_op, tmpreg, reg, l);
  917. end;
  918. end;
  919. end;
  920. const
  921. TOpCmp2AsmCond_z : array[OC_GT..OC_LTE] of TAsmCond=(
  922. C_GTZ,C_LTZ,C_GEZ,C_LEZ
  923. );
  924. TOpCmp2AsmCond_eqne: array[topcmp] of TAsmCond = (C_NONE,
  925. { eq gt lt gte lte ne }
  926. C_NONE, C_NE, C_NE, C_EQ, C_EQ, C_NONE,
  927. { be b ae a }
  928. C_EQ, C_NE, C_EQ, C_NE
  929. );
  930. procedure TCGMIPS.a_cmp_reg_reg_label(list: tasmlist; size: tcgsize; cmp_op: topcmp; reg1, reg2: tregister; l: tasmlabel);
  931. var
  932. ai : Taicpu;
  933. op: TAsmOp;
  934. hreg: TRegister;
  935. begin
  936. if not (cmp_op in [OC_EQ,OC_NE]) then
  937. begin
  938. if ((reg1=NR_R0) or (reg2=NR_R0)) and (cmp_op in [OC_GT,OC_LT,OC_GTE,OC_LTE]) then
  939. begin
  940. if (reg2=NR_R0) then
  941. begin
  942. ai:=taicpu.op_reg_sym(A_BC,reg1,l);
  943. ai.setcondition(TOpCmp2AsmCond_z[swap_opcmp(cmp_op)]);
  944. end
  945. else
  946. begin
  947. ai:=taicpu.op_reg_sym(A_BC,reg2,l);
  948. ai.setcondition(TOpCmp2AsmCond_z[cmp_op]);
  949. end;
  950. end
  951. else
  952. begin
  953. hreg:=GetIntRegister(list,OS_INT);
  954. op:=ops_slt[cmp_op in [OC_LT,OC_LTE,OC_GT,OC_GTE]];
  955. if (cmp_op in [OC_LTE,OC_GT,OC_BE,OC_A]) then { swap operands }
  956. list.concat(taicpu.op_reg_reg_reg(op,hreg,reg1,reg2))
  957. else
  958. list.concat(taicpu.op_reg_reg_reg(op,hreg,reg2,reg1));
  959. if (TOpCmp2AsmCond_eqne[cmp_op]=C_NONE) then
  960. InternalError(2013051501);
  961. ai:=taicpu.op_reg_reg_sym(A_BC,hreg,NR_R0,l);
  962. ai.SetCondition(TOpCmp2AsmCond_eqne[cmp_op]);
  963. end;
  964. end
  965. else
  966. begin
  967. ai:=taicpu.op_reg_reg_sym(A_BC,reg2,reg1,l);
  968. ai.SetCondition(TOpCmp2AsmCond[cmp_op]);
  969. end;
  970. list.concat(ai);
  971. { Delay slot }
  972. list.Concat(TAiCpu.Op_none(A_NOP));
  973. end;
  974. procedure TCGMIPS.a_jmp_always(List: tasmlist; l: TAsmLabel);
  975. var
  976. ai : Taicpu;
  977. begin
  978. ai := taicpu.op_sym(A_BA, l);
  979. list.concat(ai);
  980. { Delay slot }
  981. list.Concat(TAiCpu.Op_none(A_NOP));
  982. end;
  983. procedure TCGMIPS.a_jmp_name(list: tasmlist; const s: string);
  984. begin
  985. List.Concat(TAiCpu.op_sym(A_BA, current_asmdata.RefAsmSymbol(s,AT_FUNCTION)));
  986. { Delay slot }
  987. list.Concat(TAiCpu.Op_none(A_NOP));
  988. end;
  989. procedure TCGMIPS.a_jmp_flags(list: tasmlist; const f: TResFlags; l: tasmlabel);
  990. var
  991. ai: taicpu;
  992. begin
  993. case f.reg1 of
  994. NR_FCC0..NR_FCC7:
  995. begin
  996. if (f.reg1=NR_FCC0) then
  997. ai:=taicpu.op_sym(A_BC,l)
  998. else
  999. ai:=taicpu.op_reg_sym(A_BC,f.reg1,l);
  1000. list.concat(ai);
  1001. { delay slot }
  1002. list.concat(taicpu.op_none(A_NOP));
  1003. case f.cond of
  1004. OC_NE: ai.SetCondition(C_COP1TRUE);
  1005. OC_EQ: ai.SetCondition(C_COP1FALSE);
  1006. else
  1007. InternalError(2014082901);
  1008. end;
  1009. exit;
  1010. end;
  1011. else
  1012. ;
  1013. end;
  1014. if f.use_const then
  1015. a_cmp_const_reg_label(list,OS_INT,f.cond,f.value,f.reg1,l)
  1016. else
  1017. a_cmp_reg_reg_label(list,OS_INT,f.cond,f.reg2,f.reg1,l);
  1018. end;
  1019. procedure TCGMIPS.g_flags2reg(list: tasmlist; size: tcgsize; const f: tresflags; reg: tregister);
  1020. var
  1021. left,right: tregister;
  1022. unsigned: boolean;
  1023. hl: tasmlabel;
  1024. begin
  1025. case f.reg1 of
  1026. NR_FCC0..NR_FCC7:
  1027. begin
  1028. if (current_settings.cputype>=cpu_mips4) then
  1029. begin
  1030. a_load_const_reg(list,size,1,reg);
  1031. case f.cond of
  1032. OC_NE: list.concat(taicpu.op_reg_reg_reg(A_MOVF,reg,NR_R0,f.reg1));
  1033. OC_EQ: list.concat(taicpu.op_reg_reg_reg(A_MOVT,reg,NR_R0,f.reg1));
  1034. else
  1035. InternalError(2014082902);
  1036. end;
  1037. end
  1038. else
  1039. begin
  1040. { TODO: still possible to do branchless by extracting appropriate bit from FCSR? }
  1041. current_asmdata.getjumplabel(hl);
  1042. a_load_const_reg(list,size,1,reg);
  1043. a_jmp_flags(list,f,hl);
  1044. a_load_const_reg(list,size,0,reg);
  1045. a_label(list,hl);
  1046. end;
  1047. exit;
  1048. end;
  1049. else
  1050. ;
  1051. end;
  1052. if (f.cond in [OC_EQ,OC_NE]) then
  1053. begin
  1054. left:=reg;
  1055. if f.use_const and (f.value>=0) and (f.value<=65535) then
  1056. begin
  1057. if (f.value<>0) then
  1058. list.concat(taicpu.op_reg_reg_const(A_XORI,reg,f.reg1,f.value))
  1059. else
  1060. left:=f.reg1;
  1061. end
  1062. else
  1063. begin
  1064. if f.use_const then
  1065. begin
  1066. right:=GetIntRegister(list,OS_INT);
  1067. a_load_const_reg(list,OS_INT,f.value,right);
  1068. end
  1069. else
  1070. right:=f.reg2;
  1071. list.concat(taicpu.op_reg_reg_reg(A_XOR,reg,f.reg1,right));
  1072. end;
  1073. if f.cond=OC_EQ then
  1074. list.concat(taicpu.op_reg_reg_const(A_SLTIU,reg,left,1))
  1075. else
  1076. list.concat(taicpu.op_reg_reg_reg(A_SLTU,reg,NR_R0,left));
  1077. end
  1078. else
  1079. begin
  1080. {
  1081. sle x,a,b --> slt x,b,a; xori x,x,1 immediate not possible (or must be at left)
  1082. sgt x,a,b --> slt x,b,a likewise
  1083. sge x,a,b --> slt x,a,b; xori x,x,1
  1084. slt x,a,b --> unchanged
  1085. }
  1086. unsigned:=f.cond in [OC_GT,OC_LT,OC_GTE,OC_LTE];
  1087. if (f.cond in [OC_GTE,OC_LT,OC_B,OC_AE]) and
  1088. f.use_const and
  1089. (f.value>=simm16lo) and
  1090. (f.value<=simm16hi) then
  1091. list.Concat(taicpu.op_reg_reg_const(ops_slti[unsigned],reg,f.reg1,f.value))
  1092. else
  1093. begin
  1094. if f.use_const then
  1095. begin
  1096. if (f.value=0) then
  1097. right:=NR_R0
  1098. else
  1099. begin
  1100. right:=GetIntRegister(list,OS_INT);
  1101. a_load_const_reg(list,OS_INT,f.value,right);
  1102. end;
  1103. end
  1104. else
  1105. right:=f.reg2;
  1106. if (f.cond in [OC_LTE,OC_GT,OC_BE,OC_A]) then
  1107. list.Concat(taicpu.op_reg_reg_reg(ops_slt[unsigned],reg,right,f.reg1))
  1108. else
  1109. list.Concat(taicpu.op_reg_reg_reg(ops_slt[unsigned],reg,f.reg1,right));
  1110. end;
  1111. if (f.cond in [OC_LTE,OC_GTE,OC_BE,OC_AE]) then
  1112. list.Concat(taicpu.op_reg_reg_const(A_XORI,reg,reg,1));
  1113. end;
  1114. end;
  1115. procedure TCGMIPS.a_mul_reg_reg_pair(list: tasmlist; size: tcgsize; src1,src2,dstlo,dsthi: tregister);
  1116. var
  1117. asmop: tasmop;
  1118. begin
  1119. case size of
  1120. OS_32: asmop:=A_MULTU;
  1121. OS_S32: asmop:=A_MULT;
  1122. {$ifdef cpu64bitalu}
  1123. OS_64: asmop:=A_DMULTU;
  1124. OS_S64: asmop:=A_DMULT;
  1125. {$endif cpu64bitalu}
  1126. else
  1127. InternalError(2022020901);
  1128. end;
  1129. list.concat(taicpu.op_reg_reg(asmop,src1,src2));
  1130. if (dstlo<>NR_NO) then
  1131. list.concat(taicpu.op_reg(A_MFLO,dstlo));
  1132. if (dsthi<>NR_NO) then
  1133. list.concat(taicpu.op_reg(A_MFHI,dsthi));
  1134. end;
  1135. procedure TCGMIPS.g_overflowCheck(List: tasmlist; const Loc: TLocation; def: TDef);
  1136. begin
  1137. // this is an empty procedure
  1138. end;
  1139. procedure TCGMIPS.g_overflowCheck_loc(List: tasmlist; const Loc: TLocation; def: TDef; ovloc: tlocation);
  1140. begin
  1141. // this is an empty procedure
  1142. end;
  1143. { *********** entry/exit code and address loading ************ }
  1144. procedure FixupOffsets(p:TObject;arg:pointer);
  1145. var
  1146. sym: tabstractnormalvarsym absolute p;
  1147. begin
  1148. if (tsym(p).typ=paravarsym) and
  1149. (sym.localloc.loc=LOC_REFERENCE) and
  1150. (sym.localloc.reference.base=NR_FRAME_POINTER_REG) then
  1151. begin
  1152. sym.localloc.reference.base:=NR_STACK_POINTER_REG;
  1153. Inc(sym.localloc.reference.offset,PLongint(arg)^);
  1154. end;
  1155. end;
  1156. procedure TCGMIPS.g_proc_entry(list: tasmlist; localsize: longint; nostackframe: boolean);
  1157. var
  1158. lastintoffset,lastfpuoffset,
  1159. nextoffset : aint;
  1160. i : longint;
  1161. ra_save,framesave : taicpu;
  1162. fmask,mask : dword;
  1163. saveregs : tcpuregisterset;
  1164. href: treference;
  1165. reg : Tsuperregister;
  1166. helplist : TAsmList;
  1167. largeoffs : boolean;
  1168. begin
  1169. list.concat(tai_directive.create(asd_ent,current_procinfo.procdef.mangledname));
  1170. if nostackframe then
  1171. begin
  1172. list.concat(taicpu.op_none(A_P_SET_NOMIPS16));
  1173. list.concat(taicpu.op_none(A_P_SET_NOREORDER));
  1174. exit;
  1175. end;
  1176. helplist:=TAsmList.Create;
  1177. reference_reset(href,0,[]);
  1178. href.base:=NR_STACK_POINTER_REG;
  1179. fmask:=0;
  1180. nextoffset:=tcpuprocinfo(current_procinfo).floatregstart;
  1181. lastfpuoffset:=LocalSize;
  1182. for reg := RS_F0 to RS_F31 do { to check: what if F30 is double? }
  1183. begin
  1184. if reg in (rg[R_FPUREGISTER].used_in_proc-paramanager.get_volatile_registers_fpu(pocall_stdcall)) then
  1185. begin
  1186. fmask:=fmask or (longword(1) shl ord(reg));
  1187. href.offset:=nextoffset;
  1188. lastfpuoffset:=nextoffset;
  1189. helplist.concat(taicpu.op_reg_ref(A_SWC1,newreg(R_FPUREGISTER,reg,R_SUBFS),href));
  1190. inc(nextoffset,4);
  1191. { IEEE Double values are stored in floating point
  1192. register pairs f2X/f2X+1,
  1193. as the f2X+1 register is not correctly marked as used for now,
  1194. we simply assume it is also used if f2X is used
  1195. Should be fixed by a proper inclusion of f2X+1 into used_in_proc }
  1196. if (ord(reg)-ord(RS_F0)) mod 2 = 0 then
  1197. include(rg[R_FPUREGISTER].used_in_proc,succ(reg));
  1198. end;
  1199. end;
  1200. mask:=0;
  1201. nextoffset:=tcpuprocinfo(current_procinfo).intregstart;
  1202. saveregs:=rg[R_INTREGISTER].used_in_proc-paramanager.get_volatile_registers_int(pocall_stdcall);
  1203. if (current_procinfo.flags*[pi_do_call,pi_is_assembler]<>[]) then
  1204. include(saveregs,RS_R31);
  1205. if (pi_needs_stackframe in current_procinfo.flags) then
  1206. include(saveregs,RS_FRAME_POINTER_REG);
  1207. lastintoffset:=LocalSize;
  1208. framesave:=nil;
  1209. ra_save:=nil;
  1210. for reg:=RS_R1 to RS_R31 do
  1211. begin
  1212. if reg in saveregs then
  1213. begin
  1214. mask:=mask or (longword(1) shl ord(reg));
  1215. href.offset:=nextoffset;
  1216. lastintoffset:=nextoffset;
  1217. if (reg=RS_FRAME_POINTER_REG) then
  1218. framesave:=taicpu.op_reg_ref(A_SW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href)
  1219. else if (reg=RS_R31) then
  1220. ra_save:=taicpu.op_reg_ref(A_SW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href)
  1221. else
  1222. helplist.concat(taicpu.op_reg_ref(A_SW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href));
  1223. inc(nextoffset,4);
  1224. end;
  1225. end;
  1226. //list.concat(Taicpu.Op_reg_reg_const(A_ADDIU,NR_FRAME_POINTER_REG,NR_STACK_POINTER_REG,current_procinfo.para_stack_size));
  1227. list.concat(Taicpu.op_none(A_P_SET_NOMIPS16));
  1228. list.concat(Taicpu.op_reg_const_reg(A_P_FRAME,current_procinfo.framepointer,LocalSize,NR_R31));
  1229. list.concat(Taicpu.op_const_const(A_P_MASK,aint(mask),-(LocalSize-lastintoffset)));
  1230. list.concat(Taicpu.op_const_const(A_P_FMASK,aint(Fmask),-(LocalSize-lastfpuoffset)));
  1231. list.concat(Taicpu.op_none(A_P_SET_NOREORDER));
  1232. if tcpuprocinfo(current_procinfo).setnoat then
  1233. list.concat(Taicpu.op_none(A_P_SET_NOAT));
  1234. if (cs_create_pic in current_settings.moduleswitches) and
  1235. (pi_needs_got in current_procinfo.flags) then
  1236. begin
  1237. list.concat(Taicpu.op_reg(A_P_CPLOAD,NR_PIC_FUNC));
  1238. end;
  1239. if (-LocalSize >= simm16lo) and (-LocalSize <= simm16hi) then
  1240. begin
  1241. list.concat(Taicpu.op_none(A_P_SET_NOMACRO));
  1242. list.concat(Taicpu.Op_reg_reg_const(A_ADDIU,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,-LocalSize));
  1243. if assigned(ra_save) then
  1244. list.concat(ra_save);
  1245. if assigned(framesave) then
  1246. begin
  1247. list.concat(framesave);
  1248. list.concat(Taicpu.op_reg_reg_const(A_ADDIU,NR_FRAME_POINTER_REG,
  1249. NR_STACK_POINTER_REG,LocalSize));
  1250. end;
  1251. end
  1252. else
  1253. begin
  1254. a_load_const_reg(list,OS_32,-LocalSize,NR_R9);
  1255. list.concat(Taicpu.Op_reg_reg_reg(A_ADDU,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,NR_R9));
  1256. if assigned(ra_save) then
  1257. list.concat(ra_save);
  1258. if assigned(framesave) then
  1259. begin
  1260. list.concat(framesave);
  1261. list.concat(Taicpu.op_reg_reg_reg(A_SUBU,NR_FRAME_POINTER_REG,
  1262. NR_STACK_POINTER_REG,NR_R9));
  1263. end;
  1264. { The instructions before are macros that can extend to multiple instructions,
  1265. the settings of R9 to -LocalSize surely does,
  1266. but the saving of RA and FP also might, and might
  1267. even use AT register, which is why we use R9 instead of AT here for -LocalSize }
  1268. list.concat(Taicpu.op_none(A_P_SET_NOMACRO));
  1269. end;
  1270. if (cs_create_pic in current_settings.moduleswitches) and
  1271. (pi_needs_got in current_procinfo.flags) then
  1272. begin
  1273. largeoffs:=(tcpuprocinfo(current_procinfo).save_gp_ref.offset>simm16hi);
  1274. if largeoffs then
  1275. list.concat(Taicpu.op_none(A_P_SET_MACRO));
  1276. list.concat(Taicpu.op_const(A_P_CPRESTORE,tcpuprocinfo(current_procinfo).save_gp_ref.offset));
  1277. if largeoffs then
  1278. list.concat(Taicpu.op_none(A_P_SET_NOMACRO));
  1279. end;
  1280. href.base:=NR_STACK_POINTER_REG;
  1281. for i:=0 to MIPS_MAX_REGISTERS_USED_IN_CALL-1 do
  1282. if tcpuprocinfo(current_procinfo).register_used[i] then
  1283. begin
  1284. reg:=parasupregs[i];
  1285. href.offset:=i*sizeof(aint)+LocalSize;
  1286. list.concat(taicpu.op_reg_ref(A_SW, newreg(R_INTREGISTER,reg,R_SUBWHOLE), href));
  1287. end;
  1288. list.concatList(helplist);
  1289. helplist.Free;
  1290. if current_procinfo.has_nestedprocs then
  1291. current_procinfo.procdef.parast.SymList.ForEachCall(@FixupOffsets,@LocalSize);
  1292. end;
  1293. procedure TCGMIPS.g_proc_exit(list: tasmlist; parasize: longint; nostackframe: boolean);
  1294. var
  1295. href : treference;
  1296. stacksize : aint;
  1297. saveregs : tcpuregisterset;
  1298. nextoffset : aint;
  1299. reg : Tsuperregister;
  1300. begin
  1301. stacksize:=current_procinfo.calc_stackframe_size;
  1302. if nostackframe then
  1303. begin
  1304. list.concat(taicpu.op_reg(A_JR, NR_R31));
  1305. list.concat(Taicpu.op_none(A_NOP));
  1306. list.concat(Taicpu.op_none(A_P_SET_MACRO));
  1307. list.concat(Taicpu.op_none(A_P_SET_REORDER));
  1308. end
  1309. else
  1310. begin
  1311. if tcpuprocinfo(current_procinfo).save_gp_ref.offset<>0 then
  1312. tg.ungettemp(list,tcpuprocinfo(current_procinfo).save_gp_ref);
  1313. reference_reset(href,0,[]);
  1314. href.base:=NR_STACK_POINTER_REG;
  1315. nextoffset:=tcpuprocinfo(current_procinfo).floatregstart;
  1316. for reg := RS_F0 to RS_F31 do
  1317. begin
  1318. if reg in (rg[R_FPUREGISTER].used_in_proc-paramanager.get_volatile_registers_fpu(pocall_stdcall)) then
  1319. begin
  1320. href.offset:=nextoffset;
  1321. list.concat(taicpu.op_reg_ref(A_LWC1,newreg(R_FPUREGISTER,reg,R_SUBFS),href));
  1322. inc(nextoffset,4);
  1323. end;
  1324. end;
  1325. nextoffset:=tcpuprocinfo(current_procinfo).intregstart;
  1326. saveregs:=rg[R_INTREGISTER].used_in_proc-paramanager.get_volatile_registers_int(pocall_stdcall);
  1327. if (current_procinfo.flags*[pi_do_call,pi_is_assembler]<>[]) then
  1328. include(saveregs,RS_R31);
  1329. if (pi_needs_stackframe in current_procinfo.flags) then
  1330. include(saveregs,RS_FRAME_POINTER_REG);
  1331. // GP does not need to be restored on exit
  1332. for reg:=RS_R1 to RS_R31 do
  1333. begin
  1334. if reg in saveregs then
  1335. begin
  1336. href.offset:=nextoffset;
  1337. list.concat(taicpu.op_reg_ref(A_LW,newreg(R_INTREGISTER,reg,R_SUBWHOLE),href));
  1338. inc(nextoffset,sizeof(aint));
  1339. end;
  1340. end;
  1341. if (-stacksize >= simm16lo) and (-stacksize <= simm16hi) then
  1342. begin
  1343. list.concat(taicpu.op_reg(A_JR, NR_R31));
  1344. { correct stack pointer in the delay slot }
  1345. list.concat(Taicpu.Op_reg_reg_const(A_ADDIU, NR_STACK_POINTER_REG, NR_STACK_POINTER_REG, stacksize));
  1346. end
  1347. else
  1348. begin
  1349. a_load_const_reg(list,OS_32,stacksize,NR_R1);
  1350. list.concat(taicpu.op_reg(A_JR, NR_R31));
  1351. { correct stack pointer in the delay slot }
  1352. list.concat(taicpu.op_reg_reg_reg(A_ADD,NR_STACK_POINTER_REG,NR_STACK_POINTER_REG,NR_R1));
  1353. tcpuprocinfo(current_procinfo).setnoat:=true;
  1354. end;
  1355. list.concat(Taicpu.op_none(A_P_SET_MACRO));
  1356. list.concat(Taicpu.op_none(A_P_SET_REORDER));
  1357. end;
  1358. list.concat(tai_directive.create(asd_ent_end,current_procinfo.procdef.mangledname));
  1359. end;
  1360. { ************* concatcopy ************ }
  1361. procedure TCGMIPS.g_concatcopy_move(list: tasmlist; const Source, dest: treference; len: tcgint);
  1362. var
  1363. paraloc1, paraloc2, paraloc3: TCGPara;
  1364. pd: tprocdef;
  1365. begin
  1366. pd:=search_system_proc('MOVE');
  1367. paraloc1.init;
  1368. paraloc2.init;
  1369. paraloc3.init;
  1370. paramanager.getcgtempparaloc(list, pd, 1, paraloc1);
  1371. paramanager.getcgtempparaloc(list, pd, 2, paraloc2);
  1372. paramanager.getcgtempparaloc(list, pd, 3, paraloc3);
  1373. a_load_const_cgpara(list, OS_SINT, len, paraloc3);
  1374. a_loadaddr_ref_cgpara(list, dest, paraloc2);
  1375. a_loadaddr_ref_cgpara(list, Source, paraloc1);
  1376. paramanager.freecgpara(list, paraloc3);
  1377. paramanager.freecgpara(list, paraloc2);
  1378. paramanager.freecgpara(list, paraloc1);
  1379. alloccpuregisters(list, R_INTREGISTER, paramanager.get_volatile_registers_int(pocall_default));
  1380. alloccpuregisters(list, R_FPUREGISTER, paramanager.get_volatile_registers_fpu(pocall_default));
  1381. a_call_name(list, 'FPC_MOVE', false);
  1382. dealloccpuregisters(list, R_FPUREGISTER, paramanager.get_volatile_registers_fpu(pocall_default));
  1383. dealloccpuregisters(list, R_INTREGISTER, paramanager.get_volatile_registers_int(pocall_default));
  1384. paraloc3.done;
  1385. paraloc2.done;
  1386. paraloc1.done;
  1387. end;
  1388. procedure TCGMIPS.g_concatcopy(list: tasmlist; const Source, dest: treference; len: tcgint);
  1389. var
  1390. tmpreg1, hreg, countreg: TRegister;
  1391. src, dst: TReference;
  1392. lab: tasmlabel;
  1393. Count, count2: aint;
  1394. function reference_is_reusable(const ref: treference): boolean;
  1395. begin
  1396. result:=(ref.base<>NR_NO) and (ref.index=NR_NO) and
  1397. (ref.symbol=nil) and
  1398. (ref.offset>=simm16lo) and (ref.offset+len<=simm16hi);
  1399. end;
  1400. begin
  1401. if len > high(longint) then
  1402. internalerror(2002072704);
  1403. { A call (to FPC_MOVE) requires the outgoing parameter area to be properly
  1404. allocated on stack. This can only be done before tcpuprocinfo.set_first_temp_offset,
  1405. i.e. before secondpass. Other internal procedures request correct stack frame
  1406. by setting pi_do_call during firstpass, but for this particular one it is impossible.
  1407. Therefore, if the current procedure is a leaf one, we have to leave it that way. }
  1408. { anybody wants to determine a good value here :)? }
  1409. if (len > 100) and
  1410. assigned(current_procinfo) and
  1411. (pi_do_call in current_procinfo.flags) then
  1412. g_concatcopy_move(list, Source, dest, len)
  1413. else
  1414. begin
  1415. Count := len div 4;
  1416. if (count<=4) and reference_is_reusable(source) then
  1417. src:=source
  1418. else
  1419. begin
  1420. reference_reset(src,sizeof(aint),source.volatility);
  1421. { load the address of source into src.base }
  1422. src.base := GetAddressRegister(list);
  1423. a_loadaddr_ref_reg(list, Source, src.base);
  1424. end;
  1425. if (count<=4) and reference_is_reusable(dest) then
  1426. dst:=dest
  1427. else
  1428. begin
  1429. reference_reset(dst,sizeof(aint),dest.volatility);
  1430. { load the address of dest into dst.base }
  1431. dst.base := GetAddressRegister(list);
  1432. a_loadaddr_ref_reg(list, dest, dst.base);
  1433. end;
  1434. { generate a loop }
  1435. if Count > 4 then
  1436. begin
  1437. countreg := GetIntRegister(list, OS_INT);
  1438. tmpreg1 := GetIntRegister(list, OS_INT);
  1439. a_load_const_reg(list, OS_INT, Count, countreg);
  1440. current_asmdata.getjumplabel(lab);
  1441. a_label(list, lab);
  1442. list.concat(taicpu.op_reg_ref(A_LW, tmpreg1, src));
  1443. list.concat(taicpu.op_reg_ref(A_SW, tmpreg1, dst));
  1444. list.concat(taicpu.op_reg_reg_const(A_ADDIU, src.base, src.base, 4));
  1445. list.concat(taicpu.op_reg_reg_const(A_ADDIU, dst.base, dst.base, 4));
  1446. list.concat(taicpu.op_reg_reg_const(A_ADDIU, countreg, countreg, -1));
  1447. a_cmp_reg_reg_label(list,OS_INT,OC_GT,NR_R0,countreg,lab);
  1448. len := len mod 4;
  1449. end;
  1450. { unrolled loop }
  1451. Count := len div 4;
  1452. if Count > 0 then
  1453. begin
  1454. tmpreg1 := GetIntRegister(list, OS_INT);
  1455. count2:=1;
  1456. while count2 <= Count do
  1457. begin
  1458. list.concat(taicpu.op_reg_ref(A_LW, tmpreg1, src));
  1459. list.concat(taicpu.op_reg_ref(A_SW, tmpreg1, dst));
  1460. Inc(src.offset, 4);
  1461. Inc(dst.offset, 4);
  1462. Inc(count2);
  1463. end;
  1464. len := len mod 4;
  1465. end;
  1466. if (len and 4) <> 0 then
  1467. begin
  1468. hreg := GetIntRegister(list, OS_INT);
  1469. a_load_ref_reg(list, OS_32, OS_32, src, hreg);
  1470. a_load_reg_ref(list, OS_32, OS_32, hreg, dst);
  1471. Inc(src.offset, 4);
  1472. Inc(dst.offset, 4);
  1473. end;
  1474. { copy the leftovers }
  1475. if (len and 2) <> 0 then
  1476. begin
  1477. hreg := GetIntRegister(list, OS_INT);
  1478. a_load_ref_reg(list, OS_16, OS_16, src, hreg);
  1479. a_load_reg_ref(list, OS_16, OS_16, hreg, dst);
  1480. Inc(src.offset, 2);
  1481. Inc(dst.offset, 2);
  1482. end;
  1483. if (len and 1) <> 0 then
  1484. begin
  1485. hreg := GetIntRegister(list, OS_INT);
  1486. a_load_ref_reg(list, OS_8, OS_8, src, hreg);
  1487. a_load_reg_ref(list, OS_8, OS_8, hreg, dst);
  1488. end;
  1489. end;
  1490. end;
  1491. procedure TCGMIPS.g_concatcopy_unaligned(list: tasmlist; const Source, dest: treference; len: tcgint);
  1492. var
  1493. src, dst: TReference;
  1494. tmpreg1, countreg: TRegister;
  1495. i: aint;
  1496. lab: tasmlabel;
  1497. begin
  1498. if (len > 31) and
  1499. { see comment in g_concatcopy }
  1500. assigned(current_procinfo) and
  1501. (pi_do_call in current_procinfo.flags) then
  1502. g_concatcopy_move(list, Source, dest, len)
  1503. else
  1504. begin
  1505. reference_reset(src,sizeof(aint),source.volatility);
  1506. reference_reset(dst,sizeof(aint),dest.volatility);
  1507. { load the address of source into src.base }
  1508. src.base := GetAddressRegister(list);
  1509. a_loadaddr_ref_reg(list, Source, src.base);
  1510. { load the address of dest into dst.base }
  1511. dst.base := GetAddressRegister(list);
  1512. a_loadaddr_ref_reg(list, dest, dst.base);
  1513. { generate a loop }
  1514. if len > 4 then
  1515. begin
  1516. countreg := GetIntRegister(list, OS_INT);
  1517. tmpreg1 := GetIntRegister(list, OS_INT);
  1518. a_load_const_reg(list, OS_INT, len, countreg);
  1519. current_asmdata.getjumplabel(lab);
  1520. a_label(list, lab);
  1521. list.concat(taicpu.op_reg_ref(A_LBU, tmpreg1, src));
  1522. list.concat(taicpu.op_reg_ref(A_SB, tmpreg1, dst));
  1523. list.concat(taicpu.op_reg_reg_const(A_ADDIU, src.base, src.base, 1));
  1524. list.concat(taicpu.op_reg_reg_const(A_ADDIU, dst.base, dst.base, 1));
  1525. list.concat(taicpu.op_reg_reg_const(A_ADDIU, countreg, countreg, -1));
  1526. a_cmp_reg_reg_label(list,OS_INT,OC_GT,NR_R0,countreg,lab);
  1527. end
  1528. else
  1529. begin
  1530. { unrolled loop }
  1531. tmpreg1 := GetIntRegister(list, OS_INT);
  1532. i := 1;
  1533. while i <= len do
  1534. begin
  1535. list.concat(taicpu.op_reg_ref(A_LBU, tmpreg1, src));
  1536. list.concat(taicpu.op_reg_ref(A_SB, tmpreg1, dst));
  1537. Inc(src.offset);
  1538. Inc(dst.offset);
  1539. Inc(i);
  1540. end;
  1541. end;
  1542. end;
  1543. end;
  1544. procedure TCGMIPS.g_profilecode(list:TAsmList);
  1545. var
  1546. href: treference;
  1547. begin
  1548. if not (cs_create_pic in current_settings.moduleswitches) then
  1549. begin
  1550. reference_reset_symbol(href,current_asmdata.RefAsmSymbol('_gp',AT_DATA),0,sizeof(pint),[]);
  1551. a_loadaddr_ref_reg(list,href,NR_GP);
  1552. end;
  1553. list.concat(taicpu.op_reg_reg(A_MOVE,NR_R1,NR_RA));
  1554. list.concat(taicpu.op_reg_reg_const(A_ADDIU,NR_SP,NR_SP,-8));
  1555. a_call_sym_pic(list,current_asmdata.RefAsmSymbol('_mcount',AT_FUNCTION));
  1556. tcpuprocinfo(current_procinfo).setnoat:=true;
  1557. end;
  1558. procedure TCGMIPS.g_adjust_self_value(list:TAsmList;procdef: tprocdef;ioffset: tcgint);
  1559. begin
  1560. { This method is integrated into g_intf_wrapper and shouldn't be called separately }
  1561. InternalError(2013020102);
  1562. end;
  1563. {$ifndef mips64}
  1564. {****************************************************************************
  1565. TCG64_MIPSel
  1566. ****************************************************************************}
  1567. procedure TCg64MPSel.a_load64_reg_ref(list: tasmlist; reg: tregister64; const ref: treference);
  1568. var
  1569. tmpref: treference;
  1570. tmpreg: tregister;
  1571. begin
  1572. if target_info.endian = endian_big then
  1573. begin
  1574. tmpreg := reg.reglo;
  1575. reg.reglo := reg.reghi;
  1576. reg.reghi := tmpreg;
  1577. end;
  1578. tmpref := ref;
  1579. tcgmips(cg).make_simple_ref(list,tmpref);
  1580. list.concat(taicpu.op_reg_ref(A_SW,reg.reglo,tmpref));
  1581. Inc(tmpref.offset, 4);
  1582. list.concat(taicpu.op_reg_ref(A_SW,reg.reghi,tmpref));
  1583. end;
  1584. procedure TCg64MPSel.a_load64_ref_reg(list: tasmlist; const ref: treference; reg: tregister64);
  1585. var
  1586. tmpref: treference;
  1587. tmpreg: tregister;
  1588. begin
  1589. if target_info.endian = endian_big then
  1590. begin
  1591. tmpreg := reg.reglo;
  1592. reg.reglo := reg.reghi;
  1593. reg.reghi := tmpreg;
  1594. end;
  1595. tmpref := ref;
  1596. tcgmips(cg).make_simple_ref(list,tmpref);
  1597. list.concat(taicpu.op_reg_ref(A_LW,reg.reglo,tmpref));
  1598. Inc(tmpref.offset, 4);
  1599. list.concat(taicpu.op_reg_ref(A_LW,reg.reghi,tmpref));
  1600. end;
  1601. procedure TCg64MPSel.a_load64_ref_cgpara(list: tasmlist; const r: treference; const paraloc: tcgpara);
  1602. var
  1603. hreg64: tregister64;
  1604. begin
  1605. { Override this function to prevent loading the reference twice.
  1606. Use here some extra registers, but those are optimized away by the RA }
  1607. hreg64.reglo := cg.GetIntRegister(list, OS_S32);
  1608. hreg64.reghi := cg.GetIntRegister(list, OS_S32);
  1609. a_load64_ref_reg(list, r, hreg64);
  1610. a_load64_reg_cgpara(list, hreg64, paraloc);
  1611. end;
  1612. procedure TCg64MPSel.a_op64_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; regsrc, regdst: TRegister64);
  1613. var
  1614. tmpreg1: TRegister;
  1615. begin
  1616. case op of
  1617. OP_NEG:
  1618. begin
  1619. tmpreg1 := cg.GetIntRegister(list, OS_INT);
  1620. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reglo, NR_R0, regsrc.reglo));
  1621. list.concat(taicpu.op_reg_reg_reg(A_SLTU, tmpreg1, NR_R0, regdst.reglo));
  1622. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reghi, NR_R0, regsrc.reghi));
  1623. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reghi, regdst.reghi, tmpreg1));
  1624. end;
  1625. OP_NOT:
  1626. begin
  1627. list.concat(taicpu.op_reg_reg_reg(A_NOR, regdst.reglo, NR_R0, regsrc.reglo));
  1628. list.concat(taicpu.op_reg_reg_reg(A_NOR, regdst.reghi, NR_R0, regsrc.reghi));
  1629. end;
  1630. else
  1631. a_op64_reg_reg_reg(list,op,size,regsrc,regdst,regdst);
  1632. end;
  1633. end;
  1634. procedure TCg64MPSel.a_op64_const_reg(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regdst: TRegister64);
  1635. begin
  1636. a_op64_const_reg_reg(list, op, size, value, regdst, regdst);
  1637. end;
  1638. procedure TCg64MPSel.a_op64_const_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regsrc, regdst: tregister64);
  1639. var
  1640. l: tlocation;
  1641. begin
  1642. a_op64_const_reg_reg_checkoverflow(list, op, size, Value, regsrc, regdst, False, l);
  1643. end;
  1644. procedure TCg64MPSel.a_op64_reg_reg_reg(list: tasmlist; op: TOpCG; size: tcgsize; regsrc1, regsrc2, regdst: tregister64);
  1645. var
  1646. l: tlocation;
  1647. begin
  1648. a_op64_reg_reg_reg_checkoverflow(list, op, size, regsrc1, regsrc2, regdst, False, l);
  1649. end;
  1650. procedure TCg64MPSel.a_op64_const_reg_reg_checkoverflow(list: tasmlist; op: TOpCG; size: tcgsize; Value: int64; regsrc, regdst: tregister64; setflags: boolean; var ovloc: tlocation);
  1651. var
  1652. tmplo,carry: TRegister;
  1653. hisize: tcgsize;
  1654. begin
  1655. carry:=NR_NO;
  1656. if (size in [OS_S64]) then
  1657. hisize:=OS_S32
  1658. else
  1659. hisize:=OS_32;
  1660. case op of
  1661. OP_AND,OP_OR,OP_XOR:
  1662. begin
  1663. cg.a_op_const_reg_reg(list,op,OS_32,aint(lo(value)),regsrc.reglo,regdst.reglo);
  1664. cg.a_op_const_reg_reg(list,op,OS_32,aint(hi(value)),regsrc.reghi,regdst.reghi);
  1665. end;
  1666. OP_ADD:
  1667. begin
  1668. if lo(value)<>0 then
  1669. begin
  1670. tmplo:=cg.GetIntRegister(list,OS_32);
  1671. carry:=cg.GetIntRegister(list,OS_32);
  1672. tcgmips(cg).handle_reg_const_reg(list,A_ADDU,regsrc.reglo,aint(lo(value)),tmplo);
  1673. list.concat(taicpu.op_reg_reg_reg(A_SLTU,carry,tmplo,regsrc.reglo));
  1674. cg.a_load_reg_reg(list,OS_32,OS_32,tmplo,regdst.reglo);
  1675. end
  1676. else
  1677. cg.a_load_reg_reg(list,OS_32,OS_32,regsrc.reglo,regdst.reglo);
  1678. { With overflow checking and unsigned args, this generates slighly suboptimal code
  1679. ($80000000 constant loaded twice). Other cases are fine. Getting it perfect does not
  1680. look worth the effort. }
  1681. cg.a_op_const_reg_reg_checkoverflow(list,OP_ADD,hisize,aint(hi(value)),regsrc.reghi,regdst.reghi,setflags,ovloc);
  1682. if carry<>NR_NO then
  1683. cg.a_op_reg_reg_reg_checkoverflow(list,OP_ADD,hisize,carry,regdst.reghi,regdst.reghi,setflags,ovloc);
  1684. end;
  1685. OP_SUB:
  1686. begin
  1687. carry:=NR_NO;
  1688. if lo(value)<>0 then
  1689. begin
  1690. tmplo:=cg.GetIntRegister(list,OS_32);
  1691. carry:=cg.GetIntRegister(list,OS_32);
  1692. tcgmips(cg).handle_reg_const_reg(list,A_SUBU,regsrc.reglo,aint(lo(value)),tmplo);
  1693. list.concat(taicpu.op_reg_reg_reg(A_SLTU,carry,regsrc.reglo,tmplo));
  1694. cg.a_load_reg_reg(list,OS_32,OS_32,tmplo,regdst.reglo);
  1695. end
  1696. else
  1697. cg.a_load_reg_reg(list,OS_32,OS_32,regsrc.reglo,regdst.reglo);
  1698. cg.a_op_const_reg_reg_checkoverflow(list,OP_SUB,hisize,aint(hi(value)),regsrc.reghi,regdst.reghi,setflags,ovloc);
  1699. if carry<>NR_NO then
  1700. cg.a_op_reg_reg_reg_checkoverflow(list,OP_SUB,hisize,carry,regdst.reghi,regdst.reghi,setflags,ovloc);
  1701. end;
  1702. else
  1703. InternalError(2013050301);
  1704. end;
  1705. end;
  1706. procedure TCg64MPSel.a_op64_reg_reg_reg_checkoverflow(list: tasmlist; op: TOpCG; size: tcgsize; regsrc1, regsrc2, regdst: tregister64; setflags: boolean; var ovloc: tlocation);
  1707. var
  1708. tmplo,tmphi,carry,hreg: TRegister;
  1709. signed: boolean;
  1710. begin
  1711. case op of
  1712. OP_ADD:
  1713. begin
  1714. signed:=(size in [OS_S64]);
  1715. tmplo := cg.GetIntRegister(list,OS_S32);
  1716. carry := cg.GetIntRegister(list,OS_S32);
  1717. // destreg.reglo could be regsrc1.reglo or regsrc2.reglo
  1718. list.concat(taicpu.op_reg_reg_reg(A_ADDU, tmplo, regsrc2.reglo, regsrc1.reglo));
  1719. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, tmplo, regsrc2.reglo));
  1720. cg.a_load_reg_reg(list,OS_INT,OS_INT,tmplo,regdst.reglo);
  1721. if signed or (not setflags) then
  1722. begin
  1723. list.concat(taicpu.op_reg_reg_reg(ops_add[setflags and signed], regdst.reghi, regsrc2.reghi, regsrc1.reghi));
  1724. list.concat(taicpu.op_reg_reg_reg(ops_add[setflags and signed], regdst.reghi, regdst.reghi, carry));
  1725. end
  1726. else
  1727. begin
  1728. tmphi:=cg.GetIntRegister(list,OS_INT);
  1729. hreg:=cg.GetIntRegister(list,OS_INT);
  1730. cg.a_load_const_reg(list,OS_INT,$80000000,hreg);
  1731. // first add carry to one of the addends
  1732. list.concat(taicpu.op_reg_reg_reg(A_ADDU, tmphi, regsrc2.reghi, carry));
  1733. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, tmphi, regsrc2.reghi));
  1734. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1735. // then add another addend
  1736. list.concat(taicpu.op_reg_reg_reg(A_ADDU, regdst.reghi, tmphi, regsrc1.reghi));
  1737. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, regdst.reghi, tmphi));
  1738. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1739. end;
  1740. end;
  1741. OP_SUB:
  1742. begin
  1743. signed:=(size in [OS_S64]);
  1744. tmplo := cg.GetIntRegister(list,OS_S32);
  1745. carry := cg.GetIntRegister(list,OS_S32);
  1746. // destreg.reglo could be regsrc1.reglo or regsrc2.reglo
  1747. list.concat(taicpu.op_reg_reg_reg(A_SUBU, tmplo, regsrc2.reglo, regsrc1.reglo));
  1748. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, regsrc2.reglo,tmplo));
  1749. cg.a_load_reg_reg(list,OS_INT,OS_INT,tmplo,regdst.reglo);
  1750. if signed or (not setflags) then
  1751. begin
  1752. list.concat(taicpu.op_reg_reg_reg(ops_sub[setflags and signed], regdst.reghi, regsrc2.reghi, regsrc1.reghi));
  1753. list.concat(taicpu.op_reg_reg_reg(ops_sub[setflags and signed], regdst.reghi, regdst.reghi, carry));
  1754. end
  1755. else
  1756. begin
  1757. tmphi:=cg.GetIntRegister(list,OS_INT);
  1758. hreg:=cg.GetIntRegister(list,OS_INT);
  1759. cg.a_load_const_reg(list,OS_INT,$80000000,hreg);
  1760. // first subtract the carry...
  1761. list.concat(taicpu.op_reg_reg_reg(A_SUBU, tmphi, regsrc2.reghi, carry));
  1762. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, regsrc2.reghi, tmphi));
  1763. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1764. // ...then the subtrahend
  1765. list.concat(taicpu.op_reg_reg_reg(A_SUBU, regdst.reghi, tmphi, regsrc1.reghi));
  1766. list.concat(taicpu.op_reg_reg_reg(A_SLTU, carry, tmphi, regdst.reghi));
  1767. list.concat(taicpu.op_reg_reg_reg(A_SUB, carry, hreg, carry));
  1768. end;
  1769. end;
  1770. OP_AND,OP_OR,OP_XOR:
  1771. begin
  1772. cg.a_op_reg_reg_reg(list,op,size,regsrc1.reglo,regsrc2.reglo,regdst.reglo);
  1773. cg.a_op_reg_reg_reg(list,op,size,regsrc1.reghi,regsrc2.reghi,regdst.reghi);
  1774. end;
  1775. else
  1776. internalerror(200306017);
  1777. end;
  1778. end;
  1779. {$endif mips64}
  1780. procedure create_codegen;
  1781. begin
  1782. cg:=TCGMIPS.Create;
  1783. {$ifndef mips64}
  1784. cg64:=TCg64MPSel.Create;
  1785. {$endif mips64}
  1786. end;
  1787. end.