cgcpu.pas 66 KB

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