rgobj.pas 66 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070
  1. {
  2. $Id$
  3. Copyright (c) 1998-2002 by Florian Klaempfl
  4. This unit implements the base class for the register allocator
  5. This program is free software; you can redistribute it and/or modify
  6. it under the terms of the GNU General Public License as published by
  7. the Free Software Foundation; either version 2 of the License, or
  8. (at your option) any later version.
  9. This program is distributed in the hope that it will be useful,
  10. but WITHOUT ANY WARRANTY; without even the implied warranty of
  11. MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
  12. GNU General Public License for more details.
  13. You should have received a copy of the GNU General Public License
  14. along with this program; if not, write to the Free Software
  15. Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
  16. ****************************************************************************
  17. }
  18. {$i fpcdefs.inc}
  19. { Allow duplicate allocations, can be used to get the .s file written }
  20. { $define ALLOWDUPREG}
  21. {#******************************************************************************
  22. @abstract(Abstract register allocator unit)
  23. Register allocator introduction.
  24. Free Pascal uses a Chaitin style register allocator. We use a variant similair
  25. to the one described in the book "Modern compiler implementation in C" by
  26. Andrew W. Appel., published by Cambridge University Press.
  27. The register allocator that is described by Appel uses a much improved way
  28. of register coalescing, called "iterated register coalescing". Instead
  29. of doing coalescing as a prepass to the register allocation, the coalescing
  30. is done inside the register allocator. This has the advantage that the
  31. register allocator can coalesce very aggresively without introducing spills.
  32. Reading this book is recommended for a complete understanding. Here is a small
  33. introduction.
  34. The code generator thinks it has an infinite amount of registers. Our processor
  35. has a limited amount of registers. Therefore we must reduce the amount of
  36. registers until there are less enough to fit into the processors registers.
  37. Registers can interfere or not interfere. If two imaginary registers interfere
  38. they cannot be placed into the same psysical register. Reduction of registers
  39. is done by:
  40. - "coalescing" Two registers that do not interfere are combined
  41. into one register.
  42. - "spilling" A register is changed into a memory location and the generated
  43. code is modified to use the memory location instead of the register.
  44. Register allocation is a graph colouring problem. Each register is a colour, and
  45. if two registers interfere there is a connection between them in the graph.
  46. In addition to the imaginary registers in the code generator, the psysical
  47. CPU registers are also present in this graph. This allows us to make
  48. interferences between imaginary registers and cpu registers. This is very
  49. usefull for describing architectural constraints, like for example that
  50. the div instruction modifies edx, so variables that are in use at that time
  51. cannot be stored into edx. This can be modelled by making edx interfere
  52. with those variables.
  53. Graph colouring is an NP complete problem. Therefore we use an approximation
  54. that pushes registers to colour on to a stack. This is done in the "simplify"
  55. procedure.
  56. The register allocator first checks which registers are a candidate for
  57. coalescing.
  58. *******************************************************************************}
  59. unit rgobj;
  60. interface
  61. uses
  62. cutils, cpubase,
  63. aasmbase,aasmtai,aasmcpu,
  64. cclasses,globtype,cgbase,node,
  65. {$ifdef delphi}
  66. dmisc,
  67. {$endif}
  68. cpuinfo
  69. ;
  70. type
  71. {
  72. regvarother_longintarray = array[tregisterindex] of longint;
  73. regvarother_booleanarray = array[tregisterindex] of boolean;
  74. regvarint_longintarray = array[first_int_supreg..last_int_supreg] of longint;
  75. regvarint_ptreearray = array[first_int_supreg..last_int_supreg] of tnode;
  76. }
  77. {
  78. The interference bitmap contains of 2 layers:
  79. layer 1 - 256*256 blocks with pointers to layer 2 blocks
  80. layer 2 - blocks of 32*256 (32 bytes = 256 bits)
  81. }
  82. Tinterferencebitmap2 = array[byte] of set of byte;
  83. Pinterferencebitmap2 = ^Tinterferencebitmap2;
  84. Tinterferencebitmap1 = array[byte] of Pinterferencebitmap2;
  85. pinterferencebitmap1 = ^tinterferencebitmap1;
  86. Tinterferencebitmap=class
  87. private
  88. maxx1,
  89. maxy1 : byte;
  90. fbitmap : pinterferencebitmap1;
  91. function getbitmap(x,y:tsuperregister):boolean;
  92. procedure setbitmap(x,y:tsuperregister;b:boolean);
  93. public
  94. constructor create;
  95. destructor destroy;override;
  96. property bitmap[x,y:tsuperregister]:boolean read getbitmap write setbitmap;default;
  97. end;
  98. Tmovelistheader=record
  99. count,
  100. maxcount,
  101. sorted_until : cardinal;
  102. end;
  103. Tmovelist=record
  104. header : Tmovelistheader;
  105. data : array[tsuperregister] of Tlinkedlistitem;
  106. end;
  107. Pmovelist=^Tmovelist;
  108. {In the register allocator we keep track of move instructions.
  109. These instructions are moved between five linked lists. There
  110. is also a linked list per register to keep track about the moves
  111. it is associated with. Because we need to determine quickly in
  112. which of the five lists it is we add anu enumeradtion to each
  113. move instruction.}
  114. Tmoveset=(ms_coalesced_moves,ms_constrained_moves,ms_frozen_moves,
  115. ms_worklist_moves,ms_active_moves);
  116. Tmoveins=class(Tlinkedlistitem)
  117. moveset:Tmoveset;
  118. x,y:Tsuperregister;
  119. end;
  120. Treginfoflag=(ri_coalesced,ri_selected);
  121. Treginfoflagset=set of Treginfoflag;
  122. Treginfo=record
  123. live_start,
  124. live_end : Tai;
  125. subreg : tsubregister;
  126. alias : Tsuperregister;
  127. { The register allocator assigns each register a colour }
  128. colour : Tsuperregister;
  129. movelist : Pmovelist;
  130. adjlist : Psuperregisterworklist;
  131. degree : TSuperregister;
  132. flags : Treginfoflagset;
  133. end;
  134. Preginfo=^TReginfo;
  135. tspillreginfo = record
  136. spillreg : tregister;
  137. orgreg : tsuperregister;
  138. tempreg : tregister;
  139. regread,regwritten, mustbespilled: boolean;
  140. end;
  141. tspillregsinfo = array[0..2] of tspillreginfo;
  142. {#------------------------------------------------------------------
  143. This class implements the default register allocator. It is used by the
  144. code generator to allocate and free registers which might be valid
  145. across nodes. It also contains utility routines related to registers.
  146. Some of the methods in this class should be overriden
  147. by cpu-specific implementations.
  148. --------------------------------------------------------------------}
  149. trgobj=class
  150. preserved_by_proc : tcpuregisterset;
  151. used_in_proc : tcpuregisterset;
  152. // is_reg_var : Tsuperregisterset; {old regvars}
  153. // reg_var_loaded:Tsuperregisterset; {old regvars}
  154. constructor create(Aregtype:Tregistertype;
  155. Adefaultsub:Tsubregister;
  156. const Ausable:array of tsuperregister;
  157. Afirst_imaginary:Tsuperregister;
  158. Apreserved_by_proc:Tcpuregisterset);
  159. destructor destroy;override;
  160. {# Allocate a register. An internalerror will be generated if there is
  161. no more free registers which can be allocated.}
  162. function getregister(list:Taasmoutput;subreg:Tsubregister):Tregister;virtual;
  163. {# Get the register specified.}
  164. procedure getexplicitregister(list:Taasmoutput;r:Tregister);virtual;
  165. {# Get multiple registers specified.}
  166. procedure allocexplicitregisters(list:Taasmoutput;r:Tcpuregisterset);virtual;
  167. {# Free multiple registers specified.}
  168. procedure deallocexplicitregisters(list:Taasmoutput;r:Tcpuregisterset);virtual;
  169. function uses_registers:boolean;virtual;
  170. {# Deallocate any kind of register }
  171. procedure ungetregister(list:Taasmoutput;r:Tregister);virtual;
  172. procedure add_reg_instruction(instr:Tai;r:tregister);
  173. procedure add_move_instruction(instr:Taicpu);
  174. {# Do the register allocation.}
  175. procedure do_register_allocation(list:Taasmoutput;headertai:tai);virtual;
  176. { Adds an interference edge.
  177. don't move this to the protected section, the arm cg requires to access this (FK) }
  178. procedure add_edge(u,v:Tsuperregister);
  179. protected
  180. regtype : Tregistertype;
  181. { default subregister used }
  182. defaultsub : tsubregister;
  183. live_registers:Tsuperregisterworklist;
  184. { can be overriden to add cpu specific interferences }
  185. procedure add_cpu_interferences(p : tai);virtual;
  186. function get_insert_pos(p:Tai;huntfor1,huntfor2,huntfor3:Tsuperregister):Tai;
  187. procedure forward_allocation(pfrom,pto:Tai);
  188. procedure getregisterinline(list:Taasmoutput;position:Tai;subreg:Tsubregister;var result:Tregister);
  189. procedure ungetregisterinline(list:Taasmoutput;position:Tai;r:Tregister);
  190. procedure add_constraints(reg:Tregister);virtual;
  191. function get_spill_subreg(r : tregister) : tsubregister;virtual;
  192. procedure do_spill_read(list:Taasmoutput;instr:Taicpu;
  193. pos:Tai;regidx:word;
  194. const spilltemplist:Tspill_temp_list;
  195. const regs:Tspillregsinfo);virtual;
  196. procedure do_spill_written(list:Taasmoutput;instr:Taicpu;
  197. pos:Tai;regidx:word;
  198. const spilltemplist:Tspill_temp_list;
  199. const regs:Tspillregsinfo);virtual;
  200. procedure do_spill_readwritten(list:Taasmoutput;instr:Taicpu;
  201. pos:Tai;regidx:word;
  202. const spilltemplist:Tspill_temp_list;
  203. const regs:Tspillregsinfo);virtual;
  204. function instr_spill_register(list:Taasmoutput;
  205. instr:taicpu;
  206. const r:Tsuperregisterset;
  207. const spilltemplist:Tspill_temp_list): boolean;virtual;
  208. private
  209. {# First imaginary register.}
  210. first_imaginary : Tsuperregister;
  211. {# Highest register allocated until now.}
  212. reginfo : PReginfo;
  213. maxreginfo,
  214. maxreginfoinc,
  215. maxreg : Tsuperregister;
  216. usable_registers_cnt : word;
  217. usable_registers : array[0..maxcpuregister-1] of tsuperregister;
  218. ibitmap : Tinterferencebitmap;
  219. spillednodes,
  220. simplifyworklist,
  221. freezeworklist,
  222. spillworklist,
  223. coalescednodes,
  224. selectstack : tsuperregisterworklist;
  225. worklist_moves,
  226. active_moves,
  227. frozen_moves,
  228. coalesced_moves,
  229. constrained_moves : Tlinkedlist;
  230. {$ifdef EXTDEBUG}
  231. procedure writegraph(loopidx:longint);
  232. {$endif EXTDEBUG}
  233. {# Disposes of the reginfo array.}
  234. procedure dispose_reginfo;
  235. {# Prepare the register colouring.}
  236. procedure prepare_colouring;
  237. {# Clean up after register colouring.}
  238. procedure epilogue_colouring;
  239. {# Colour the registers; that is do the register allocation.}
  240. procedure colour_registers;
  241. {# Spills certain registers in the specified assembler list.}
  242. procedure insert_regalloc_info(list:Taasmoutput;headertai:tai);
  243. procedure generate_interference_graph(list:Taasmoutput;headertai:tai);
  244. procedure translate_registers(list:Taasmoutput);
  245. function spill_registers(list:Taasmoutput;headertai:tai):boolean;virtual;
  246. function getnewreg(subreg:tsubregister):tsuperregister;
  247. procedure add_edges_used(u:Tsuperregister);
  248. procedure add_to_movelist(u:Tsuperregister;data:Tlinkedlistitem);
  249. function move_related(n:Tsuperregister):boolean;
  250. procedure make_work_list;
  251. procedure sort_simplify_worklist;
  252. procedure enable_moves(n:Tsuperregister);
  253. procedure decrement_degree(m:Tsuperregister);
  254. procedure simplify;
  255. function get_alias(n:Tsuperregister):Tsuperregister;
  256. procedure add_worklist(u:Tsuperregister);
  257. function adjacent_ok(u,v:Tsuperregister):boolean;
  258. function conservative(u,v:Tsuperregister):boolean;
  259. procedure combine(u,v:Tsuperregister);
  260. procedure coalesce;
  261. procedure freeze_moves(u:Tsuperregister);
  262. procedure freeze;
  263. procedure select_spill;
  264. procedure assign_colours;
  265. procedure clear_interferences(u:Tsuperregister);
  266. end;
  267. const
  268. first_reg = 0;
  269. last_reg = high(tsuperregister)-1;
  270. maxspillingcounter = 20;
  271. implementation
  272. uses
  273. systems,
  274. globals,verbose,tgobj,procinfo;
  275. procedure sort_movelist(ml:Pmovelist);
  276. {Ok, sorting pointers is silly, but it does the job to make Trgobj.combine
  277. faster.}
  278. var h,i,p:word;
  279. t:Tlinkedlistitem;
  280. begin
  281. with ml^ do
  282. begin
  283. if header.count<2 then
  284. exit;
  285. p:=1;
  286. while 2*p<header.count do
  287. p:=2*p;
  288. while p<>0 do
  289. begin
  290. for h:=p to header.count-1 do
  291. begin
  292. i:=h;
  293. t:=data[i];
  294. repeat
  295. if ptrint(data[i-p])<=ptrint(t) then
  296. break;
  297. data[i]:=data[i-p];
  298. dec(i,p);
  299. until i<p;
  300. data[i]:=t;
  301. end;
  302. p:=p shr 1;
  303. end;
  304. header.sorted_until:=header.count-1;
  305. end;
  306. end;
  307. {******************************************************************************
  308. tinterferencebitmap
  309. ******************************************************************************}
  310. constructor tinterferencebitmap.create;
  311. begin
  312. inherited create;
  313. maxx1:=1;
  314. getmem(fbitmap,sizeof(tinterferencebitmap1)*2);
  315. fillchar(fbitmap^,sizeof(tinterferencebitmap1)*2,0);
  316. end;
  317. destructor tinterferencebitmap.destroy;
  318. var i,j:byte;
  319. begin
  320. for i:=0 to maxx1 do
  321. for j:=0 to maxy1 do
  322. if assigned(fbitmap[i,j]) then
  323. dispose(fbitmap[i,j]);
  324. freemem(fbitmap);
  325. end;
  326. function tinterferencebitmap.getbitmap(x,y:tsuperregister):boolean;
  327. var
  328. page : pinterferencebitmap2;
  329. begin
  330. result:=false;
  331. if (x shr 8>maxx1) then
  332. exit;
  333. page:=fbitmap[x shr 8,y shr 8];
  334. result:=assigned(page) and
  335. ((x and $ff) in page^[y and $ff]);
  336. end;
  337. procedure tinterferencebitmap.setbitmap(x,y:tsuperregister;b:boolean);
  338. var
  339. x1,y1 : byte;
  340. begin
  341. x1:=x shr 8;
  342. y1:=y shr 8;
  343. if x1>maxx1 then
  344. begin
  345. reallocmem(fbitmap,sizeof(tinterferencebitmap1)*(x1+1));
  346. fillchar(fbitmap[maxx1+1],sizeof(tinterferencebitmap1)*(x1-maxx1),0);
  347. maxx1:=x1;
  348. end;
  349. if not assigned(fbitmap[x1,y1]) then
  350. begin
  351. if y1>maxy1 then
  352. maxy1:=y1;
  353. new(fbitmap[x1,y1]);
  354. fillchar(fbitmap[x1,y1]^,sizeof(tinterferencebitmap2),0);
  355. end;
  356. if b then
  357. include(fbitmap[x1,y1]^[y and $ff],(x and $ff))
  358. else
  359. exclude(fbitmap[x1,y1]^[y and $ff],(x and $ff));
  360. end;
  361. {******************************************************************************
  362. trgobj
  363. ******************************************************************************}
  364. constructor trgobj.create(Aregtype:Tregistertype;
  365. Adefaultsub:Tsubregister;
  366. const Ausable:array of tsuperregister;
  367. Afirst_imaginary:Tsuperregister;
  368. Apreserved_by_proc:Tcpuregisterset);
  369. var
  370. i : Tsuperregister;
  371. begin
  372. { empty super register sets can cause very strange problems }
  373. if high(Ausable)=0 then
  374. internalerror(200210181);
  375. first_imaginary:=Afirst_imaginary;
  376. maxreg:=Afirst_imaginary;
  377. regtype:=Aregtype;
  378. defaultsub:=Adefaultsub;
  379. preserved_by_proc:=Apreserved_by_proc;
  380. used_in_proc:=[];
  381. live_registers.init;
  382. { Get reginfo for CPU registers }
  383. maxreginfo:=first_imaginary;
  384. maxreginfoinc:=16;
  385. worklist_moves:=Tlinkedlist.create;
  386. reginfo:=allocmem(first_imaginary*sizeof(treginfo));
  387. for i:=0 to first_imaginary-1 do
  388. begin
  389. reginfo[i].degree:=high(tsuperregister);
  390. reginfo[i].alias:=RS_INVALID;
  391. end;
  392. { Usable registers }
  393. fillchar(usable_registers,sizeof(usable_registers),0);
  394. for i:=low(Ausable) to high(Ausable) do
  395. usable_registers[i]:=Ausable[i];
  396. usable_registers_cnt:=high(Ausable)+1;
  397. { Initialize Worklists }
  398. spillednodes.init;
  399. simplifyworklist.init;
  400. freezeworklist.init;
  401. spillworklist.init;
  402. coalescednodes.init;
  403. selectstack.init;
  404. end;
  405. destructor trgobj.destroy;
  406. begin
  407. spillednodes.done;
  408. simplifyworklist.done;
  409. freezeworklist.done;
  410. spillworklist.done;
  411. coalescednodes.done;
  412. selectstack.done;
  413. live_registers.done;
  414. worklist_moves.free;
  415. dispose_reginfo;
  416. end;
  417. procedure Trgobj.dispose_reginfo;
  418. var i:Tsuperregister;
  419. begin
  420. if reginfo<>nil then
  421. begin
  422. for i:=0 to maxreg-1 do
  423. with reginfo[i] do
  424. begin
  425. if adjlist<>nil then
  426. dispose(adjlist,done);
  427. if movelist<>nil then
  428. dispose(movelist);
  429. end;
  430. freemem(reginfo);
  431. reginfo:=nil;
  432. end;
  433. end;
  434. function trgobj.getnewreg(subreg:tsubregister):tsuperregister;
  435. var
  436. oldmaxreginfo : tsuperregister;
  437. begin
  438. result:=maxreg;
  439. inc(maxreg);
  440. if maxreg>=last_reg then
  441. internalerror(200310146);
  442. if maxreg>=maxreginfo then
  443. begin
  444. oldmaxreginfo:=maxreginfo;
  445. inc(maxreginfo,maxreginfoinc);
  446. if maxreginfoinc<256 then
  447. maxreginfoinc:=maxreginfoinc*2;
  448. reallocmem(reginfo,maxreginfo*sizeof(treginfo));
  449. { Do we really need it to clear it ? At least for 1.0.x (PFV) }
  450. fillchar(reginfo[oldmaxreginfo],(maxreginfo-oldmaxreginfo)*sizeof(treginfo),0);
  451. end;
  452. reginfo[result].subreg:=subreg;
  453. end;
  454. function trgobj.getregister(list:Taasmoutput;subreg:Tsubregister):Tregister;
  455. begin
  456. {$ifdef EXTDEBUG}
  457. if reginfo=nil then
  458. InternalError(2004020901);
  459. {$endif EXTDEBUG}
  460. if defaultsub=R_SUBNONE then
  461. result:=newreg(regtype,getnewreg(R_SUBNONE),R_SUBNONE)
  462. else
  463. result:=newreg(regtype,getnewreg(subreg),subreg);
  464. end;
  465. function trgobj.uses_registers:boolean;
  466. begin
  467. result:=(maxreg>first_imaginary);
  468. end;
  469. procedure trgobj.ungetregister(list:Taasmoutput;r:Tregister);
  470. begin
  471. {$ifdef EXTDEBUG}
  472. if (reginfo=nil) and (getsupreg(r)>=first_imaginary) then
  473. InternalError(2004020901);
  474. {$endif EXTDEBUG}
  475. { Only explicit allocs insert regalloc info }
  476. if getsupreg(r)<first_imaginary then
  477. list.concat(Tai_regalloc.dealloc(r));
  478. end;
  479. procedure trgobj.getexplicitregister(list:Taasmoutput;r:Tregister);
  480. var
  481. supreg:Tsuperregister;
  482. begin
  483. supreg:=getsupreg(r);
  484. if supreg>=first_imaginary then
  485. internalerror(2003121503);
  486. include(used_in_proc,supreg);
  487. list.concat(Tai_regalloc.alloc(r));
  488. end;
  489. procedure trgobj.allocexplicitregisters(list:Taasmoutput;r:Tcpuregisterset);
  490. var i:Tsuperregister;
  491. begin
  492. for i:=0 to first_imaginary-1 do
  493. if i in r then
  494. getexplicitregister(list,newreg(regtype,i,defaultsub));
  495. end;
  496. procedure trgobj.deallocexplicitregisters(list:Taasmoutput;r:Tcpuregisterset);
  497. var i:Tsuperregister;
  498. begin
  499. for i:=0 to first_imaginary-1 do
  500. if i in r then
  501. ungetregister(list,newreg(regtype,i,defaultsub));
  502. end;
  503. procedure trgobj.do_register_allocation(list:Taasmoutput;headertai:tai);
  504. var
  505. spillingcounter:byte;
  506. endspill:boolean;
  507. i:Tsuperregister;
  508. begin
  509. { Insert regalloc info for imaginary registers }
  510. insert_regalloc_info(list,headertai);
  511. ibitmap:=tinterferencebitmap.create;
  512. generate_interference_graph(list,headertai);
  513. { Don't do the real allocation when -sr is passed }
  514. if (cs_no_regalloc in aktglobalswitches) then
  515. exit;
  516. {Do register allocation.}
  517. spillingcounter:=0;
  518. repeat
  519. prepare_colouring;
  520. colour_registers;
  521. epilogue_colouring;
  522. endspill:=true;
  523. if spillednodes.length<>0 then
  524. begin
  525. inc(spillingcounter);
  526. if spillingcounter>maxspillingcounter then
  527. internalerror(200309041);
  528. endspill:=not spill_registers(list,headertai);
  529. end;
  530. until endspill;
  531. ibitmap.free;
  532. translate_registers(list);
  533. dispose_reginfo;
  534. end;
  535. procedure trgobj.add_constraints(reg:Tregister);
  536. begin
  537. end;
  538. procedure trgobj.add_edge(u,v:Tsuperregister);
  539. {This procedure will add an edge to the virtual interference graph.}
  540. procedure addadj(u,v:Tsuperregister);
  541. begin
  542. with reginfo[u] do
  543. begin
  544. if adjlist=nil then
  545. new(adjlist,init);
  546. adjlist^.add(v);
  547. end;
  548. end;
  549. begin
  550. if (u<>v) and not(ibitmap[v,u]) then
  551. begin
  552. ibitmap[v,u]:=true;
  553. ibitmap[u,v]:=true;
  554. {Precoloured nodes are not stored in the interference graph.}
  555. if (u>=first_imaginary) then
  556. addadj(u,v);
  557. if (v>=first_imaginary) then
  558. addadj(v,u);
  559. end;
  560. end;
  561. procedure trgobj.add_edges_used(u:Tsuperregister);
  562. var i:word;
  563. begin
  564. with live_registers do
  565. if length>0 then
  566. for i:=0 to length-1 do
  567. add_edge(u,buf^[i]);
  568. end;
  569. {$ifdef EXTDEBUG}
  570. procedure trgobj.writegraph(loopidx:longint);
  571. {This procedure writes out the current interference graph in the
  572. register allocator.}
  573. var f:text;
  574. i,j:Tsuperregister;
  575. begin
  576. assign(f,'igraph'+tostr(loopidx));
  577. rewrite(f);
  578. writeln(f,'Interference graph');
  579. writeln(f);
  580. write(f,' ');
  581. for i:=0 to 15 do
  582. for j:=0 to 15 do
  583. write(f,hexstr(i,1));
  584. writeln(f);
  585. write(f,' ');
  586. for i:=0 to 15 do
  587. write(f,'0123456789ABCDEF');
  588. writeln(f);
  589. for i:=0 to maxreg-1 do
  590. begin
  591. write(f,hexstr(i,2):4);
  592. for j:=0 to maxreg-1 do
  593. if ibitmap[i,j] then
  594. write(f,'*')
  595. else
  596. write(f,'-');
  597. writeln(f);
  598. end;
  599. close(f);
  600. end;
  601. {$endif EXTDEBUG}
  602. procedure trgobj.add_to_movelist(u:Tsuperregister;data:Tlinkedlistitem);
  603. begin
  604. with reginfo[u] do
  605. begin
  606. if movelist=nil then
  607. begin
  608. getmem(movelist,sizeof(tmovelistheader)+60*sizeof(pointer));
  609. movelist^.header.maxcount:=60;
  610. movelist^.header.count:=0;
  611. movelist^.header.sorted_until:=0;
  612. end
  613. else
  614. begin
  615. if movelist^.header.count>=movelist^.header.maxcount then
  616. begin
  617. movelist^.header.maxcount:=movelist^.header.maxcount*2;
  618. reallocmem(movelist,sizeof(tmovelistheader)+movelist^.header.maxcount*sizeof(pointer));
  619. end;
  620. end;
  621. movelist^.data[movelist^.header.count]:=data;
  622. inc(movelist^.header.count);
  623. end;
  624. end;
  625. procedure trgobj.add_reg_instruction(instr:Tai;r:tregister);
  626. var
  627. supreg : tsuperregister;
  628. begin
  629. supreg:=getsupreg(r);
  630. if supreg>=first_imaginary then
  631. with reginfo[supreg] do
  632. begin
  633. if not assigned(live_start) then
  634. live_start:=instr;
  635. live_end:=instr;
  636. end;
  637. end;
  638. procedure trgobj.add_move_instruction(instr:Taicpu);
  639. {This procedure notifies a certain as a move instruction so the
  640. register allocator can try to eliminate it.}
  641. var i:Tmoveins;
  642. ssupreg,dsupreg:Tsuperregister;
  643. begin
  644. {$ifdef extdebug}
  645. if (instr.oper[O_MOV_SOURCE]^.typ<>top_reg) or
  646. (instr.oper[O_MOV_DEST]^.typ<>top_reg) then
  647. internalerror(200311291);
  648. {$endif}
  649. i:=Tmoveins.create;
  650. i.moveset:=ms_worklist_moves;
  651. worklist_moves.insert(i);
  652. ssupreg:=getsupreg(instr.oper[O_MOV_SOURCE]^.reg);
  653. add_to_movelist(ssupreg,i);
  654. dsupreg:=getsupreg(instr.oper[O_MOV_DEST]^.reg);
  655. if ssupreg<>dsupreg then
  656. {Avoid adding the same move instruction twice to a single register.}
  657. add_to_movelist(dsupreg,i);
  658. i.x:=ssupreg;
  659. i.y:=dsupreg;
  660. end;
  661. function trgobj.move_related(n:Tsuperregister):boolean;
  662. var i:cardinal;
  663. begin
  664. move_related:=false;
  665. with reginfo[n] do
  666. if movelist<>nil then
  667. with movelist^ do
  668. for i:=0 to header.count-1 do
  669. if Tmoveins(data[i]).moveset in [ms_worklist_moves,ms_active_moves] then
  670. begin
  671. move_related:=true;
  672. break;
  673. end;
  674. end;
  675. procedure Trgobj.sort_simplify_worklist;
  676. {Sorts the simplifyworklist by the number of interferences the
  677. registers in it cause. This allows simplify to execute in
  678. constant time.}
  679. var p,h,i,leni,lent:word;
  680. t:Tsuperregister;
  681. adji,adjt:Psuperregisterworklist;
  682. begin
  683. with simplifyworklist do
  684. begin
  685. if length<2 then
  686. exit;
  687. p:=1;
  688. while 2*p<length do
  689. p:=2*p;
  690. while p<>0 do
  691. begin
  692. for h:=p to length-1 do
  693. begin
  694. i:=h;
  695. t:=buf^[i];
  696. adjt:=reginfo[buf^[i]].adjlist;
  697. lent:=0;
  698. if adjt<>nil then
  699. lent:=adjt^.length;
  700. repeat
  701. adji:=reginfo[buf^[i-p]].adjlist;
  702. leni:=0;
  703. if adji<>nil then
  704. leni:=adji^.length;
  705. if leni<=lent then
  706. break;
  707. buf^[i]:=buf^[i-p];
  708. dec(i,p)
  709. until i<p;
  710. buf^[i]:=t;
  711. end;
  712. p:=p shr 1;
  713. end;
  714. end;
  715. end;
  716. procedure trgobj.make_work_list;
  717. var n:Tsuperregister;
  718. begin
  719. {If we have 7 cpu registers, and the degree of a node is 7, we cannot
  720. assign it to any of the registers, thus it is significant.}
  721. for n:=first_imaginary to maxreg-1 do
  722. with reginfo[n] do
  723. begin
  724. if adjlist=nil then
  725. degree:=0
  726. else
  727. degree:=adjlist^.length;
  728. if degree>=usable_registers_cnt then
  729. spillworklist.add(n)
  730. else if move_related(n) then
  731. freezeworklist.add(n)
  732. else
  733. simplifyworklist.add(n);
  734. end;
  735. sort_simplify_worklist;
  736. end;
  737. procedure trgobj.prepare_colouring;
  738. var i:word;
  739. begin
  740. make_work_list;
  741. active_moves:=Tlinkedlist.create;
  742. frozen_moves:=Tlinkedlist.create;
  743. coalesced_moves:=Tlinkedlist.create;
  744. constrained_moves:=Tlinkedlist.create;
  745. selectstack.clear;
  746. end;
  747. procedure trgobj.enable_moves(n:Tsuperregister);
  748. var m:Tlinkedlistitem;
  749. i:cardinal;
  750. begin
  751. with reginfo[n] do
  752. if movelist<>nil then
  753. for i:=0 to movelist^.header.count-1 do
  754. begin
  755. m:=movelist^.data[i];
  756. if Tmoveins(m).moveset in [ms_worklist_moves,ms_active_moves] then
  757. if Tmoveins(m).moveset=ms_active_moves then
  758. begin
  759. {Move m from the set active_moves to the set worklist_moves.}
  760. active_moves.remove(m);
  761. Tmoveins(m).moveset:=ms_worklist_moves;
  762. worklist_moves.concat(m);
  763. end;
  764. end;
  765. end;
  766. procedure Trgobj.decrement_degree(m:Tsuperregister);
  767. var adj : Psuperregisterworklist;
  768. n : tsuperregister;
  769. d,i : word;
  770. begin
  771. with reginfo[m] do
  772. begin
  773. d:=degree;
  774. if d=0 then
  775. internalerror(200312151);
  776. dec(degree);
  777. if d=usable_registers_cnt then
  778. begin
  779. {Enable moves for m.}
  780. enable_moves(m);
  781. {Enable moves for adjacent.}
  782. adj:=adjlist;
  783. if adj<>nil then
  784. for i:=1 to adj^.length do
  785. begin
  786. n:=adj^.buf^[i-1];
  787. if reginfo[n].flags*[ri_selected,ri_coalesced]<>[] then
  788. enable_moves(n);
  789. end;
  790. {Remove the node from the spillworklist.}
  791. if not spillworklist.delete(m) then
  792. internalerror(200310145);
  793. if move_related(m) then
  794. freezeworklist.add(m)
  795. else
  796. simplifyworklist.add(m);
  797. end;
  798. end;
  799. end;
  800. procedure trgobj.simplify;
  801. var adj : Psuperregisterworklist;
  802. m,n : Tsuperregister;
  803. i : word;
  804. begin
  805. {We take the element with the least interferences out of the
  806. simplifyworklist. Since the simplifyworklist is now sorted, we
  807. no longer need to search, but we can simply take the first element.}
  808. m:=simplifyworklist.get;
  809. {Push it on the selectstack.}
  810. selectstack.add(m);
  811. with reginfo[m] do
  812. begin
  813. include(flags,ri_selected);
  814. adj:=adjlist;
  815. end;
  816. if adj<>nil then
  817. for i:=1 to adj^.length do
  818. begin
  819. n:=adj^.buf^[i-1];
  820. if (n>=first_imaginary) and
  821. (reginfo[n].flags*[ri_selected,ri_coalesced]=[]) then
  822. decrement_degree(n);
  823. end;
  824. end;
  825. function trgobj.get_alias(n:Tsuperregister):Tsuperregister;
  826. begin
  827. while ri_coalesced in reginfo[n].flags do
  828. n:=reginfo[n].alias;
  829. get_alias:=n;
  830. end;
  831. procedure trgobj.add_worklist(u:Tsuperregister);
  832. begin
  833. if (u>=first_imaginary) and
  834. (not move_related(u)) and
  835. (reginfo[u].degree<usable_registers_cnt) then
  836. begin
  837. if not freezeworklist.delete(u) then
  838. internalerror(200308161); {must be found}
  839. simplifyworklist.add(u);
  840. end;
  841. end;
  842. function trgobj.adjacent_ok(u,v:Tsuperregister):boolean;
  843. {Check wether u and v should be coalesced. u is precoloured.}
  844. function ok(t,r:Tsuperregister):boolean;
  845. begin
  846. ok:=(t<first_imaginary) or
  847. (reginfo[t].degree<usable_registers_cnt) or
  848. ibitmap[r,t];
  849. end;
  850. var adj : Psuperregisterworklist;
  851. i : word;
  852. n : tsuperregister;
  853. begin
  854. with reginfo[v] do
  855. begin
  856. adjacent_ok:=true;
  857. adj:=adjlist;
  858. if adj<>nil then
  859. for i:=1 to adj^.length do
  860. begin
  861. n:=adj^.buf^[i-1];
  862. if (flags*[ri_coalesced,ri_selected]=[]) and not ok(n,u) then
  863. begin
  864. adjacent_ok:=false;
  865. break;
  866. end;
  867. end;
  868. end;
  869. end;
  870. function trgobj.conservative(u,v:Tsuperregister):boolean;
  871. var adj : Psuperregisterworklist;
  872. done : Tsuperregisterset; {To prevent that we count nodes twice.}
  873. i,k:word;
  874. n : tsuperregister;
  875. begin
  876. k:=0;
  877. supregset_reset(done,false);
  878. with reginfo[u] do
  879. begin
  880. adj:=adjlist;
  881. if adj<>nil then
  882. for i:=1 to adj^.length do
  883. begin
  884. n:=adj^.buf^[i-1];
  885. if flags*[ri_coalesced,ri_selected]=[] then
  886. begin
  887. supregset_include(done,n);
  888. if reginfo[n].degree>=usable_registers_cnt then
  889. inc(k);
  890. end;
  891. end;
  892. end;
  893. adj:=reginfo[v].adjlist;
  894. if adj<>nil then
  895. for i:=1 to adj^.length do
  896. begin
  897. n:=adj^.buf^[i-1];
  898. if not supregset_in(done,n) and
  899. (reginfo[n].degree>=usable_registers_cnt) and
  900. (reginfo[u].flags*[ri_coalesced,ri_selected]=[]) then
  901. inc(k);
  902. end;
  903. conservative:=(k<usable_registers_cnt);
  904. end;
  905. procedure trgobj.combine(u,v:Tsuperregister);
  906. var adj : Psuperregisterworklist;
  907. i,n,p,q:cardinal;
  908. t : tsuperregister;
  909. searched:Tlinkedlistitem;
  910. label l1;
  911. begin
  912. if not freezeworklist.delete(v) then
  913. spillworklist.delete(v);
  914. coalescednodes.add(v);
  915. include(reginfo[v].flags,ri_coalesced);
  916. reginfo[v].alias:=u;
  917. {Combine both movelists. Since the movelists are sets, only add
  918. elements that are not already present. The movelists cannot be
  919. empty by definition; nodes are only coalesced if there is a move
  920. between them. To prevent quadratic time blowup (movelists of
  921. especially machine registers can get very large because of moves
  922. generated during calls) we need to go into disgusting complexity.
  923. (See webtbs/tw2242 for an example that stresses this.)
  924. We want to sort the movelist to be able to search logarithmically.
  925. Unfortunately, sorting the movelist every time before searching
  926. is counter-productive, since the movelist usually grows with a few
  927. items at a time. Therefore, we split the movelist into a sorted
  928. and an unsorted part and search through both. If the unsorted part
  929. becomes too large, we sort.}
  930. if assigned(reginfo[u].movelist) then
  931. begin
  932. {We have to weigh the cost of sorting the list against searching
  933. the cost of the unsorted part. I use factor of 8 here; if the
  934. number of items is less than 8 times the numer of unsorted items,
  935. we'll sort the list.}
  936. with reginfo[u].movelist^ do
  937. if header.count<8*(header.count-header.sorted_until) then
  938. sort_movelist(reginfo[u].movelist);
  939. if assigned(reginfo[v].movelist) then
  940. begin
  941. for n:=0 to reginfo[v].movelist^.header.count-1 do
  942. begin
  943. {Binary search the sorted part of the list.}
  944. searched:=reginfo[v].movelist^.data[n];
  945. p:=0;
  946. q:=reginfo[u].movelist^.header.sorted_until;
  947. i:=0;
  948. if q<>0 then
  949. repeat
  950. i:=(p+q) shr 1;
  951. if ptrint(searched)>ptrint(reginfo[u].movelist^.data[i]) then
  952. p:=i+1
  953. else
  954. q:=i;
  955. until p=q;
  956. with reginfo[u].movelist^ do
  957. if searched<>data[i] then
  958. begin
  959. {Linear search the unsorted part of the list.}
  960. for i:=header.sorted_until+1 to header.count-1 do
  961. if searched=data[i] then
  962. goto l1;
  963. {Not found -> add}
  964. add_to_movelist(u,searched);
  965. l1:
  966. end;
  967. end;
  968. end;
  969. end;
  970. enable_moves(v);
  971. adj:=reginfo[v].adjlist;
  972. if adj<>nil then
  973. for i:=1 to adj^.length do
  974. begin
  975. t:=adj^.buf^[i-1];
  976. with reginfo[t] do
  977. if not(ri_coalesced in flags) then
  978. begin
  979. {t has a connection to v. Since we are adding v to u, we
  980. need to connect t to u. However, beware if t was already
  981. connected to u...}
  982. if (ibitmap[t,u]) and not (ri_selected in flags) then
  983. {... because in that case, we are actually removing an edge
  984. and the degree of t decreases.}
  985. decrement_degree(t)
  986. else
  987. begin
  988. add_edge(t,u);
  989. {We have added an edge to t and u. So their degree increases.
  990. However, v is added to u. That means its neighbours will
  991. no longer point to v, but to u instead. Therefore, only the
  992. degree of u increases.}
  993. if (u>=first_imaginary) and not (ri_selected in flags) then
  994. inc(reginfo[u].degree);
  995. end;
  996. end;
  997. end;
  998. if (reginfo[u].degree>=usable_registers_cnt) and freezeworklist.delete(u) then
  999. spillworklist.add(u);
  1000. end;
  1001. procedure trgobj.coalesce;
  1002. var m:Tmoveins;
  1003. x,y,u,v:Tsuperregister;
  1004. begin
  1005. m:=Tmoveins(worklist_moves.getfirst);
  1006. x:=get_alias(m.x);
  1007. y:=get_alias(m.y);
  1008. if (y<first_imaginary) then
  1009. begin
  1010. u:=y;
  1011. v:=x;
  1012. end
  1013. else
  1014. begin
  1015. u:=x;
  1016. v:=y;
  1017. end;
  1018. if (u=v) then
  1019. begin
  1020. m.moveset:=ms_coalesced_moves; {Already coalesced.}
  1021. coalesced_moves.insert(m);
  1022. add_worklist(u);
  1023. end
  1024. {Do u and v interfere? In that case the move is constrained. Two
  1025. precoloured nodes interfere allways. If v is precoloured, by the above
  1026. code u is precoloured, thus interference...}
  1027. else if (v<first_imaginary) or ibitmap[u,v] then
  1028. begin
  1029. m.moveset:=ms_constrained_moves; {Cannot coalesce yet...}
  1030. constrained_moves.insert(m);
  1031. add_worklist(u);
  1032. add_worklist(v);
  1033. end
  1034. {Next test: is it possible and a good idea to coalesce??}
  1035. else if ((u<first_imaginary) and adjacent_ok(u,v)) or
  1036. ((u>=first_imaginary) and conservative(u,v)) then
  1037. begin
  1038. m.moveset:=ms_coalesced_moves; {Move coalesced!}
  1039. coalesced_moves.insert(m);
  1040. combine(u,v);
  1041. add_worklist(u);
  1042. end
  1043. else
  1044. begin
  1045. m.moveset:=ms_active_moves;
  1046. active_moves.insert(m);
  1047. end;
  1048. end;
  1049. procedure trgobj.freeze_moves(u:Tsuperregister);
  1050. var i:cardinal;
  1051. m:Tlinkedlistitem;
  1052. v,x,y:Tsuperregister;
  1053. begin
  1054. if reginfo[u].movelist<>nil then
  1055. for i:=0 to reginfo[u].movelist^.header.count-1 do
  1056. begin
  1057. m:=reginfo[u].movelist^.data[i];
  1058. if Tmoveins(m).moveset in [ms_worklist_moves,ms_active_moves] then
  1059. begin
  1060. x:=Tmoveins(m).x;
  1061. y:=Tmoveins(m).y;
  1062. if get_alias(y)=get_alias(u) then
  1063. v:=get_alias(x)
  1064. else
  1065. v:=get_alias(y);
  1066. {Move m from active_moves/worklist_moves to frozen_moves.}
  1067. if Tmoveins(m).moveset=ms_active_moves then
  1068. active_moves.remove(m)
  1069. else
  1070. worklist_moves.remove(m);
  1071. Tmoveins(m).moveset:=ms_frozen_moves;
  1072. frozen_moves.insert(m);
  1073. if (v>=first_imaginary) and not(move_related(v)) and
  1074. (reginfo[v].degree<usable_registers_cnt) then
  1075. begin
  1076. freezeworklist.delete(v);
  1077. simplifyworklist.add(v);
  1078. end;
  1079. end;
  1080. end;
  1081. end;
  1082. procedure trgobj.freeze;
  1083. var n:Tsuperregister;
  1084. begin
  1085. { We need to take a random element out of the freezeworklist. We take
  1086. the last element. Dirty code! }
  1087. n:=freezeworklist.get;
  1088. {Add it to the simplifyworklist.}
  1089. simplifyworklist.add(n);
  1090. freeze_moves(n);
  1091. end;
  1092. procedure trgobj.select_spill;
  1093. var
  1094. n : tsuperregister;
  1095. adj : psuperregisterworklist;
  1096. max,p,i:word;
  1097. begin
  1098. { We must look for the element with the most interferences in the
  1099. spillworklist. This is required because those registers are creating
  1100. the most conflicts and keeping them in a register will not reduce the
  1101. complexity and even can cause the help registers for the spilling code
  1102. to get too much conflicts with the result that the spilling code
  1103. will never converge (PFV) }
  1104. max:=0;
  1105. p:=0;
  1106. with spillworklist do
  1107. begin
  1108. {Safe: This procedure is only called if length<>0}
  1109. for i:=0 to length-1 do
  1110. begin
  1111. adj:=reginfo[buf^[i]].adjlist;
  1112. if assigned(adj) and (adj^.length>max) then
  1113. begin
  1114. p:=i;
  1115. max:=adj^.length;
  1116. end;
  1117. end;
  1118. n:=buf^[p];
  1119. deleteidx(p);
  1120. end;
  1121. simplifyworklist.add(n);
  1122. freeze_moves(n);
  1123. end;
  1124. procedure trgobj.assign_colours;
  1125. {Assign_colours assigns the actual colours to the registers.}
  1126. var adj : Psuperregisterworklist;
  1127. i,j,k : word;
  1128. n,a,c : Tsuperregister;
  1129. adj_colours,
  1130. colourednodes : Tsuperregisterset;
  1131. found : boolean;
  1132. begin
  1133. spillednodes.clear;
  1134. {Reset colours}
  1135. for n:=0 to maxreg-1 do
  1136. reginfo[n].colour:=n;
  1137. {Colour the cpu registers...}
  1138. supregset_reset(colourednodes,false);
  1139. for n:=0 to first_imaginary-1 do
  1140. supregset_include(colourednodes,n);
  1141. {Now colour the imaginary registers on the select-stack.}
  1142. for i:=selectstack.length downto 1 do
  1143. begin
  1144. n:=selectstack.buf^[i-1];
  1145. {Create a list of colours that we cannot assign to n.}
  1146. supregset_reset(adj_colours,false);
  1147. adj:=reginfo[n].adjlist;
  1148. if adj<>nil then
  1149. for j:=0 to adj^.length-1 do
  1150. begin
  1151. a:=get_alias(adj^.buf^[j]);
  1152. if supregset_in(colourednodes,a) then
  1153. supregset_include(adj_colours,reginfo[a].colour);
  1154. end;
  1155. supregset_include(adj_colours,RS_STACK_POINTER_REG);
  1156. {Assume a spill by default...}
  1157. found:=false;
  1158. {Search for a colour not in this list.}
  1159. for k:=0 to usable_registers_cnt-1 do
  1160. begin
  1161. c:=usable_registers[k];
  1162. if not(supregset_in(adj_colours,c)) then
  1163. begin
  1164. reginfo[n].colour:=c;
  1165. found:=true;
  1166. supregset_include(colourednodes,n);
  1167. include(used_in_proc,c);
  1168. break;
  1169. end;
  1170. end;
  1171. if not found then
  1172. spillednodes.add(n);
  1173. end;
  1174. {Finally colour the nodes that were coalesced.}
  1175. for i:=1 to coalescednodes.length do
  1176. begin
  1177. n:=coalescednodes.buf^[i-1];
  1178. k:=get_alias(n);
  1179. reginfo[n].colour:=reginfo[k].colour;
  1180. if reginfo[k].colour<maxcpuregister then
  1181. include(used_in_proc,reginfo[k].colour);
  1182. end;
  1183. {$ifdef ra_debug}
  1184. if aktfilepos.line=179 then
  1185. begin
  1186. writeln('colourlist');
  1187. for i:=0 to maxreg-1 do
  1188. writeln(i:4,' ',reginfo[i].colour:4)
  1189. end;
  1190. {$endif ra_debug}
  1191. end;
  1192. procedure trgobj.colour_registers;
  1193. begin
  1194. repeat
  1195. if simplifyworklist.length<>0 then
  1196. simplify
  1197. else if not(worklist_moves.empty) then
  1198. coalesce
  1199. else if freezeworklist.length<>0 then
  1200. freeze
  1201. else if spillworklist.length<>0 then
  1202. select_spill;
  1203. until (simplifyworklist.length=0) and
  1204. worklist_moves.empty and
  1205. (freezeworklist.length=0) and
  1206. (spillworklist.length=0);
  1207. assign_colours;
  1208. end;
  1209. procedure trgobj.epilogue_colouring;
  1210. var
  1211. i : Tsuperregister;
  1212. begin
  1213. worklist_moves.clear;
  1214. active_moves.destroy;
  1215. active_moves:=nil;
  1216. frozen_moves.destroy;
  1217. frozen_moves:=nil;
  1218. coalesced_moves.destroy;
  1219. coalesced_moves:=nil;
  1220. constrained_moves.destroy;
  1221. constrained_moves:=nil;
  1222. for i:=0 to maxreg-1 do
  1223. with reginfo[i] do
  1224. if movelist<>nil then
  1225. begin
  1226. dispose(movelist);
  1227. movelist:=nil;
  1228. end;
  1229. end;
  1230. procedure trgobj.clear_interferences(u:Tsuperregister);
  1231. {Remove node u from the interference graph and remove all collected
  1232. move instructions it is associated with.}
  1233. var i : word;
  1234. v : Tsuperregister;
  1235. adj,adj2 : Psuperregisterworklist;
  1236. begin
  1237. adj:=reginfo[u].adjlist;
  1238. if adj<>nil then
  1239. begin
  1240. for i:=1 to adj^.length do
  1241. begin
  1242. v:=adj^.buf^[i-1];
  1243. {Remove (u,v) and (v,u) from bitmap.}
  1244. ibitmap[u,v]:=false;
  1245. ibitmap[v,u]:=false;
  1246. {Remove (v,u) from adjacency list.}
  1247. adj2:=reginfo[v].adjlist;
  1248. if adj2<>nil then
  1249. begin
  1250. adj2^.delete(u);
  1251. if adj2^.length=0 then
  1252. begin
  1253. dispose(adj2,done);
  1254. reginfo[v].adjlist:=nil;
  1255. end;
  1256. end;
  1257. end;
  1258. {Remove ( u,* ) from adjacency list.}
  1259. dispose(adj,done);
  1260. reginfo[u].adjlist:=nil;
  1261. end;
  1262. end;
  1263. procedure trgobj.getregisterinline(list:Taasmoutput;
  1264. position:Tai;subreg:Tsubregister;var result:Tregister);
  1265. var p:Tsuperregister;
  1266. r:Tregister;
  1267. begin
  1268. p:=getnewreg(subreg);
  1269. live_registers.add(p);
  1270. r:=newreg(regtype,p,subreg);
  1271. if position=nil then
  1272. list.insert(Tai_regalloc.alloc(r))
  1273. else
  1274. list.insertafter(Tai_regalloc.alloc(r),position);
  1275. add_edges_used(p);
  1276. add_constraints(r);
  1277. result:=r;
  1278. end;
  1279. procedure trgobj.ungetregisterinline(list:Taasmoutput;
  1280. position:Tai;r:Tregister);
  1281. var supreg:Tsuperregister;
  1282. begin
  1283. supreg:=getsupreg(r);
  1284. live_registers.delete(supreg);
  1285. if position=nil then
  1286. list.insert(Tai_regalloc.dealloc(r))
  1287. else
  1288. list.insertafter(Tai_regalloc.dealloc(r),position);
  1289. end;
  1290. procedure trgobj.insert_regalloc_info(list:Taasmoutput;headertai:tai);
  1291. var
  1292. supreg : tsuperregister;
  1293. p : tai;
  1294. r : tregister;
  1295. begin
  1296. { Insert regallocs for all imaginary registers }
  1297. for supreg:=first_imaginary to maxreg-1 do
  1298. with reginfo[supreg] do
  1299. begin
  1300. r:=newreg(regtype,supreg,subreg);
  1301. if assigned(live_start) then
  1302. begin
  1303. {$ifdef EXTDEBUG}
  1304. if live_start=live_end then
  1305. Comment(V_Warning,'Register '+std_regname(r)+' is only used once');
  1306. {$endif EXTDEBUG}
  1307. list.insertbefore(Tai_regalloc.alloc(r),live_start);
  1308. { Insert live end deallocation before reg allocations
  1309. to reduce conflicts }
  1310. p:=live_end;
  1311. while assigned(p) and
  1312. assigned(p.previous) and
  1313. (tai(p.previous).typ=ait_regalloc) and
  1314. (tai_regalloc(p.previous).ratype=ra_alloc) and
  1315. (tai_regalloc(p.previous).reg<>r) do
  1316. p:=tai(p.previous);
  1317. list.insertbefore(Tai_regalloc.dealloc(r),p);
  1318. end
  1319. {$ifdef EXTDEBUG}
  1320. else
  1321. Comment(V_Warning,'Register '+std_regname(r)+' not used');
  1322. {$endif EXTDEBUG}
  1323. end;
  1324. end;
  1325. procedure trgobj.add_cpu_interferences(p : tai);
  1326. begin
  1327. end;
  1328. procedure trgobj.generate_interference_graph(list:Taasmoutput;headertai:tai);
  1329. var
  1330. p : tai;
  1331. i : integer;
  1332. supreg : tsuperregister;
  1333. begin
  1334. { All allocations are available. Now we can generate the
  1335. interference graph. Walk through all instructions, we can
  1336. start with the headertai, because before the header tai is
  1337. only symbols. }
  1338. live_registers.clear;
  1339. p:=headertai;
  1340. while assigned(p) do
  1341. begin
  1342. if p.typ=ait_regalloc then
  1343. with Tai_regalloc(p) do
  1344. begin
  1345. if (getregtype(reg)=regtype) then
  1346. begin
  1347. supreg:=getsupreg(reg);
  1348. case ratype of
  1349. ra_alloc :
  1350. begin
  1351. live_registers.add(supreg);
  1352. add_edges_used(supreg);
  1353. end;
  1354. ra_dealloc :
  1355. begin
  1356. live_registers.delete(supreg);
  1357. add_edges_used(supreg);
  1358. end;
  1359. end;
  1360. { constraints needs always to be updated }
  1361. add_constraints(reg);
  1362. end;
  1363. end;
  1364. add_cpu_interferences(p);
  1365. p:=Tai(p.next);
  1366. end;
  1367. {$ifdef EXTDEBUG}
  1368. if live_registers.length>0 then
  1369. begin
  1370. for i:=0 to live_registers.length-1 do
  1371. begin
  1372. { Only report for imaginary registers }
  1373. if live_registers.buf^[i]>=first_imaginary then
  1374. Comment(V_Warning,'Register '+std_regname(newreg(R_INTREGISTER,live_registers.buf^[i],defaultsub))+' not released');
  1375. end;
  1376. end;
  1377. {$endif}
  1378. end;
  1379. procedure Trgobj.translate_registers(list:taasmoutput);
  1380. var
  1381. hp,p,q:Tai;
  1382. i:shortint;
  1383. {$ifdef arm}
  1384. so:pshifterop;
  1385. {$endif arm}
  1386. begin
  1387. { Leave when no imaginary registers are used }
  1388. if maxreg<=first_imaginary then
  1389. exit;
  1390. p:=Tai(list.first);
  1391. while assigned(p) do
  1392. begin
  1393. case p.typ of
  1394. ait_regalloc:
  1395. with Tai_regalloc(p) do
  1396. begin
  1397. if (getregtype(reg)=regtype) then
  1398. setsupreg(reg,reginfo[getsupreg(reg)].colour);
  1399. {
  1400. Remove sequences of release and
  1401. allocation of the same register like:
  1402. # Register X released
  1403. # Register X allocated
  1404. }
  1405. if assigned(previous) and
  1406. (Tai(previous).typ=ait_regalloc) and
  1407. (Tai_regalloc(previous).reg=reg) and
  1408. { deallocation,allocation }
  1409. { note: do not remove allocation,deallocation, those }
  1410. { do have a real meaning }
  1411. (not(Tai_regalloc(previous).ratype=ra_alloc) and (ratype=ra_alloc)) then
  1412. begin
  1413. q:=Tai(next);
  1414. hp:=tai(previous);
  1415. list.remove(hp);
  1416. hp.free;
  1417. list.remove(p);
  1418. p.free;
  1419. p:=q;
  1420. continue;
  1421. end;
  1422. end;
  1423. ait_instruction:
  1424. with Taicpu(p) do
  1425. begin
  1426. for i:=0 to ops-1 do
  1427. with oper[i]^ do
  1428. case typ of
  1429. Top_reg:
  1430. if (getregtype(reg)=regtype) then
  1431. setsupreg(reg,reginfo[getsupreg(reg)].colour);
  1432. Top_ref:
  1433. begin
  1434. if regtype=R_INTREGISTER then
  1435. with ref^ do
  1436. begin
  1437. if base<>NR_NO then
  1438. setsupreg(base,reginfo[getsupreg(base)].colour);
  1439. if index<>NR_NO then
  1440. setsupreg(index,reginfo[getsupreg(index)].colour);
  1441. end;
  1442. end;
  1443. {$ifdef arm}
  1444. Top_shifterop:
  1445. begin
  1446. so:=shifterop;
  1447. if so^.rs<>NR_NO then
  1448. setsupreg(so^.rs,reginfo[getsupreg(so^.rs)].colour);
  1449. end;
  1450. {$endif arm}
  1451. end;
  1452. { Maybe the operation can be removed when
  1453. it is a move and both arguments are the same }
  1454. if is_same_reg_move(regtype) then
  1455. begin
  1456. q:=Tai(p.next);
  1457. list.remove(p);
  1458. p.free;
  1459. p:=q;
  1460. continue;
  1461. end;
  1462. end;
  1463. end;
  1464. p:=Tai(p.next);
  1465. end;
  1466. end;
  1467. function trgobj.get_insert_pos(p:Tai;huntfor1,huntfor2,huntfor3:Tsuperregister):Tai;
  1468. var
  1469. back : Tsuperregisterworklist;
  1470. supreg : tsuperregister;
  1471. begin
  1472. back.copyfrom(live_registers);
  1473. result:=p;
  1474. while (p<>nil) and (p.typ=ait_regalloc) do
  1475. begin
  1476. supreg:=getsupreg(Tai_regalloc(p).reg);
  1477. {Rewind the register allocation.}
  1478. if (Tai_regalloc(p).ratype=ra_alloc) then
  1479. live_registers.delete(supreg)
  1480. else
  1481. begin
  1482. live_registers.add(supreg);
  1483. if supreg=huntfor1 then
  1484. begin
  1485. get_insert_pos:=Tai(p.previous);
  1486. back.done;
  1487. back.copyfrom(live_registers);
  1488. end;
  1489. if supreg=huntfor2 then
  1490. begin
  1491. get_insert_pos:=Tai(p.previous);
  1492. back.done;
  1493. back.copyfrom(live_registers);
  1494. end;
  1495. if supreg=huntfor3 then
  1496. begin
  1497. get_insert_pos:=Tai(p.previous);
  1498. back.done;
  1499. back.copyfrom(live_registers);
  1500. end;
  1501. end;
  1502. p:=Tai(p.previous);
  1503. end;
  1504. live_registers.done;
  1505. live_registers:=back;
  1506. end;
  1507. procedure trgobj.forward_allocation(pfrom,pto:Tai);
  1508. var
  1509. p : tai;
  1510. begin
  1511. {Forward the register allocation again.}
  1512. p:=pfrom;
  1513. while (p<>pto) do
  1514. begin
  1515. if p.typ<>ait_regalloc then
  1516. internalerror(200305311);
  1517. case Tai_regalloc(p).ratype of
  1518. ra_alloc :
  1519. live_registers.add(getsupreg(Tai_regalloc(p).reg));
  1520. ra_dealloc :
  1521. live_registers.delete(getsupreg(Tai_regalloc(p).reg));
  1522. end;
  1523. p:=Tai(p.next);
  1524. end;
  1525. end;
  1526. function trgobj.spill_registers(list:Taasmoutput;headertai:tai):boolean;
  1527. { Returns true if any help registers have been used }
  1528. var
  1529. i : word;
  1530. t : tsuperregister;
  1531. p,q : Tai;
  1532. regs_to_spill_set:Tsuperregisterset;
  1533. spill_temps : ^Tspill_temp_list;
  1534. supreg : tsuperregister;
  1535. templist : taasmoutput;
  1536. begin
  1537. spill_registers:=false;
  1538. live_registers.clear;
  1539. for i:=first_imaginary to maxreg-1 do
  1540. exclude(reginfo[i].flags,ri_selected);
  1541. spill_temps:=allocmem(sizeof(treference)*maxreg);
  1542. supregset_reset(regs_to_spill_set,false);
  1543. { Allocate temps and insert in front of the list }
  1544. templist:=taasmoutput.create;
  1545. {Safe: this procedure is only called if there are spilled nodes.}
  1546. with spillednodes do
  1547. for i:=0 to length-1 do
  1548. begin
  1549. t:=buf^[i];
  1550. {Alternative representation.}
  1551. supregset_include(regs_to_spill_set,t);
  1552. {Clear all interferences of the spilled register.}
  1553. clear_interferences(t);
  1554. {Get a temp for the spilled register}
  1555. tg.gettemp(templist,tcgsize2size[reg_cgsize(newreg(regtype,t,R_SUBWHOLE))],tt_noreuse,spill_temps^[t]);
  1556. end;
  1557. list.insertlistafter(headertai,templist);
  1558. templist.free;
  1559. { Walk through all instructions, we can start with the headertai,
  1560. because before the header tai is only symbols }
  1561. p:=headertai;
  1562. while assigned(p) do
  1563. begin
  1564. case p.typ of
  1565. ait_regalloc:
  1566. with Tai_regalloc(p) do
  1567. begin
  1568. if (getregtype(reg)=regtype) then
  1569. begin
  1570. {A register allocation of a spilled register can be removed.}
  1571. supreg:=getsupreg(reg);
  1572. if supregset_in(regs_to_spill_set,supreg) then
  1573. begin
  1574. q:=Tai(p.next);
  1575. list.remove(p);
  1576. p.free;
  1577. p:=q;
  1578. continue;
  1579. end
  1580. else
  1581. begin
  1582. case ratype of
  1583. ra_alloc :
  1584. live_registers.add(supreg);
  1585. ra_dealloc :
  1586. live_registers.delete(supreg);
  1587. end;
  1588. end;
  1589. end;
  1590. end;
  1591. ait_instruction:
  1592. with Taicpu(p) do
  1593. begin
  1594. aktfilepos:=fileinfo;
  1595. if instr_spill_register(list,taicpu(p),regs_to_spill_set,spill_temps^) then
  1596. spill_registers:=true;
  1597. end;
  1598. end;
  1599. p:=Tai(p.next);
  1600. end;
  1601. aktfilepos:=current_procinfo.exitpos;
  1602. {Safe: this procedure is only called if there are spilled nodes.}
  1603. with spillednodes do
  1604. for i:=0 to length-1 do
  1605. tg.ungettemp(list,spill_temps^[buf^[i]]);
  1606. freemem(spill_temps);
  1607. end;
  1608. procedure Trgobj.do_spill_read(list:Taasmoutput;instr:taicpu;
  1609. pos:Tai;regidx:word;
  1610. const spilltemplist:Tspill_temp_list;
  1611. const regs:Tspillregsinfo);
  1612. var helpins:Tai;
  1613. begin
  1614. with regs[regidx] do
  1615. begin
  1616. helpins:=spilling_create_load(spilltemplist[orgreg],tempreg);
  1617. if pos=nil then
  1618. list.insertafter(helpins,list.first)
  1619. else
  1620. list.insertafter(helpins,pos.next);
  1621. ungetregisterinline(list,instr,tempreg);
  1622. forward_allocation(tai(helpins.next),instr);
  1623. end;
  1624. end;
  1625. procedure Trgobj.do_spill_written(list:Taasmoutput;instr:taicpu;
  1626. pos:Tai;regidx:word;
  1627. const spilltemplist:Tspill_temp_list;
  1628. const regs:Tspillregsinfo);
  1629. var helpins:Tai;
  1630. begin
  1631. with regs[regidx] do
  1632. begin
  1633. helpins:=spilling_create_store(tempreg,spilltemplist[orgreg]);
  1634. list.insertafter(helpins,instr);
  1635. ungetregisterinline(list,helpins,tempreg);
  1636. end;
  1637. end;
  1638. procedure Trgobj.do_spill_readwritten(list:Taasmoutput;instr:taicpu;
  1639. pos:Tai;regidx:word;
  1640. const spilltemplist:Tspill_temp_list;
  1641. const regs:Tspillregsinfo);
  1642. var helpins1,helpins2:Tai;
  1643. begin
  1644. with regs[regidx] do
  1645. begin
  1646. helpins1:=spilling_create_load(spilltemplist[orgreg],tempreg);
  1647. if pos=nil then
  1648. list.insertafter(helpins1,list.first)
  1649. else
  1650. list.insertafter(helpins1,pos.next);
  1651. helpins2:=spilling_create_store(tempreg,spilltemplist[orgreg]);
  1652. list.insertafter(helpins2,instr);
  1653. ungetregisterinline(list,helpins2,tempreg);
  1654. forward_allocation(tai(helpins1.next),instr);
  1655. end;
  1656. end;
  1657. function trgobj.get_spill_subreg(r : tregister) : tsubregister;
  1658. begin
  1659. result:=defaultsub;
  1660. end;
  1661. function trgobj.instr_spill_register(list:Taasmoutput;
  1662. instr:taicpu;
  1663. const r:Tsuperregisterset;
  1664. const spilltemplist:Tspill_temp_list): boolean;
  1665. var
  1666. counter, regindex: longint;
  1667. pos: tai;
  1668. regs: tspillregsinfo;
  1669. spilled: boolean;
  1670. procedure addreginfo(reg: tregister; operation: topertype);
  1671. var
  1672. i, tmpindex: longint;
  1673. supreg : tsuperregister;
  1674. begin
  1675. tmpindex := regindex;
  1676. supreg:=getsupreg(reg);
  1677. // did we already encounter this register?
  1678. for i := 0 to pred(regindex) do
  1679. if (regs[i].orgreg = supreg) then
  1680. begin
  1681. tmpindex := i;
  1682. break;
  1683. end;
  1684. if tmpindex > high(regs) then
  1685. internalerror(2003120301);
  1686. regs[tmpindex].orgreg := supreg;
  1687. regs[tmpindex].spillreg:=reg;
  1688. if supregset_in(r,supreg) then
  1689. begin
  1690. // add/update info on this register
  1691. regs[tmpindex].mustbespilled := true;
  1692. case operation of
  1693. operand_read:
  1694. regs[tmpindex].regread := true;
  1695. operand_write:
  1696. regs[tmpindex].regwritten := true;
  1697. operand_readwrite:
  1698. begin
  1699. regs[tmpindex].regread := true;
  1700. regs[tmpindex].regwritten := true;
  1701. end;
  1702. end;
  1703. spilled := true;
  1704. end;
  1705. inc(regindex,ord(regindex=tmpindex));
  1706. end;
  1707. procedure tryreplacereg(var reg: tregister);
  1708. var
  1709. i: longint;
  1710. supreg: tsuperregister;
  1711. begin
  1712. supreg := getsupreg(reg);
  1713. for i := 0 to pred(regindex) do
  1714. if (regs[i].mustbespilled) and
  1715. (regs[i].orgreg = supreg) then
  1716. begin
  1717. reg := regs[i].tempreg;
  1718. break;
  1719. end;
  1720. end;
  1721. begin
  1722. result := false;
  1723. fillchar(regs,sizeof(regs),0);
  1724. for counter := low(regs) to high(regs) do
  1725. regs[counter].orgreg := RS_INVALID;
  1726. spilled := false;
  1727. regindex := 0;
  1728. { check whether and if so which and how (read/written) this instructions contains
  1729. registers that must be spilled }
  1730. for counter := 0 to instr.ops-1 do
  1731. with instr.oper[counter]^ do
  1732. begin
  1733. case typ of
  1734. top_reg:
  1735. begin
  1736. if (getregtype(reg) = regtype) then
  1737. addreginfo(reg,instr.spilling_get_operation_type(counter));
  1738. end;
  1739. top_ref:
  1740. begin
  1741. if regtype in [R_INTREGISTER,R_ADDRESSREGISTER] then
  1742. with ref^ do
  1743. begin
  1744. if (base <> NR_NO) then
  1745. addreginfo(base,operand_read);
  1746. if (index <> NR_NO) then
  1747. addreginfo(index,operand_read);
  1748. end;
  1749. end;
  1750. {$ifdef ARM}
  1751. top_shifterop:
  1752. begin
  1753. if shifterop^.rs<>NR_NO then
  1754. addreginfo(shifterop^.rs,operand_read);
  1755. end;
  1756. {$endif ARM}
  1757. end;
  1758. end;
  1759. { if no spilling for this instruction we can leave }
  1760. if not spilled then
  1761. exit;
  1762. { generate the spilling code }
  1763. result := true;
  1764. for counter := 0 to pred(regindex) do
  1765. with regs[counter] do
  1766. begin
  1767. if mustbespilled then
  1768. begin
  1769. pos:=get_insert_pos(Tai(instr.previous),regs[0].orgreg,regs[1].orgreg,regs[2].orgreg);
  1770. getregisterinline(list,pos,get_spill_subreg(regs[counter].spillreg),tempreg);
  1771. if regread then
  1772. if regwritten then
  1773. do_spill_readwritten(list,instr,pos,counter,spilltemplist,regs)
  1774. else
  1775. do_spill_read(list,instr,pos,counter,spilltemplist,regs)
  1776. else
  1777. do_spill_written(list,instr,pos,counter,spilltemplist,regs)
  1778. end;
  1779. end;
  1780. { substitute registers }
  1781. for counter := 0 to instr.ops-1 do
  1782. with instr.oper[counter]^ do
  1783. begin
  1784. case typ of
  1785. top_reg:
  1786. begin
  1787. tryreplacereg(reg);
  1788. end;
  1789. top_ref:
  1790. begin
  1791. tryreplacereg(ref^.base);
  1792. tryreplacereg(ref^.index);
  1793. end;
  1794. {$ifdef ARM}
  1795. top_shifterop:
  1796. begin
  1797. tryreplacereg(shifterop^.rs);
  1798. end;
  1799. {$endif ARM}
  1800. end;
  1801. end;
  1802. end;
  1803. end.
  1804. {
  1805. $Log$
  1806. Revision 1.130 2004-06-22 18:24:18 florian
  1807. * fixed arm compilation
  1808. Revision 1.129 2004/06/20 08:55:30 florian
  1809. * logs truncated
  1810. Revision 1.128 2004/06/20 08:47:33 florian
  1811. * spilling of doubles on sparc fixed
  1812. Revision 1.127 2004/06/16 20:07:09 florian
  1813. * dwarf branch merged
  1814. Revision 1.126 2004/05/22 23:34:28 peter
  1815. tai_regalloc.allocation changed to ratype to notify rgobj of register size changes
  1816. Revision 1.125 2004/04/26 19:57:50 jonas
  1817. * do not remove "allocation,deallocation" pairs, as those are important
  1818. for the optimizer
  1819. Revision 1.124.2.3 2004/06/13 10:51:16 florian
  1820. * fixed several register allocator problems (sparc/arm)
  1821. }