1 {
2     Copyright (c) 2000-2002 by Florian Klaempfl
3 
4     This unit implements some basic nodes
5 
6     This program is free software; you can redistribute it and/or modify
7     it under the terms of the GNU General Public License as published by
8     the Free Software Foundation; either version 2 of the License, or
9     (at your option) any later version.
10 
11     This program is distributed in the hope that it will be useful,
12     but WITHOUT ANY WARRANTY; without even the implied warranty of
13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14     GNU General Public License for more details.
15 
16     You should have received a copy of the GNU General Public License
17     along with this program; if not, write to the Free Software
18     Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
19 
20  ****************************************************************************
21 }
22 unit ncgbas;
23 
24 {$i fpcdefs.inc}
25 
26 interface
27 
28     uses
29        globtype,
30        aasmtai,aasmdata,
31        cpubase,cgutils,
32        node,nbas;
33 
34     type
35        tcgnothingnode = class(tnothingnode)
36           procedure pass_generate_code;override;
37        end;
38 
39        tcgasmnode = class(tasmnode)
40          protected
41           procedure ResolveRef(const filepos: tfileposinfo; var op:toper); virtual;
42          public
43           procedure pass_generate_code;override;
44        end;
45 
46        tcgstatementnode = class(tstatementnode)
47           procedure pass_generate_code;override;
48        end;
49 
50        tcgblocknode = class(tblocknode)
51           procedure pass_generate_code;override;
52        end;
53 
54        tcgtempcreatenode = class(ttempcreatenode)
55           procedure pass_generate_code;override;
56        end;
57 
58        tcgtemprefnode = class(ttemprefnode)
59           procedure pass_generate_code;override;
60           { Changes the location of this temp to ref. Useful when assigning }
61           { another temp to this one. The current location will be freed.   }
62           { Can only be called in pass 2 (since earlier, the temp location  }
63           { isn't known yet)                                                }
64           procedure changelocation(const ref: treference);
65        end;
66 
67        tcgtempdeletenode = class(ttempdeletenode)
68           procedure pass_generate_code;override;
69        end;
70 
71   implementation
72 
73     uses
74       globals,
75       cutils,verbose,
76       aasmbase,aasmcpu,
77       symsym,symconst,defutil,
78       pass_2,ncgutil,
79       cgbase,cgobj,hlcgobj,
80       procinfo,
81       cpuinfo,
82       tgobj
83       ;
84 
85 {*****************************************************************************
86                                  TNOTHING
87 *****************************************************************************}
88 
89     procedure tcgnothingnode.pass_generate_code;
90       begin
91          location_reset(location,LOC_VOID,OS_NO);
92 
93          { avoid an abstract rte }
94       end;
95 
96 
97 {*****************************************************************************
98                                TSTATEMENTNODE
99 *****************************************************************************}
100 
101     procedure tcgstatementnode.pass_generate_code;
102       var
103          hp : tstatementnode;
104       begin
105          location_reset(location,LOC_VOID,OS_NO);
106 
107          hp:=self;
108          while assigned(hp) do
109           begin
110             if assigned(hp.left) then
111              begin
112                secondpass(hp.left);
113                { Compiler inserted blocks can return values }
114                location_copy(hp.location,hp.left.location);
115              end;
116             hp:=tstatementnode(hp.right);
117           end;
118       end;
119 
120 
121 {*****************************************************************************
122                                TASMNODE
123 *****************************************************************************}
124 
125 
126     procedure tcgasmnode.ResolveRef(const filepos: tfileposinfo; var op:toper);
127       var
128         sym : tabstractnormalvarsym;
129 {$ifdef x86}
130         segment : tregister;
131         scale : byte;
132 {$endif x86}
133         forceref,
134         getoffset : boolean;
135         indexreg : tregister;
136         sofs : longint;
137       begin
138         if (op.typ=top_local) then
139           begin
140             sofs:=op.localoper^.localsymofs;
141             indexreg:=op.localoper^.localindexreg;
142 {$ifdef x86}
143             segment:=op.localoper^.localsegment;
144             scale:=op.localoper^.localscale;
145 {$endif x86}
146             getoffset:=op.localoper^.localgetoffset;
147             forceref:=op.localoper^.localforceref;
148             sym:=tabstractnormalvarsym(pointer(op.localoper^.localsym));
149             dispose(op.localoper);
150             case sym.localloc.loc of
151               LOC_REFERENCE :
152                 begin
153                   if getoffset then
154                     begin
155                       if (indexreg=NR_NO)
156 {$ifdef x86}
157                          and (segment=NR_NO)
158 {$endif x86}
159                          then
160                         begin
161                           op.typ:=top_const;
162                           op.val:=sym.localloc.reference.offset+sofs;
163                         end
164                       else
165                         begin
166                           op.typ:=top_ref;
167                           new(op.ref);
168                           reference_reset_base(op.ref^,indexreg,sym.localloc.reference.offset+sofs,
169                             sym.localloc.reference.temppos,newalignment(sym.localloc.reference.alignment,sofs),[]);
170 {$ifdef x86}
171                           op.ref^.segment:=segment;
172 {$endif x86}
173                         end;
174                     end
175                   else
176                     begin
177                       op.typ:=top_ref;
178                       new(op.ref);
179                       reference_reset_base(op.ref^,sym.localloc.reference.base,sym.localloc.reference.offset+sofs,
180                         sym.localloc.reference.temppos,newalignment(sym.localloc.reference.alignment,sofs),[]);
181                       op.ref^.index:=indexreg;
182 {$ifdef x86}
183                       op.ref^.segment:=segment;
184                       op.ref^.scalefactor:=scale;
185 {$endif x86}
186                     end;
187                 end;
188               LOC_REGISTER :
189                 begin
190                   if getoffset then
191                     MessagePos(filepos,asmr_e_invalid_reference_syntax);
192                   { Subscribed access }
193                   if forceref or
194 {$ifdef avr}
195                      (sofs>=tcgsize2size[sym.localloc.size])
196 {$else avr}
197                      (sofs<>0)
198 {$endif avr}
199                      then
200                     begin
201                       op.typ:=top_ref;
202                       new(op.ref);
203                       { no idea about the actual alignment }
204                       reference_reset_base(op.ref^,sym.localloc.register,sofs,ctempposinvalid,1,[]);
205                       op.ref^.index:=indexreg;
206 {$ifdef x86}
207                       op.ref^.scalefactor:=scale;
208 {$endif x86}
209                     end
210                   else
211                     begin
212                       op.typ:=top_reg;
213                       op.reg:=sym.localloc.register;
214 
215 {$ifdef avr}
216                       case sofs of
217                         1: op.reg:=cg.GetNextReg(op.reg);
218                         2: op.reg:=cg.GetNextReg(cg.GetNextReg(op.reg));
219                         3: op.reg:=cg.GetNextReg(cg.GetNextReg(cg.GetNextReg(op.reg)));
220                       end;
221 {$endif avr}
222                     end;
223                 end;
224               LOC_FPUREGISTER,
225               LOC_MMXREGISTER,
226               LOC_MMREGISTER :
227                 begin
228                   op.typ:=top_reg;
229                   op.reg:=NR_NO;
230                   if getoffset then
231                     MessagePos(filepos,asmr_e_invalid_reference_syntax);
232                   { Using an MM/FPU register in a reference is not possible }
233                   if forceref or (sofs<>0) then
234                     MessagePos1(filepos,asmr_e_invalid_ref_register,std_regname(sym.localloc.register))
235                   else
236                     op.reg:=sym.localloc.register;
237                 end;
238               LOC_INVALID :
239                 begin
240                   { in "assembler; nostackframe;" routines, the
241                     funcret loc is set to LOC_INVALID in case the
242                     result is returned via a complex location
243                     (more than one register, ...) }
244                   if (vo_is_funcret in tabstractvarsym(sym).varoptions) then
245                     MessagePos(filepos,asmr_e_complex_function_result_location)
246                   else
247                     internalerror(2012082101);
248                   { recover }
249                   op.typ:=top_reg;
250                   op.reg:=NR_FUNCTION_RETURN_REG;
251                 end;
252               else
253                 internalerror(201001031);
254             end;
255           end;
256       end;
257 
258 
259     procedure tcgasmnode.pass_generate_code;
260 
261       procedure ReLabel(var p:tasmsymbol);
262         begin
263           { Only relabel local tasmlabels }
264           if (p.bind = AB_LOCAL) and
265              (p is tasmlabel) then
266            begin
267              if not assigned(p.altsymbol) then
268                current_asmdata.GenerateAltSymbol(p);
269              p:=p.altsymbol;
270              p.increfs;
271            end;
272         end;
273 
274       var
275         hp,hp2 : tai;
276         i : longint;
277       begin
278          location_reset(location,LOC_VOID,OS_NO);
279 
280          if (nf_get_asm_position in flags) then
281            begin
282              { Add a marker, to be sure the list is not empty }
283              current_asmdata.CurrAsmList.concat(tai_marker.create(mark_Position));
284              currenttai:=tai(current_asmdata.CurrAsmList.last);
285              exit;
286            end;
287          { Switch to the CPU instruction set, specified by the $ASMCPU directive }
288          current_asmdata.CurrAsmList.Concat(tai_directive.create(asd_cpu,cputypestr[current_settings.asmcputype]));
289 
290          { Allocate registers used in the assembler block }
291          { has_registerlist=true means that registers are specified and already allocated }
292          if (not has_registerlist) then
293            cg.allocallcpuregisters(current_asmdata.CurrAsmList);
294 
295          if (po_inline in current_procinfo.procdef.procoptions) then
296            begin
297              hp:=tai(p_asm.first);
298              while assigned(hp) do
299               begin
300                 hp2:=tai(hp.getcopy);
301                 case hp2.typ of
302                   ait_label :
303                      ReLabel(tasmsymbol(tai_label(hp2).labsym));
304                   ait_const :
305                      begin
306                        if assigned(tai_const(hp2).sym) then
307                          ReLabel(tai_const(hp2).sym);
308                        if assigned(tai_const(hp2).endsym) then
309                          ReLabel(tai_const(hp2).endsym);
310                      end;
311                   ait_instruction :
312                      begin
313                        { remove cached insentry, because the new code can
314                          require another less optimized instruction }
315 {$ifdef i386}
316 {$ifndef NOAG386BIN}
317                        taicpu(hp2).ResetPass1;
318 {$endif}
319 {$endif}
320                        { fixup the references }
321                        for i:=1 to taicpu(hp2).ops do
322                         begin
323                           ResolveRef(taicpu(hp2).fileinfo,taicpu(hp2).oper[i-1]^);
324                           with taicpu(hp2).oper[i-1]^ do
325                            begin
326                              case typ of
327                                top_ref :
328                                  begin
329                                    if assigned(ref^.symbol) then
330                                      ReLabel(ref^.symbol);
331                                    if assigned(ref^.relsymbol) then
332                                      ReLabel(ref^.relsymbol);
333 {$ifdef x86}
334                                    if (ref^.segment<>NR_NO) and (ref^.segment<>get_default_segment_of_ref(ref^)) then
335                                      taicpu(hp2).segprefix:=ref^.segment;
336 {$endif x86}
337                                  end;
338                              end;
339                            end;
340                         end;
341 {$ifdef x86}
342                         { can only be checked now that all local operands }
343                         { have been resolved                              }
344                         taicpu(hp2).CheckIfValid;
345 {$endif x86}
346                      end;
347                 end;
348                 current_asmdata.CurrAsmList.concat(hp2);
349                 hp:=tai(hp.next);
350               end;
351              { restore used symbols }
352              current_asmdata.ResetAltSymbols;
353            end
354          else
355            begin
356              hp:=tai(p_asm.first);
357              while assigned(hp) do
358               begin
359                 case hp.typ of
360                   ait_instruction :
361                      begin
362                        { remove cached insentry, because the new code can
363                          require another less optimized instruction }
364 {$ifdef i386}
365 {$ifndef NOAG386BIN}
366                        taicpu(hp).ResetPass1;
367 {$endif}
368 {$endif}
369                        { fixup the references }
370                        for i:=1 to taicpu(hp).ops do
371                          begin
372                            ResolveRef(taicpu(hp).fileinfo,taicpu(hp).oper[i-1]^);
373 {$ifdef x86}
374                            with taicpu(hp).oper[i-1]^ do
375                              begin
376                                case typ of
377                                  top_ref :
378                                    if (ref^.segment<>NR_NO) and (ref^.segment<>get_default_segment_of_ref(ref^)) then
379                                      taicpu(hp).segprefix:=ref^.segment;
380                                end;
381                              end;
382 {$endif x86}
383                          end;
384 {$ifdef x86}
385                       { can only be checked now that all local operands }
386                       { have been resolved                              }
387                       taicpu(hp).CheckIfValid;
388 {$endif x86}
389                      end;
390                 end;
391                 hp:=tai(hp.next);
392               end;
393              { insert the list }
394              current_asmdata.CurrAsmList.concatlist(p_asm);
395            end;
396 
397          { Update section count }
398          current_asmdata.currasmlist.section_count:=current_asmdata.currasmlist.section_count+p_asm.section_count;
399 
400          { Release register used in the assembler block }
401          if (not has_registerlist) then
402            cg.deallocallcpuregisters(current_asmdata.CurrAsmList);
403 
404          { Switch back to the CPU instruction set of the target CPU }
405          current_asmdata.CurrAsmList.Concat(tai_directive.create(asd_cpu,cputypestr[current_settings.cputype]));
406        end;
407 
408 
409 {*****************************************************************************
410                              TBLOCKNODE
411 *****************************************************************************}
412 
413     procedure tcgblocknode.pass_generate_code;
414       var
415         hp : tstatementnode;
416         oldexitlabel : tasmlabel;
417         oldflowcontrol : tflowcontrol;
418       begin
419         location_reset(location,LOC_VOID,OS_NO);
420         oldflowcontrol:=[];
421         oldexitlabel:=nil;
422 
423         { replace exitlabel? }
424         if nf_block_with_exit in flags then
425           begin
426             oldexitlabel:=current_procinfo.CurrExitLabel;
427             current_asmdata.getjumplabel(current_procinfo.CurrExitLabel);
428             oldflowcontrol:=flowcontrol;
429             { the nested block will not span an exit statement of the parent }
430             exclude(flowcontrol,fc_exit);
431             include(flowcontrol,fc_no_direct_exit);
432           end;
433 
434         { do second pass on left node }
435         if assigned(left) then
436          begin
437            hp:=tstatementnode(left);
438            while assigned(hp) do
439             begin
440               if assigned(hp.left) then
441                begin
442                  secondpass(hp.left);
443                  location_copy(hp.location,hp.left.location);
444                end;
445               location_copy(location,hp.location);
446               hp:=tstatementnode(hp.right);
447             end;
448          end;
449 
450         { write exitlabel }
451         if nf_block_with_exit in flags then
452           begin
453             cg.a_label(current_asmdata.CurrAsmList,current_procinfo.CurrExitLabel);
454             current_procinfo.CurrExitLabel:=oldexitlabel;
455             { the exit statements inside this block are not exit statements }
456             { out of the parent                                             }
457             flowcontrol:=oldflowcontrol+(flowcontrol - [fc_exit,fc_no_direct_exit]);
458           end;
459       end;
460 
461 
462 {*****************************************************************************
463                           TTEMPCREATENODE
464 *****************************************************************************}
465 
466     procedure tcgtempcreatenode.pass_generate_code;
467       begin
468         location_reset(location,LOC_VOID,OS_NO);
469 
470         { if we're secondpassing the same tcgtempcreatenode twice, we have a bug }
471         if (ti_valid in tempflags) then
472           internalerror(200108222);
473 
474         { in case of ti_reference, the location will be initialised using the
475           location of the tempinitnode once the first temprefnode is processed }
476         if not(ti_reference in tempflags) then
477           begin
478             { get a (persistent) temp }
479             if is_managed_type(tempinfo^.typedef) and
480               not(ti_const in tempflags) then
481               begin
482                 location_reset_ref(tempinfo^.location,LOC_REFERENCE,def_cgsize(tempinfo^.typedef),0,[]);
483                 tg.gethltempmanaged(current_asmdata.CurrAsmList,tempinfo^.typedef,tempinfo^.temptype,tempinfo^.location.reference);
484                 if not(ti_nofini in tempflags) then
485                   hlcg.g_finalize(current_asmdata.CurrAsmList,tempinfo^.typedef,tempinfo^.location.reference);
486               end
487             else if (ti_may_be_in_reg in tempflags) then
488               begin
489                 location_allocate_register(current_asmdata.CurrAsmList,tempinfo^.location,tempinfo^.typedef,tempinfo^.temptype = tt_persistent);
490               end
491             else
492               begin
493                 location_reset_ref(tempinfo^.location,LOC_REFERENCE,def_cgsize(tempinfo^.typedef),0,[]);
494                 tg.gethltemp(current_asmdata.CurrAsmList,tempinfo^.typedef,size,tempinfo^.temptype,tempinfo^.location.reference);
495               end;
496           end;
497         includetempflag(ti_valid);
498         if assigned(tempinfo^.tempinitcode) then
499           includetempflag(ti_executeinitialisation);
500       end;
501 
502 
503 {*****************************************************************************
504                              TTEMPREFNODE
505 *****************************************************************************}
506 
507     procedure tcgtemprefnode.pass_generate_code;
508       begin
509         if ti_executeinitialisation in tempflags then
510           begin
511             { avoid recursion }
512             excludetempflag(ti_executeinitialisation);
513             secondpass(tempinfo^.tempinitcode);
514             if (ti_reference in tempflags) then
515               begin
516                 case tempinfo^.tempinitcode.location.loc of
517                   LOC_CREGISTER,
518                   LOC_CFPUREGISTER,
519                   LOC_CMMREGISTER,
520                   LOC_CSUBSETREG:
521                     begin
522                       { although it's ok if we need this value multiple times
523                         for reading, it's not in case of writing (because the
524                         register could change due to SSA -> storing to the saved
525                         register afterwards would be wrong). }
526                       if not(ti_readonly in tempflags) then
527                         internalerror(2011031407);
528                     end;
529                   { in case reference contains CREGISTERS, that doesn't matter:
530                     we want to write to the location indicated by the current
531                     value of those registers, and we can save those values }
532                 end;
533                 hlcg.g_reference_loc(current_asmdata.CurrAsmList,tempinfo^.typedef,tempinfo^.tempinitcode.location,tempinfo^.location);
534               end;
535           end;
536         { check if the temp is valid }
537         if not(ti_valid in tempflags) then
538           internalerror(200108231);
539         location:=tempinfo^.location;
540         case tempinfo^.location.loc of
541           LOC_REFERENCE:
542             begin
543               { ti_valid should be excluded if it's a normal temp }
544             end;
545           LOC_REGISTER,
546           LOC_FPUREGISTER,
547           LOC_MMREGISTER :
548             excludetempflag(ti_valid);
549         end;
550       end;
551 
552 
553     procedure tcgtemprefnode.changelocation(const ref: treference);
554       begin
555         { check if the temp is valid }
556         if not(ti_valid in tempflags) then
557           internalerror(200306081);
558         if (tempinfo^.location.loc<>LOC_REFERENCE) then
559           internalerror(2004020203);
560         if (tempinfo^.temptype = tt_persistent) then
561           tg.ChangeTempType(current_asmdata.CurrAsmList,tempinfo^.location.reference,tt_normal);
562         tg.ungettemp(current_asmdata.CurrAsmList,tempinfo^.location.reference);
563         tempinfo^.location.reference := ref;
564         tg.ChangeTempType(current_asmdata.CurrAsmList,tempinfo^.location.reference,tempinfo^.temptype);
565         { adapt location }
566         location.reference := ref;
567       end;
568 
569 
570 {*****************************************************************************
571                            TTEMPDELETENODE
572 *****************************************************************************}
573 
574     procedure tcgtempdeletenode.pass_generate_code;
575       begin
576         if ti_reference in tempflags then
577           begin
578             { release_to_normal means that the temp will be freed the next
579               time it's used. However, reference temps reference some other
580               location that is not managed by this temp and hence cannot be
581               freed }
582             if release_to_normal then
583               internalerror(2011052205);
584             { so we only mark this temp location as "no longer valid" when
585               it's deleted (ttempdeletenodes are also used during getcopy, so
586               we really do need one) }
587             excludetempflag(ti_valid);
588             exit;
589           end;
590 
591         location_reset(location,LOC_VOID,OS_NO);
592 
593         if ti_cleanup_only in tempflags then
594           exit;
595 
596         { see comments at ti_const declaration: if we initialised this temp with
597           the value of another temp, that other temp was not freed because the
598           ti_const flag was set }
599         if (ti_const in tempflags) and
600            assigned(tempinfo^.tempinitcode) then
601           begin
602             if tempinfo^.tempinitcode.nodetype<>assignn then
603               internalerror(2016081201);
604             if tbinarynode(tempinfo^.tempinitcode).right.location.loc in [LOC_REFERENCE,LOC_CREFERENCE] then
605               tg.ungetiftemp(current_asmdata.CurrAsmList,tbinarynode(tempinfo^.tempinitcode).right.location.reference);
606           end;
607 
608 
609         case tempinfo^.location.loc of
610           LOC_REFERENCE:
611             begin
612               if release_to_normal then
613                 tg.ChangeTempType(current_asmdata.CurrAsmList,tempinfo^.location.reference,tt_normal)
614               else
615                 begin
616                   tg.UnGetTemp(current_asmdata.CurrAsmList,tempinfo^.location.reference);
617                   excludetempflag(ti_valid);
618                 end;
619             end;
620           LOC_CREGISTER,
621           LOC_REGISTER:
622             begin
623               if (not(cs_opt_regvar in current_settings.optimizerswitches) or
624                  (pi_has_label in current_procinfo.flags)) and not(ti_no_final_regsync in tempflags) then
625                 begin
626                   { make sure the register allocator doesn't reuse the }
627                   { register e.g. in the middle of a loop              }
628 {$if defined(cpu32bitalu)}
629                   if tempinfo^.location.size in [OS_64,OS_S64] then
630                     begin
631                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register64.reghi);
632                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register64.reglo);
633                     end
634                   else
635 {$elseif defined(cpu16bitalu)}
636                   if tempinfo^.location.size in [OS_64,OS_S64] then
637                     begin
638                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register64.reghi);
639                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(tempinfo^.location.register64.reghi));
640                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register64.reglo);
641                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(tempinfo^.location.register64.reglo));
642                     end
643                   else
644                   if tempinfo^.location.size in [OS_32,OS_S32] then
645                     begin
646                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register);
647                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(tempinfo^.location.register));
648                     end
649                   else
650 {$elseif defined(cpu8bitalu)}
651                   if tempinfo^.location.size in [OS_64,OS_S64] then
652                     begin
653                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register64.reghi);
654                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(tempinfo^.location.register64.reghi));
655                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(cg.GetNextReg(tempinfo^.location.register64.reghi)));
656                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(cg.GetNextReg(cg.GetNextReg(tempinfo^.location.register64.reghi))));
657                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register64.reglo);
658                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(tempinfo^.location.register64.reglo));
659                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(cg.GetNextReg(tempinfo^.location.register64.reglo)));
660                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(cg.GetNextReg(cg.GetNextReg(tempinfo^.location.register64.reglo))));
661                     end
662                   else
663                   if tempinfo^.location.size in [OS_32,OS_S32] then
664                     begin
665                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register);
666                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(tempinfo^.location.register));
667                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(cg.GetNextReg(tempinfo^.location.register)));
668                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(cg.GetNextReg(cg.GetNextReg(tempinfo^.location.register))));
669                     end
670                   else
671                   if tempinfo^.location.size in [OS_16,OS_S16] then
672                     begin
673                       cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register);
674                       cg.a_reg_sync(current_asmdata.CurrAsmList,cg.GetNextReg(tempinfo^.location.register));
675                     end
676                   else
677 {$endif}
678                     cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register);
679                 end;
680               if release_to_normal then
681                 tempinfo^.location.loc := LOC_REGISTER
682               else
683                 excludetempflag(ti_valid);
684             end;
685           LOC_CFPUREGISTER,
686           LOC_FPUREGISTER:
687             begin
688               if (not(cs_opt_regvar in current_settings.optimizerswitches) or
689                  (pi_has_label in current_procinfo.flags)) and not(ti_no_final_regsync in tempflags) then
690                 begin
691                   { make sure the register allocator doesn't reuse the }
692                   { register e.g. in the middle of a loop              }
693                   cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register);
694                 end;
695               if release_to_normal then
696                 tempinfo^.location.loc := LOC_FPUREGISTER
697               else
698                 excludetempflag(ti_valid);
699             end;
700           LOC_CMMREGISTER,
701           LOC_MMREGISTER:
702             begin
703               if (not(cs_opt_regvar in current_settings.optimizerswitches) or
704                  (pi_has_label in current_procinfo.flags)) and not(ti_no_final_regsync in tempflags) then
705                 begin
706                   { make sure the register allocator doesn't reuse the }
707                   { register e.g. in the middle of a loop              }
708                   cg.a_reg_sync(current_asmdata.CurrAsmList,tempinfo^.location.register);
709                 end;
710               if release_to_normal then
711                 tempinfo^.location.loc := LOC_MMREGISTER
712               else
713                 excludetempflag(ti_valid);
714             end;
715           else
716             internalerror(200507161);
717         end;
718       end;
719 
720 
721 begin
722    cnothingnode:=tcgnothingnode;
723    casmnode:=tcgasmnode;
724    cstatementnode:=tcgstatementnode;
725    cblocknode:=tcgblocknode;
726    ctempcreatenode:=tcgtempcreatenode;
727    ctemprefnode:=tcgtemprefnode;
728    ctempdeletenode:=tcgtempdeletenode;
729 end.
730