1 {
2     Copyright (c) 1998-2006 by Florian Klaempfl
3 
4     This unit implements an abstract asmoutput class for all processor types
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 { @abstract(This unit implements an abstract asm output class for all processor types)
23   This unit implements an abstract assembler output class for all processors, these
24   are then overridden for each assembler writer to actually write the data in these
25   classes to an assembler file.
26 }
27 
28 unit aasmtai;
29 
30 {$i fpcdefs.inc}
31 
32 interface
33 
34     uses
35        cutils,cclasses,
36        globtype,systems,
37        cpuinfo,cpubase,
38 {$ifdef llvm}
39        { overrides max_operands }
40        llvmbase,
41 {$endif llvm}
42        cgbase,cgutils,
43        symtype,
44        aasmbase,aasmdata,ogbase
45 {$ifdef jvm}
46        ,widestr
47 {$endif jvm}
48        ;
49 
50     type
51        { keep the number of elements in this enumeration less or equal than 32 as long
52          as FPC knows only 4 byte and 32 byte sets (FK) }
53        taitype = (
54           ait_none,
55           ait_align,
56           ait_section,
57           ait_comment,
58           ait_string,
59           ait_instruction,
60           ait_datablock,
61           ait_symbol,
62           { needed to calc the size of a symbol }
63           ait_symbol_end,
64           ait_directive,
65           ait_label,
66           ait_const,
67           ait_realconst,
68           ait_typedconst,
69           ait_stab,
70           ait_force_line,
71           ait_function_name,
72           ait_symbolpair,
73           { used to split into tiny assembler files }
74           ait_cutobject,
75           ait_regalloc,
76           ait_tempalloc,
77           { used to mark assembler blocks and inlined functions }
78           ait_marker,
79           { used to describe a new location of a variable }
80           ait_varloc,
81 {$ifdef JVM}
82           { JVM only }
83           ait_jvar,    { debug information for a local variable }
84           ait_jcatch,  { exception catch clause }
85 {$endif JVM}
86 {$ifdef llvm}
87           ait_llvmins, { llvm instruction }
88           ait_llvmalias, { alias for a symbol }
89           ait_llvmdecl, { llvm symbol declaration (global/external variable, external procdef) }
90 {$endif}
91           { SEH directives used in ARM,MIPS and x86_64 COFF targets }
92           ait_seh_directive,
93           { Dwarf CFI directive }
94           ait_cfi
95           );
96 
97         taiconst_type = (
98           aitconst_128bit,
99           aitconst_64bit,
100           aitconst_32bit,
101           aitconst_16bit,
102           aitconst_8bit,
103           aitconst_sleb128bit,
104           aitconst_uleb128bit,
105           { win32 only }
106           aitconst_rva_symbol,
107           aitconst_secrel32_symbol,
108           { darwin only }
109           { From gcc/config/darwin.c (darwin_asm_output_dwarf_delta):
110             ***
111             Output a difference of two labels that will be an assembly time
112             constant if the two labels are local.  (.long lab1-lab2 will be
113             very different if lab1 is at the boundary between two sections; it
114             will be relocated according to the second section, not the first,
115             so one ends up with a difference between labels in different
116             sections, which is bad in the dwarf2 eh context for instance.)
117             ***
118             We cannot use this everywhere, because older versions of the
119             darwin assembler don't support the construct used for these
120             relsyms (nor do they support dwarf, for that matter)
121           }
122           aitconst_darwin_dwarf_delta64,
123           aitconst_darwin_dwarf_delta32,
124           { ARM Thumb-2 only }
125           aitconst_half16bit, { used for table jumps. The actual value is the 16bit value shifted left once }
126           { AVR }
127           aitconst_gs, { Upper 16-bit of 17-bit constant }
128           { for use by dwarf debugger information }
129           aitconst_16bit_unaligned,
130           aitconst_32bit_unaligned,
131           aitconst_64bit_unaligned,
132           { i8086 far pointer; emits: 'DW symbol, SEG symbol' }
133           aitconst_farptr,
134           { i8086 segment of symbol; emits: 'DW SEG symbol' }
135           aitconst_seg,
136           { i8086 data segment group; emits: 'DW dgroup'
137             generated by the this inline asm:
138               DW SEG @DATA
139             in all memory models, except huge }
140           aitconst_dgroup,
141           { i8086 far data segment of the current pascal module (unit or program);
142             emits: 'DW CURRENTMODULENAME_DATA'
143             generated by the this inline asm:
144               DW SEG @DATA
145             in the huge memory model }
146           aitconst_fardataseg,
147           { offset of symbol's GOT slot in GOT }
148           aitconst_got,
149           { offset of symbol itself from GOT }
150           aitconst_gotoff_symbol
151         );
152 
153         tairealconsttype = (
154           aitrealconst_s32bit,
155           aitrealconst_s64bit,
156           aitrealconst_s80bit,
157           aitrealconst_s128bit,
158           aitrealconst_s64comp
159         );
160 
161     const
162 {$if defined(cpu64bitaddr)}
163        aitconst_ptr = aitconst_64bit;
164        aitconst_ptr_unaligned = aitconst_64bit_unaligned;
165        aitconst_sizeint = aitconst_64bit;
166        aitconst_sizeint_unaligned = aitconst_64bit_unaligned;
167 {$elseif defined(cpu32bitaddr)}
168        aitconst_ptr = aitconst_32bit;
169        aitconst_ptr_unaligned = aitconst_32bit_unaligned;
170        aitconst_sizeint = aitconst_32bit;
171        aitconst_sizeint_unaligned = aitconst_32bit_unaligned;
172 {$elseif defined(cpu16bitaddr)}
173        aitconst_ptr = aitconst_16bit;
174        aitconst_ptr_unaligned = aitconst_16bit_unaligned;
175        aitconst_sizeint = aitconst_16bit;
176        aitconst_sizeint_unaligned = aitconst_16bit_unaligned;
177 {$endif}
178 
179 {$if defined(cpu64bitalu)}
180        aitconst_aint = aitconst_64bit;
181 {$elseif defined(cpu32bitalu)}
182        aitconst_aint = aitconst_32bit;
183 {$elseif defined(cpu16bitalu)}
184        aitconst_aint = aitconst_16bit;
185 {$elseif defined(cpu8bitalu)}
186        aitconst_aint = aitconst_8bit;
187 {$endif}
188 
189        taitypestr : array[taitype] of string[24] = (
190           '<none>',
191           'align',
192           'section',
193           'comment',
194           'string',
195           'instruction',
196           'datablock',
197           'symbol',
198           'symbol_end',
199           'symbol_directive',
200           'label',
201           'const',
202           'realconst',
203           'typedconst',
204           'stab',
205           'force_line',
206           'function_name',
207           'symbolpair',
208           'cut',
209           'regalloc',
210           'tempalloc',
211           'marker',
212           'varloc',
213 {$ifdef JVM}
214           'jvar',
215           'jcatch',
216 {$endif JVM}
217 {$ifdef llvm}
218           'llvmins',
219           'llvmalias',
220           'llvmdecl',
221 {$endif}
222           'cfi',
223           'seh_directive'
224           );
225 
226     type
227       { Types of operand }
228       toptype=(top_none,top_reg,top_ref,top_const,top_bool,top_local
229 {$ifdef arm}
230        { ARM only }
231        ,top_regset
232        ,top_modeflags
233        ,top_specialreg
234 {$endif arm}
235 {$if defined(arm) or defined(aarch64)}
236        ,top_conditioncode
237        ,top_shifterop
238        ,top_realconst
239 {$endif defined(arm) or defined(aarch64)}
240 {$ifdef m68k}
241        { m68k only }
242        ,top_regset
243        ,top_regpair
244        ,top_realconst
245 {$endif m68k}
246 {$ifdef jvm}
247        { jvm only}
248        ,top_single
249        ,top_double
250        ,top_string
251        ,top_wstring
252 {$endif jvm}
253 {$ifdef llvm}
254        { llvm only }
255        ,top_single
256        ,top_double
257        ,top_undef
258 {$ifdef cpuextended}
259        ,top_extended80
260 {$endif cpuextended}
261        ,top_tai
262        ,top_def
263        ,top_fpcond
264        ,top_cond
265        ,top_para
266        ,top_asmlist
267 {$endif llvm}
268        );
269 
270       { kinds of operations that an instruction can perform on an operand }
271       topertype = (operand_read,operand_write,operand_readwrite);
272 
273       tlocaloper = record
274         localsym : pointer;
275         localsymderef : tderef;
276         localsymofs : longint;
277 {$ifdef x86}
278         localsegment,
279 {$endif x86}
280         localindexreg : tregister;
281         localscale : byte;
282         localgetoffset,
283         localforceref : boolean
284       end;
285       plocaloper = ^tlocaloper;
286 
287     const
288       { ait_* types which don't result in executable code or which don't influence
289         the way the program runs/behaves, but which may be encountered by the
290         optimizer (= if it's sometimes added to the exprasm list). Update if you add
291         a new ait type!                                                              }
292       SkipInstr = [ait_comment, ait_symbol,ait_section
293                    ,ait_stab, ait_function_name, ait_force_line
294                    ,ait_regalloc, ait_tempalloc, ait_symbol_end
295                    ,ait_directive
296                    ,ait_varloc,
297 {$ifdef JVM}
298                    ait_jvar,
299 {$endif JVM}
300                    ait_seh_directive];
301 
302       { ait_* types which do not have line information (and hence which are of type
303         tai, otherwise, they are of type tailineinfo }
304       SkipLineInfo =[ait_label,
305                      ait_regalloc,ait_tempalloc,
306                      ait_stab,ait_function_name,
307                      ait_cutobject,ait_marker,ait_varloc,ait_align,ait_section,ait_comment,
308                      ait_const,ait_directive,
309                      ait_symbolpair,
310                      ait_realconst,
311                      ait_symbol,
312 {$ifdef JVM}
313                      ait_jvar, ait_jcatch,
314 {$endif JVM}
315 {$ifdef llvm}
316                      ait_llvmdecl,
317 {$endif llvm}
318                      ait_seh_directive,
319                      ait_cfi
320                     ];
321 
322 
323     type
324       { cut type, required for alphanumeric ordering of the assembler filenames }
325       TCutPlace=(cut_normal,cut_begin,cut_end);
326 
327       TAsmMarker = (
328         mark_NoPropInfoStart,mark_NoPropInfoEnd,
329         mark_AsmBlockStart,mark_AsmBlockEnd,
330         mark_NoLineInfoStart,mark_NoLineInfoEnd,mark_BlockStart,
331         mark_Position
332       );
333 
334       TRegAllocType = (ra_alloc,ra_dealloc,ra_sync,ra_resize,ra_markused);
335 
336       TStabType = (stab_stabs,stab_stabn,stab_stabd,
337                    { AIX/XCOFF stab types }
338                    stab_stabx,
339                    { begin/end include file }
340                    stabx_bi,stabx_ei,
341                    { begin/end function }
342                    stabx_bf, stabx_ef,
343                    { begin/end static data block }
344                    stabx_bs, stabx_es,
345                    { line spec, function start/end label }
346                    stabx_line, stabx_function);
347 
TAsmDirectivenull348       TAsmDirective=(
349         asd_indirect_symbol,
350         asd_extern,asd_nasm_import, asd_toc_entry,
351         asd_reference,asd_no_dead_strip,asd_weak_reference,asd_lazy_reference,
352         asd_weak_definition,
353         { for Jasmin }
354         asd_jclass,asd_jinterface,asd_jsuper,asd_jfield,asd_jlimit,asd_jline,
355         { .ent/.end for MIPS }
356         asd_ent,asd_ent_end,
357         { supported by recent clang-based assemblers for data-in-code  }
358         asd_data_region, asd_end_data_region,
359         { ARM }
360         asd_thumb_func,asd_code,
361         { restricts the assembler only to those instructions, which are
362           available on the specified CPU; this represents directives such as
363           NASM's 'CPU 686' or MASM/TASM's '.686p'. Might not be supported by
364           all assemblers. }
365         asd_cpu,
366         { for the OMF object format }
367         asd_omf_linnum_line
368       );
369 
370       TAsmSehDirective=(
371           ash_proc,ash_endproc,
372           ash_endprologue,ash_handler,ash_handlerdata,
373           ash_eh,ash_32,ash_no32,
374           ash_setframe,ash_stackalloc,ash_pushreg,
375           ash_savereg,ash_savexmm,ash_pushframe,
376           ash_pushnv,ash_savenv
377         );
378 
379       TSymbolPairKind = (spk_set, spk_thumb_set, spk_localentry);
380 
381 
382     const
383       regallocstr : array[tregalloctype] of string[10]=('allocated','released','sync','resized','used');
384       tempallocstr : array[boolean] of string[10]=('released','allocated');
385       stabtypestr : array[TStabType] of string[8]=(
386         'stabs','stabn','stabd',
387         'stabx',
388         'bi','ei',
389         'bf','ef',
390         'bs','es',
391         'line','function');
392       directivestr : array[TAsmDirective] of string[23]=(
393         'indirect_symbol',
394         'extern','nasm_import', 'tc', 'reference',
395         'no_dead_strip','weak','lazy_reference','weak',
396         { for Jasmin }
397         'class','interface','super','field','limit','line',
398         { .ent/.end for MIPS }
399         'ent','end',
400         { supported by recent clang-based assemblers for data-in-code }
401         'data_region','end_data_region',
402         { ARM }
403         'thumb_func',
404         'code',
405         'cpu',
406         { for the OMF object format }
407         'omf_line'
408       );
409       sehdirectivestr : array[TAsmSehDirective] of string[16]=(
410         '.seh_proc','.seh_endproc',
411         '.seh_endprologue','.seh_handler','.seh_handlerdata',
412         '.seh_eh','.seh_32','seh_no32',
413         '.seh_setframe','.seh_stackalloc','.seh_pushreg',
414         '.seh_savereg','.seh_savexmm','.seh_pushframe',
415         '.pushnv','.savenv'
416       );
417       symbolpairkindstr: array[TSymbolPairKind] of string[11]=(
418         '.set', '.thumb_set', '.localentry'
419       );
420 
421     type
422         tai = class;
423 
424         { please keep the size of this record <=12 bytes and keep it properly aligned }
425         toper = record
426           ot : longint;
427           case typ : toptype of
428             top_none   : ();
429             top_reg    : (reg:tregister);
430             top_ref    : (ref:preference);
431             top_const  : (val:tcgint);
432             top_bool   : (b:boolean);
433             { local varsym that will be inserted in pass_generate_code }
434             top_local  : (localoper:plocaloper);
435         {$ifdef arm}
436             top_regset : (regset:^tcpuregisterset; regtyp: tregistertype; subreg: tsubregister; usermode: boolean);
437             top_modeflags : (modeflags : tcpumodeflags);
438             top_specialreg : (specialreg:tregister; specialflags:tspecialregflags);
439         {$endif arm}
440         {$if defined(arm) or defined(aarch64)}
441             top_shifterop : (shifterop : pshifterop);
442             top_conditioncode : (cc : TAsmCond);
443             top_realconst : (val_real:bestreal);
444         {$endif defined(arm) or defined(aarch64)}
445         {$ifdef m68k}
446             top_regset : (dataregset,addrregset,fpuregset: tcpuregisterset);
447             top_regpair : (reghi,reglo: tregister);
448             top_realconst : (val_real:bestreal);
449         {$endif m68k}
450         {$ifdef jvm}
451             top_single : (sval:single);
452             top_double : (dval:double);
453             top_string : (pcvallen: aint; pcval: pchar);
454             top_wstring : (pwstrval: pcompilerwidestring);
455         {$endif jvm}
456         {$ifdef llvm}
457             top_single : (sval:single);
458             top_double : (dval:double);
459             top_undef :  ();
460           {$ifdef cpuextended}
461             top_extended80 : (eval:extended);
462           {$endif cpuextended}
463             top_tai    : (ai: tai);
464             top_def    : (def: tdef);
465             top_cond   : (cond: topcmp);
466             top_fpcond : (fpcond: tllvmfpcmp);
467             top_para   : (paras: tfplist);
468             top_asmlist : (asmlist: tasmlist);
469         {$endif llvm}
470         end;
471         poper=^toper;
472 
473        { abstract assembler item }
474        tai = class(TLinkedListItem)
475 {$ifndef NOOPT}
476           { pointer to record with optimizer info about this tai object }
477           optinfo  : pointer;
478 {$endif NOOPT}
479           typ      : taitype;
480           constructor Create;
481           constructor ppuload(t:taitype;ppufile:tcompilerppufile);virtual;
482           procedure ppuwrite(ppufile:tcompilerppufile);virtual;
483           procedure buildderefimpl;virtual;
484           procedure derefimpl;virtual;
485        end;
486 
487        { abstract assembler item with line information }
488        tailineinfo = class(tai)
489         fileinfo : tfileposinfo;
490         constructor Create;
491         constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
492         procedure ppuwrite(ppufile:tcompilerppufile);override;
493        end;
494 
495        tai_simple = class(tai)
496          constructor create(_typ : taitype);
497        end;
498 
499        taiclass = class of tai;
500 
501        taiclassarray = array[taitype] of taiclass;
502 
503        { Generates an assembler string }
504        tai_string = class(tailineinfo)
505           str : pchar;
506           { extra len so the string can contain an \0 }
507           len : longint;
508           constructor Create(const _str : string);
509           constructor Create_pchar(_str : pchar;length : longint);
510           destructor Destroy;override;
511           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
512           procedure ppuwrite(ppufile:tcompilerppufile);override;
getcopynull513           function getcopy:tlinkedlistitem;override;
514        end;
515 
516        { Generates a common label }
517        tai_symbol = class(tai)
518           sym       : tasmsymbol;
519           value     : puint;
520           size      : longint;
521           is_global,
522           has_value : boolean;
523           constructor Create(_sym:tasmsymbol;siz:longint);
524           constructor Create_Global(_sym:tasmsymbol;siz:longint);
525           constructor Createname(const _name : string;_symtyp:Tasmsymtype;siz:longint;def:tdef);
526           constructor Createname_global(const _name : string;_symtyp:Tasmsymtype;siz:longint;def:tdef);
527           constructor Createname_global_value(const _name : string;_symtyp:Tasmsymtype;siz:longint;val:ptruint;def:tdef);
528           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
529           procedure ppuwrite(ppufile:tcompilerppufile);override;
530           procedure derefimpl;override;
531        end;
532 
533        tai_symbol_end = class(tailineinfo)
534           sym : tasmsymbol;
535           constructor Create(_sym:tasmsymbol);
536           constructor Createname(const _name : string);
537           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
538           procedure ppuwrite(ppufile:tcompilerppufile);override;
539           procedure derefimpl;override;
540        end;
541 
542        tai_directive = class(tailineinfo)
543           name : ansistring;
544           directive : TAsmDirective;
545           constructor Create(_directive:TAsmDirective;const _name:ansistring);
546           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
547           procedure ppuwrite(ppufile:tcompilerppufile);override;
548        end;
549 
550        { Generates an assembler label }
551        tai_label = class(tai)
552           labsym    : tasmlabel;
553 {$ifdef arm}
554           { set to true when the label has been moved by insertpcrelativedata to the correct location
555             so one label can be used multiple times }
556           moved     : boolean;
557           { true, if a label has been already inserted, this is important for arm thumb where no negative
558             pc relative offsets are allowed }
559           inserted  : boolean;
560 {$endif arm}
561           constructor Create(_labsym : tasmlabel);
562           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
563           procedure ppuwrite(ppufile:tcompilerppufile);override;
564           procedure derefimpl;override;
565        end;
566 
567        { Generates an assembler comment }
568        tai_comment = class(tai)
569           str : pchar;
570           constructor Create(_str : pchar);
571           destructor Destroy; override;
572           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
573           procedure ppuwrite(ppufile:tcompilerppufile);override;
getcopynull574           function getcopy:tlinkedlistitem;override;
575        end;
576 
577        type
578          TSectionFlags = (SF_None,SF_A,SF_W,SF_X);
579          TSectionProgbits = (SPB_None,SPB_PROGBITS,SPB_NOBITS);
580 
581        { Generates a section / segment directive }
582        tai_section = class(tai)
583           sectype  : TAsmSectiontype;
584           secorder : TasmSectionorder;
585           secalign : longint;
586           name     : pshortstring;
587           { used in binary writer }
588           sec      : TObjSection;
589           { used only by ELF so far }
590           secflags : TSectionFlags;
591           secprogbits : TSectionProgbits;
592           destructor Destroy;override;
593           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
594           procedure ppuwrite(ppufile:tcompilerppufile);override;
595 {$push}{$warnings off}
596          private
597           { this constructor is made private on purpose }
598           { because sections should be created via new_section() }
599           constructor Create(Asectype:TAsmSectiontype;const Aname:string;Aalign:longint;Asecorder:TasmSectionorder=secorder_default);
600 {$pop}
601        end;
602 
603 
604        { Generates an uninitializised data block }
605        tai_datablock = class(tailineinfo)
606           is_global : boolean;
607           sym       : tasmsymbol;
608           size      : asizeint;
609           constructor Create(const _name : string;_size : asizeint; def: tdef);
610           constructor Create_global(const _name : string;_size : asizeint; def: tdef);
611           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
612           procedure ppuwrite(ppufile:tcompilerppufile);override;
613           procedure derefimpl;override;
614        end;
615 
616 
617        { Generates an integer const }
618 
619        { tai_const }
620 
621        tai_const = class(tai)
622           sym,
623           endsym  : tasmsymbol;
624           { if symbols and offset are provided the symofs is used,
625             the value is calculated during assembling }
626           symofs,
627           value   : int64;
628           consttype : taiconst_type;
629           { we use for the 128bit int64/qword for now because I can't imagine a
630             case where we need 128 bit now (FK) }
631           constructor Create(_typ:taiconst_type;_value : int64);
632           constructor Create_128bit(_value : int64);
633           constructor Create_64bit(_value : int64);
634           constructor Create_32bit(_value : longint);
635           constructor Create_16bit(_value : word);
636           constructor Create_64bit_unaligned(_value : int64);
637           constructor Create_32bit_unaligned(_value : longint);
638           constructor Create_16bit_unaligned(_value : word);
639           constructor Create_8bit(_value : byte);
640           constructor Create_char(size: integer; _value: dword);
641           constructor Create_sleb128bit(_value : int64);
642           constructor Create_uleb128bit(_value : qword);
643           constructor Create_aint(_value : aint);
644           constructor Create_sizeint(_value : asizeint);
645           constructor Create_sizeint_unaligned(_value : asizeint);
646           constructor Create_sym(_sym:tasmsymbol);
647 {$ifdef i8086}
648           constructor Create_sym_near(_sym:tasmsymbol);
649           constructor Create_sym_far(_sym:tasmsymbol);
650           constructor Createname_near(const name:string;ofs:asizeint);
651           constructor Createname_far(const name:string;ofs:asizeint);
652           constructor Createname_near(const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
653           constructor Createname_far(const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
654 {$endif i8086}
655           constructor Create_type_sym(_typ:taiconst_type;_sym:tasmsymbol);
656           constructor Create_sym_offset(_sym:tasmsymbol;ofs:asizeint);
657           constructor Create_type_sym_offset(_typ:taiconst_type;_sym:tasmsymbol;ofs:asizeint);
658           constructor Create_rel_sym(_typ:taiconst_type;_sym,_endsym:tasmsymbol);
659           constructor Create_rel_sym_offset(_typ : taiconst_type; _sym,_endsym : tasmsymbol; _ofs : int64);
660           constructor Create_rva_sym(_sym:tasmsymbol);
661           constructor Createname(const name:string;ofs:asizeint);
662           constructor Createname(const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
663           constructor Create_type_name(_typ:taiconst_type;const name:string;ofs:asizeint);
664           constructor Create_type_name(_typ:taiconst_type;const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
665           constructor Create_nil_codeptr;
666           constructor Create_nil_codeptr_unaligned;
667           constructor Create_nil_dataptr;
668           constructor Create_nil_dataptr_unaligned;
669           constructor Create_int_codeptr(_value: int64);
670           constructor Create_int_codeptr_unaligned(_value: int64);
671           constructor Create_int_dataptr(_value: int64);
672           constructor Create_int_dataptr_unaligned(_value: int64);
673 {$ifdef i8086}
674           constructor Create_seg_name(const name:string);
675           constructor Create_dgroup;
676           constructor Create_fardataseg;
677 {$endif i8086}
678           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
679           procedure ppuwrite(ppufile:tcompilerppufile);override;
680           procedure derefimpl;override;
getcopynull681           function getcopy:tlinkedlistitem;override;
sizenull682           function size:longint;
683        end;
684 
685        { floating point const }
686        tformatoptions = (fo_none,fo_hiloswapped);
687        tai_realconst = class(tai)
688           realtyp: tairealconsttype;
689           savesize: byte;
690           value: record
691             case tairealconsttype of
692               aitrealconst_s32bit: (s32val: ts32real);
693               aitrealconst_s64bit: (s64val: ts64real);
694               aitrealconst_s80bit: (s80val: ts80real);
695               aitrealconst_s128bit: (s128val: ts128real);
696               aitrealconst_s64comp: (s64compval: ts64comp);
697           end;
698 {$ifdef ARM}
699           formatoptions : tformatoptions;
700 {$endif ARM}
701           constructor create_s32real(val: ts32real);
702           constructor create_s64real(val: ts64real);
703 {$ifdef ARM}
704           constructor create_s64real_hiloswapped(val : ts64real);
705 {$endif ARM}
706           constructor create_s80real(val: ts80real; _savesize: byte);
707           constructor create_s128real(val: ts128real);
708           constructor create_s64compreal(val: ts64comp);
709           constructor ppuload(t: taitype;ppufile: tcompilerppufile); override;
710           procedure ppuwrite(ppufile: tcompilerppufile); override;
getcopynull711           function getcopy:tlinkedlistitem;override;
datasizenull712           function datasize: word;
713        end;
714 
715        { tai_stab }
716 
717        tai_stab = class(tai)
718           str : pchar;
719           stabtype : TStabType;
720           constructor Create(_stabtype:TStabType;_str : pchar);
721           constructor Create_str(_stabtype:TStabType;const s:string);
722           constructor create_ansistr(_stabtype: TStabType; const s: ansistring);
723           destructor Destroy;override;
724        end;
725 
726        tai_force_line = class(tailineinfo)
727           constructor Create;
728        end;
729 
730        tai_function_name = class(tai)
731           funcname : pshortstring;
732           constructor create(const s:string);
733           destructor destroy;override;
734        end;
735 
736        { Insert a cut to split assembler into several smaller files }
737        tai_cutobject = class(tai)
738           place : tcutplace;
739           constructor Create;
740           constructor Create_begin;
741           constructor Create_end;
742           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
743           procedure ppuwrite(ppufile:tcompilerppufile);override;
744        end;
745 
746        { Insert a marker for assembler and inline blocks }
747        tai_marker = class(tai)
748           Kind: TAsmMarker;
749           Constructor Create(_Kind: TAsmMarker);
750           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
751           procedure ppuwrite(ppufile:tcompilerppufile);override;
752        end;
753 
754        tai_tempalloc = class(tai)
755           allocation : boolean;
756 {$ifdef EXTDEBUG}
757           problem : pshortstring;
758 {$endif EXTDEBUG}
759           temppos,
760           tempsize   : longint;
761           constructor alloc(pos,size:longint);
762           constructor dealloc(pos,size:longint);
763 {$ifdef EXTDEBUG}
764           constructor allocinfo(pos,size:longint;const st:string);
765 {$endif EXTDEBUG}
766           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
767           destructor destroy;override;
768           procedure ppuwrite(ppufile:tcompilerppufile);override;
769        end;
770 
771        tai_regalloc = class(tai)
772           reg     : tregister;
773           ratype  : TRegAllocType;
774           { tells BuildLabelTableAndFixRegAlloc that the deallocation should be kept }
775           keep    : boolean;
776           { reg(de)alloc belongs to this instruction, this
777             is only used for automatic inserted (de)alloc for
778             imaginary register and required for spilling code }
779           instr   : tai;
780           constructor alloc(r : tregister;ainstr:tai);
781           constructor dealloc(r : tregister;ainstr:tai);
782           constructor sync(r : tregister);
783           constructor resize(r : tregister);
784           constructor markused(r : tregister);
785           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
786           procedure ppuwrite(ppufile:tcompilerppufile);override;
787        end;
788 
789        tadd_reg_instruction_proc=procedure(instr:Tai;r:tregister) of object;
790 
791         { Class template for assembler instructions
792         }
793         tai_cpu_abstract = class(tailineinfo)
794         protected
795            procedure ppuloadoper(ppufile:tcompilerppufile;var o:toper);virtual;
796            procedure ppuwriteoper(ppufile:tcompilerppufile;const o:toper);virtual;
797            procedure ppubuildderefimploper(var o:toper);virtual;abstract;
798            procedure ppuderefoper(var o:toper);virtual;abstract;
799         public
800            { Condition flags for instruction }
801            condition : TAsmCond;
802            { Number of operands to instruction }
803            ops       : byte;
804            { Number of allocate oper structures }
805            opercnt   : byte;
806            { Operands of instruction }
807            oper      : array[0..max_operands-1] of poper;
808            { Actual opcode of instruction }
809            opcode    : tasmop;
810 {$ifdef x86}
811            segprefix : tregister;
812 {$endif x86}
813            { true if instruction is a jmp }
814            is_jmp    : boolean; { is this instruction a jump? (needed for optimizer) }
815            Constructor Create(op : tasmop);virtual;
816            Destructor Destroy;override;
getcopynull817            function getcopy:TLinkedListItem;override;
818            constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
819            procedure ppuwrite(ppufile:tcompilerppufile);override;
820            procedure buildderefimpl;override;
821            procedure derefimpl;override;
822            procedure SetCondition(const c:TAsmCond);
823            procedure allocate_oper(opers:longint);
824            procedure loadconst(opidx:longint;l:tcgint);
825            procedure loadsymbol(opidx:longint;s:tasmsymbol;sofs:longint);
826            procedure loadlocal(opidx:longint;s:pointer;sofs:longint;indexreg:tregister;scale:byte;getoffset,forceref:boolean);
827            procedure loadref(opidx:longint;const r:treference);
828            procedure loadreg(opidx:longint;r:tregister);
829            procedure loadoper(opidx:longint;o:toper); virtual;
830            procedure clearop(opidx:longint); virtual;
831            procedure freeop(opidx:longint);
832            { register allocator }
is_same_reg_movenull833            function is_same_reg_move(regtype: Tregistertype):boolean;virtual;
spilling_get_operation_typenull834            function spilling_get_operation_type(opnr: longint): topertype;virtual;
spilling_get_operation_type_refnull835            function spilling_get_operation_type_ref(opnr: longint; reg: tregister): topertype;virtual;
836 
Pass1null837            function  Pass1(objdata:TObjData):longint;virtual;
838            procedure Pass2(objdata:TObjData);virtual;
839 
840            procedure resetpass1; virtual;
841            procedure resetpass2; virtual;
842         end;
843         tai_cpu_class = class of tai_cpu_abstract;
844 
845         { Buffer type used for alignment }
846         tfillbuffer = array[0..63] of char;
847 
848         { alignment for operator }
849         tai_align_abstract = class(tai)
850            aligntype : byte;   { 1 = no align, 2 = word align, 4 = dword align }
851            fillsize  : byte;   { real size to fill }
852            fillop    : byte;   { value to fill with - optional }
853            use_op    : boolean;
854            constructor Create(b:byte);virtual;
855            constructor Create_op(b: byte; _op: byte);virtual;
856            constructor Create_zeros(b:byte);
857            constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
858            procedure ppuwrite(ppufile:tcompilerppufile);override;
calculatefillbufnull859            function calculatefillbuf(var buf : tfillbuffer;executable : boolean):pchar;virtual;
860         end;
861         tai_align_class = class of tai_align_abstract;
862 
863         tai_varloc = class(tai)
864            newlocation,
865            newlocationhi : tregister;
866            varsym : tsym;
867            constructor create(sym : tsym;loc : tregister);
868            constructor create64(sym : tsym;loc,lochi : tregister);
869 {$ifdef cpu64bitalu}
870            constructor create128(sym : tsym;loc,lochi : tregister);
871 {$endif cpu64bitalu}
872            constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
873            procedure ppuwrite(ppufile:tcompilerppufile);override;
874            procedure buildderefimpl;override;
875            procedure derefimpl;override;
876         end;
877 
878         TSehDirectiveDatatype=(sd_none,sd_string,sd_reg,sd_offset,sd_regoffset);
879 
880         TSehDirectiveData=record
881         case typ: TSehDirectiveDatatype of
882           sd_none: ();
883           sd_string: (name:pshortstring;flags:byte);
884           sd_reg,sd_offset,sd_regoffset: (reg:TRegister;offset:dword);
885         end;
886 
887         tai_seh_directive = class(tai)
888           kind: TAsmSehDirective;
889           data: TSehDirectiveData;
890           constructor create(_kind:TAsmSehDirective);
891           constructor create_name(_kind:TAsmSehDirective;const _name: string);
892           constructor create_reg(_kind:TAsmSehDirective;r:TRegister);
893           constructor create_offset(_kind:TAsmSehDirective;ofs:dword);
894           constructor create_reg_offset(_kind:TAsmSehDirective;r:TRegister;ofs:dword);
895           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
896           destructor destroy;override;
897           procedure ppuwrite(ppufile:tcompilerppufile);override;
898           procedure generate_code(objdata:TObjData);virtual;
899           property datatype: TSehDirectiveDatatype read data.typ;
900         end;
901         tai_seh_directive_class=class of tai_seh_directive;
902 
903 {$ifdef JVM}
904         { JVM variable live range description }
905         tai_jvar = class(tai)
906           stackslot: longint;
907           desc: pshortstring;
908           startlab,stoplab: tasmsymbol;
909 
910           constructor Create(_stackslot: longint; const _desc: shortstring; _startlab, _stoplab: TAsmSymbol);
911           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
912           procedure ppuwrite(ppufile:tcompilerppufile);override;
913           destructor destroy;override;
914         end;
915         tai_jvar_class = class of tai_jvar;
916 
917         { JVM exception catch description }
918         tai_jcatch = class(tai)
919           name: pshortstring;
920           startlab,stoplab,handlerlab: tasmsymbol;
921 
922           constructor Create(const _name: shortstring; _startlab, _stoplab, _handlerlab: TAsmSymbol);
923           destructor destroy;override;
924           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
925           procedure ppuwrite(ppufile:tcompilerppufile);override;
926         end;
927         tai_jcatch_class = class of tai_jcatch;
928 {$endif JVM}
929 
930         tai_symbolpair = class(tai)
931           kind: TSymbolPairKind;
932           sym,
933           value: pshortstring;
934           constructor create(akind: TSymbolPairKind; const asym, avalue: string);
935           destructor destroy;override;
936           constructor ppuload(t:taitype;ppufile:tcompilerppufile);override;
937           procedure ppuwrite(ppufile:tcompilerppufile);override;
938         end;
939 
940     var
941       { array with all class types for tais }
942       aiclass : taiclassarray;
943 
944       { target specific tais, possibly overwritten in target specific aasmcpu }
945       cai_align : tai_align_class = tai_align_abstract;
946       cai_cpu   : tai_cpu_class = tai_cpu_abstract;
947       cai_seh_directive: tai_seh_directive_class = tai_seh_directive;
948 
949       { hook to notify uses of registers }
950       add_reg_instruction_hook : tadd_reg_instruction_proc;
951 
952     procedure maybe_new_object_file(list:TAsmList);
new_sectionnull953     function new_section(list:TAsmList;Asectype:TAsmSectiontype;const Aname:string;Aalign:byte;Asecorder:TasmSectionorder=secorder_default) : tai_section;
954 
ppuloadainull955     function ppuloadai(ppufile:tcompilerppufile):tai;
956     procedure ppuwriteai(ppufile:tcompilerppufile;n:tai);
957 
958 
959 implementation
960 
961     uses
962 {$ifdef x86}
963       aasmcpu,
964 {$endif x86}
965       SysUtils,
966       verbose,
967       globals;
968 
969     const
970       pputaimarker = 254;
971 
972 {****************************************************************************
973                                  Helpers
974  ****************************************************************************}
975 
976     procedure maybe_new_object_file(list:TAsmList);
977       begin
978         if create_smartlink_library then
979           list.concat(tai_cutobject.create);
980       end;
981 
982 
new_sectionnull983     function new_section(list:TAsmList;Asectype:TAsmSectiontype;const Aname:string;Aalign:byte;Asecorder:TasmSectionorder=secorder_default) : tai_section;
984       begin
985         Result:=tai_section.create(Asectype,Aname,Aalign,Asecorder);
986         list.concat(Result);
987         inc(list.section_count);
988         list.concat(cai_align.create(Aalign));
989       end;
990 
991 
ppuloadainull992     function ppuloadai(ppufile:tcompilerppufile):tai;
993       var
994         b : byte;
995         t : taitype;
996       begin
997         { marker }
998         b:=ppufile.getbyte;
999         if b<>pputaimarker then
1000           internalerror(200208181);
1001         { load nodetype }
1002         t:=taitype(ppufile.getbyte);
1003         if t<>ait_none then
1004          begin
1005            if t>high(taitype) then
1006              internalerror(200208182);
1007            if not assigned(aiclass[t]) then
1008              internalerror(200208183);
1009            {writeln('taiload: ',taitypestr[t]);}
1010            { generate tai of the correct class }
1011            ppuloadai:=aiclass[t].ppuload(t,ppufile);
1012          end
1013         else
1014          ppuloadai:=nil;
1015       end;
1016 
1017 
1018     procedure ppuwriteai(ppufile:tcompilerppufile;n:tai);
1019       begin
1020         { marker, read by ppuloadnode }
1021         ppufile.putbyte(pputaimarker);
1022         if assigned(n) then
1023          begin
1024            { type, read by ppuloadnode }
1025            ppufile.putbyte(byte(n.typ));
1026            {writeln('taiwrite: ',taitypestr[n.typ]);}
1027            n.ppuwrite(ppufile);
1028          end
1029         else
1030          ppufile.putbyte(byte(ait_none));
1031       end;
1032 
1033 
1034     constructor tai_symbolpair.create(akind: TSymbolPairKind; const asym, avalue: string);
1035       begin
1036         inherited create;
1037         kind:=akind;
1038         typ:=ait_symbolpair;
1039         sym:=stringdup(asym);
1040         value:=stringdup(avalue);
1041       end;
1042 
1043     destructor tai_symbolpair.destroy;
1044       begin
1045         stringdispose(sym);
1046         stringdispose(value);
1047         inherited destroy;
1048       end;
1049 
1050     constructor tai_symbolpair.ppuload(t: taitype; ppufile: tcompilerppufile);
1051       begin
1052         inherited ppuload(t,ppufile);
1053         kind:=TSymbolPairKind(ppufile.getbyte);;
1054         sym:=ppufile.getpshortstring;
1055         value:=ppufile.getpshortstring;
1056       end;
1057 
1058     procedure tai_symbolpair.ppuwrite(ppufile: tcompilerppufile);
1059       begin
1060         inherited ppuwrite(ppufile);
1061         ppufile.putbyte(byte(kind));
1062         ppufile.putstring(sym^);
1063         ppufile.putstring(value^);
1064       end;
1065 
1066 
1067     constructor tai_varloc.create(sym: tsym; loc: tregister);
1068       begin
1069         inherited Create;
1070         typ:=ait_varloc;
1071         newlocation:=loc;
1072         newlocationhi:=NR_NO;
1073         varsym:=sym;
1074       end;
1075 
1076 
1077     constructor tai_varloc.create64(sym: tsym; loc, lochi: tregister);
1078       begin
1079         inherited Create;
1080         typ:=ait_varloc;
1081         newlocation:=loc;
1082         newlocationhi:=lochi;
1083         varsym:=sym;
1084       end;
1085 
1086 
1087 {$ifdef cpu64bitalu}
1088     constructor tai_varloc.create128(sym: tsym; loc, lochi: tregister);
1089       begin
1090         inherited Create;
1091         typ:=ait_varloc;
1092         newlocation:=loc;
1093         newlocationhi:=lochi;
1094         varsym:=sym;
1095       end;
1096 {$endif cpu64bitalu}
1097 
1098 
1099     constructor tai_varloc.ppuload(t: taitype; ppufile: tcompilerppufile);
1100       begin
1101         inherited ppuload(t, ppufile);
1102       end;
1103 
1104 
1105     procedure tai_varloc.ppuwrite(ppufile: tcompilerppufile);
1106       begin
1107         inherited ppuwrite(ppufile);
1108       end;
1109 
1110 
1111     procedure tai_varloc.buildderefimpl;
1112       begin
1113         inherited buildderefimpl;
1114       end;
1115 
1116 
1117     procedure tai_varloc.derefimpl;
1118       begin
1119         inherited derefimpl;
1120       end;
1121 
1122 
1123 {****************************************************************************
1124                              TAI
1125  ****************************************************************************}
1126 
1127     constructor tai.Create;
1128       begin
1129 {$ifndef NOOPT}
1130         optinfo:=nil;
1131 {$endif NOOPT}
1132       end;
1133 
1134 
1135     constructor tai.ppuload(t:taitype;ppufile:tcompilerppufile);
1136       begin
1137         typ:=t;
1138 {$ifndef NOOPT}
1139         optinfo:=nil;
1140 {$endif}
1141       end;
1142 
1143 
1144     procedure tai.ppuwrite(ppufile:tcompilerppufile);
1145       begin
1146       end;
1147 
1148 
1149     procedure tai.buildderefimpl;
1150       begin
1151       end;
1152 
1153 
1154     procedure tai.derefimpl;
1155       begin
1156       end;
1157 
1158 
1159 {****************************************************************************
1160                               TAILINEINFO
1161  ****************************************************************************}
1162 
1163     constructor tailineinfo.create;
1164      begin
1165        inherited create;
1166        fileinfo:=current_filepos;
1167      end;
1168 
1169 
1170     constructor tailineinfo.ppuload(t:taitype;ppufile:tcompilerppufile);
1171       begin
1172         inherited ppuload(t,ppufile);
1173         ppufile.getposinfo(fileinfo);
1174       end;
1175 
1176 
1177     procedure tailineinfo.ppuwrite(ppufile:tcompilerppufile);
1178       begin
1179         inherited ppuwrite(ppufile);
1180         ppufile.putposinfo(fileinfo);
1181       end;
1182 
1183 
1184 {****************************************************************************
1185                               TAI_SIMPLE
1186  ****************************************************************************}
1187 
1188     constructor tai_simple.create(_typ : taitype);
1189       begin
1190         inherited create;
1191         typ:=_typ;
1192       end;
1193 
1194 
1195 {****************************************************************************
1196                              TAI_SECTION
1197  ****************************************************************************}
1198 
1199     constructor tai_section.Create(Asectype:TAsmSectiontype;const Aname:string;Aalign:longint;Asecorder:TasmSectionorder=secorder_default);
1200       begin
1201         inherited Create;
1202         typ:=ait_section;
1203         sectype:=asectype;
1204         secalign:=Aalign;
1205         secorder:=Asecorder;
1206         name:=stringdup(Aname);
1207         sec:=nil;
1208       end;
1209 
1210 
1211     constructor tai_section.ppuload(t:taitype;ppufile:tcompilerppufile);
1212       begin
1213         inherited ppuload(t,ppufile);
1214         sectype:=TAsmSectiontype(ppufile.getbyte);
1215         secalign:=ppufile.getlongint;
1216         name:=ppufile.getpshortstring;
1217         secflags:=TSectionFlags(ppufile.getbyte);
1218         secprogbits:=TSectionProgbits(ppufile.getbyte);
1219         sec:=nil;
1220       end;
1221 
1222 
1223     destructor tai_section.Destroy;
1224       begin
1225         stringdispose(name);
1226       end;
1227 
1228 
1229     procedure tai_section.ppuwrite(ppufile:tcompilerppufile);
1230       begin
1231         inherited ppuwrite(ppufile);
1232         ppufile.putbyte(byte(sectype));
1233         ppufile.putlongint(secalign);
1234         ppufile.putstring(name^);
1235         ppufile.putbyte(byte(secflags));
1236         ppufile.putbyte(byte(secprogbits));
1237       end;
1238 
1239 
1240 {****************************************************************************
1241                              TAI_DATABLOCK
1242  ****************************************************************************}
1243 
1244     constructor tai_datablock.Create(const _name : string;_size : asizeint; def: tdef);
1245 
1246       begin
1247          inherited Create;
1248          typ:=ait_datablock;
1249          sym:=current_asmdata.DefineAsmSymbol(_name,AB_LOCAL,AT_DATA,def);
1250          { keep things aligned }
1251          if _size<=0 then
1252            _size:=sizeof(aint);
1253          size:=_size;
1254          is_global:=false;
1255       end;
1256 
1257 
1258     constructor tai_datablock.Create_global(const _name : string;_size : asizeint; def: tdef);
1259       begin
1260          inherited Create;
1261          typ:=ait_datablock;
1262          sym:=current_asmdata.DefineAsmSymbol(_name,AB_GLOBAL,AT_DATA,def);
1263          { keep things aligned }
1264          if _size<=0 then
1265            _size:=sizeof(aint);
1266          size:=_size;
1267          is_global:=true;
1268       end;
1269 
1270 
1271     constructor tai_datablock.ppuload(t:taitype;ppufile:tcompilerppufile);
1272       begin
1273         inherited Create;
1274         sym:=ppufile.getasmsymbol;
1275         size:=ppufile.getaint;
1276         is_global:=ppufile.getboolean;
1277       end;
1278 
1279 
1280     procedure tai_datablock.ppuwrite(ppufile:tcompilerppufile);
1281       begin
1282         inherited ppuwrite(ppufile);
1283         ppufile.putasmsymbol(sym);
1284         ppufile.putaint(size);
1285         ppufile.putboolean(is_global);
1286       end;
1287 
1288 
1289     procedure tai_datablock.derefimpl;
1290       begin
1291       end;
1292 
1293 
1294 {****************************************************************************
1295                                TAI_SYMBOL
1296  ****************************************************************************}
1297 
1298     constructor tai_symbol.Create(_sym:tasmsymbol;siz:longint);
1299       begin
1300          inherited Create;
1301          typ:=ait_symbol;
1302          sym:=_sym;
1303          size:=siz;
1304          { don't redefine global/external symbols as local, as code to access
1305            such symbols is different on some platforms }
1306          if not(sym.bind in [AB_NONE,AB_LOCAL]) then
1307            internalerror(2013081601);
1308          sym.bind:=AB_LOCAL;
1309          is_global:=false;
1310       end;
1311 
1312 
1313     constructor tai_symbol.Create_global(_sym:tasmsymbol;siz:longint);
1314       begin
1315          inherited Create;
1316          typ:=ait_symbol;
1317          sym:=_sym;
1318          size:=siz;
1319          { don't override PRIVATE_EXTERN with GLOBAL }
1320          if not(sym.bind in [AB_GLOBAL,AB_PRIVATE_EXTERN]) then
1321            sym.bind:=AB_GLOBAL;
1322          is_global:=true;
1323       end;
1324 
1325 
1326     constructor tai_symbol.Createname(const _name : string;_symtyp:Tasmsymtype;siz:longint;def:tdef);
1327       begin
1328          inherited Create;
1329          typ:=ait_symbol;
1330          sym:=current_asmdata.DefineAsmSymbol(_name,AB_LOCAL,_symtyp,def);
1331          size:=siz;
1332          is_global:=false;
1333       end;
1334 
1335 
1336     constructor tai_symbol.Createname_global(const _name : string;_symtyp:Tasmsymtype;siz:longint;def:tdef);
1337       begin
1338          inherited Create;
1339          typ:=ait_symbol;
1340          sym:=current_asmdata.DefineAsmSymbol(_name,AB_GLOBAL,_symtyp,def);
1341          size:=siz;
1342          is_global:=true;
1343       end;
1344 
1345 
1346     constructor tai_symbol.createname_global_value(const _name: string;_symtyp: tasmsymtype; siz: longint; val: ptruint;def:tdef);
1347       begin
1348         Createname_global(_name,_symtyp,siz,def);
1349         value:=val;
1350         has_value:=true;
1351       end;
1352 
1353 
1354     constructor tai_symbol.ppuload(t:taitype;ppufile:tcompilerppufile);
1355       begin
1356         inherited ppuload(t,ppufile);
1357         sym:=ppufile.getasmsymbol;
1358         size:=ppufile.getlongint;
1359         is_global:=ppufile.getboolean;
1360       end;
1361 
1362 
1363     procedure tai_symbol.ppuwrite(ppufile:tcompilerppufile);
1364       begin
1365         inherited ppuwrite(ppufile);
1366         ppufile.putasmsymbol(sym);
1367         ppufile.putlongint(size);
1368         ppufile.putboolean(is_global);
1369       end;
1370 
1371 
1372     procedure tai_symbol.derefimpl;
1373       begin
1374       end;
1375 
1376 
1377 {****************************************************************************
1378                                TAI_SYMBOL_END
1379  ****************************************************************************}
1380 
1381     constructor tai_symbol_end.Create(_sym:tasmsymbol);
1382       begin
1383          inherited Create;
1384          typ:=ait_symbol_end;
1385          sym:=_sym;
1386       end;
1387 
1388 
1389     constructor tai_symbol_end.Createname(const _name : string);
1390       begin
1391          inherited Create;
1392          typ:=ait_symbol_end;
1393          sym:=current_asmdata.GetAsmSymbol(_name);
1394          if not assigned(sym) then
1395            internalerror(2013080301);
1396       end;
1397 
1398 
1399     constructor tai_symbol_end.ppuload(t:taitype;ppufile:tcompilerppufile);
1400       begin
1401         inherited ppuload(t,ppufile);
1402         sym:=ppufile.getasmsymbol;
1403       end;
1404 
1405 
1406     procedure tai_symbol_end.ppuwrite(ppufile:tcompilerppufile);
1407       begin
1408         inherited ppuwrite(ppufile);
1409         ppufile.putasmsymbol(sym);
1410       end;
1411 
1412 
1413     procedure tai_symbol_end.derefimpl;
1414       begin
1415       end;
1416 
1417 
1418 {****************************************************************************
1419                                TAI_SYMBOL_END
1420  ****************************************************************************}
1421 
1422     constructor tai_directive.Create(_directive:TAsmDirective;const _name:ansistring);
1423       begin
1424          inherited Create;
1425          typ:=ait_directive;
1426          name:=_name;
1427          directive:=_directive;
1428       end;
1429 
1430 
1431     constructor tai_directive.ppuload(t:taitype;ppufile:tcompilerppufile);
1432       begin
1433         inherited ppuload(t,ppufile);
1434         name:=ppufile.getansistring;
1435         directive:=TAsmDirective(ppufile.getbyte);
1436       end;
1437 
1438 
1439     procedure tai_directive.ppuwrite(ppufile:tcompilerppufile);
1440       begin
1441         inherited ppuwrite(ppufile);
1442         ppufile.putansistring(name);
1443         ppufile.putbyte(byte(directive));
1444       end;
1445 
1446 
1447 {****************************************************************************
1448                                TAI_CONST
1449  ****************************************************************************}
1450 
1451     constructor tai_const.Create(_typ:taiconst_type;_value : int64);
1452       begin
1453          inherited Create;
1454          typ:=ait_const;
1455          consttype:=_typ;
1456          value:=_value;
1457          sym:=nil;
1458          endsym:=nil;
1459       end;
1460 
1461 
1462     constructor tai_const.Create_128bit(_value : int64);
1463       begin
1464          inherited Create;
1465          typ:=ait_const;
1466          consttype:=aitconst_128bit;
1467          value:=_value;
1468          sym:=nil;
1469          endsym:=nil;
1470       end;
1471 
1472 
1473     constructor tai_const.Create_64bit(_value : int64);
1474       begin
1475          inherited Create;
1476          typ:=ait_const;
1477          consttype:=aitconst_64bit;
1478          value:=_value;
1479          sym:=nil;
1480          endsym:=nil;
1481       end;
1482 
1483 
1484     constructor tai_const.Create_32bit(_value : longint);
1485       begin
1486          inherited Create;
1487          typ:=ait_const;
1488          consttype:=aitconst_32bit;
1489          value:=_value;
1490          sym:=nil;
1491          endsym:=nil;
1492       end;
1493 
1494 
1495     constructor tai_const.Create_16bit(_value : word);
1496       begin
1497          inherited Create;
1498          typ:=ait_const;
1499          consttype:=aitconst_16bit;
1500          value:=_value;
1501          sym:=nil;
1502          endsym:=nil;
1503       end;
1504 
1505     constructor tai_const.Create_64bit_unaligned(_value : int64);
1506       begin
1507          inherited Create;
1508          typ:=ait_const;
1509          consttype:=aitconst_64bit_unaligned;
1510          value:=_value;
1511          sym:=nil;
1512          endsym:=nil;
1513       end;
1514 
1515 
1516     constructor tai_const.Create_32bit_unaligned(_value : longint);
1517       begin
1518          inherited Create;
1519          typ:=ait_const;
1520          consttype:=aitconst_32bit_unaligned;
1521          value:=_value;
1522          sym:=nil;
1523          endsym:=nil;
1524       end;
1525 
1526 
1527     constructor tai_const.Create_16bit_unaligned(_value : word);
1528       begin
1529          inherited Create;
1530          typ:=ait_const;
1531          consttype:=aitconst_16bit_unaligned;
1532          value:=_value;
1533          sym:=nil;
1534          endsym:=nil;
1535       end;
1536 
1537 
1538     constructor tai_const.Create_8bit(_value : byte);
1539       begin
1540          inherited Create;
1541          typ:=ait_const;
1542          consttype:=aitconst_8bit;
1543          value:=_value;
1544          sym:=nil;
1545          endsym:=nil;
1546       end;
1547 
1548 
1549     constructor tai_const.Create_char(size: integer; _value: dword);
1550       begin
1551          inherited Create;
1552          typ:=ait_const;
1553          case size of
1554             1:
1555               begin
1556                 consttype:=aitconst_8bit;
1557                 value:=byte(_value)
1558               end;
1559              2:
1560                begin
1561                  consttype:=aitconst_16bit;
1562                  value:=word(_value)
1563                end
1564              else
1565                InternalError(2010030701)
1566          end
1567       end;
1568 
1569 
1570     constructor tai_const.Create_sleb128bit(_value : int64);
1571       begin
1572          inherited Create;
1573          typ:=ait_const;
1574          consttype:=aitconst_sleb128bit;
1575          value:=_value;
1576          sym:=nil;
1577          endsym:=nil;
1578       end;
1579 
1580 
1581     constructor tai_const.Create_uleb128bit(_value : qword);
1582       begin
1583          inherited Create;
1584          typ:=ait_const;
1585          consttype:=aitconst_uleb128bit;
1586          value:=int64(_value);
1587          sym:=nil;
1588          endsym:=nil;
1589       end;
1590 
1591 
1592     constructor tai_const.Create_aint(_value : aint);
1593       begin
1594          inherited Create;
1595          typ:=ait_const;
1596          consttype:=aitconst_aint;
1597          value:=_value;
1598          sym:=nil;
1599          endsym:=nil;
1600       end;
1601 
1602 
1603     constructor tai_const.Create_sizeint(_value : asizeint);
1604       begin
1605         inherited Create;
1606         typ:=ait_const;
1607         consttype:=aitconst_sizeint;
1608         value:=_value;
1609         sym:=nil;
1610         endsym:=nil;
1611       end;
1612 
1613 
1614     constructor tai_const.Create_sizeint_unaligned(_value : asizeint);
1615       begin
1616         inherited Create;
1617         typ:=ait_const;
1618         consttype:=aitconst_sizeint_unaligned;
1619         value:=_value;
1620         sym:=nil;
1621         endsym:=nil;
1622       end;
1623 
1624 
1625     constructor tai_const.Create_type_sym(_typ:taiconst_type;_sym:tasmsymbol);
1626       begin
1627          inherited Create;
1628          typ:=ait_const;
1629          consttype:=_typ;
1630          sym:=_sym;
1631          endsym:=nil;
1632          value:=0;
1633          { update sym info }
1634          if assigned(sym) then
1635            sym.increfs;
1636       end;
1637 
1638 
1639     constructor tai_const.Create_sym(_sym:tasmsymbol);
1640       begin
1641          self.create_sym_offset(_sym,0);
1642       end;
1643 
1644 
1645 {$ifdef i8086}
1646     constructor tai_const.Create_sym_near(_sym: tasmsymbol);
1647       begin
1648          self.create_sym(_sym);
1649          consttype:=aitconst_ptr;
1650       end;
1651 
1652 
1653     constructor tai_const.Create_sym_far(_sym: tasmsymbol);
1654       begin
1655         self.create_sym(_sym);
1656         consttype:=aitconst_farptr;
1657       end;
1658 
1659 
1660     constructor tai_const.Createname_near(const name:string;ofs:asizeint);
1661       begin
1662         self.Createname(name,ofs);
1663         consttype:=aitconst_ptr;
1664       end;
1665 
1666 
1667     constructor tai_const.Createname_far(const name:string;ofs:asizeint);
1668       begin
1669         self.Createname(name,ofs);
1670         consttype:=aitconst_farptr;
1671       end;
1672 
1673 
1674     constructor tai_const.Createname_near(const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
1675       begin
1676         self.Createname(name,_symtyp,ofs);
1677         consttype:=aitconst_ptr;
1678       end;
1679 
1680 
1681     constructor tai_const.Createname_far(const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
1682       begin
1683         self.Createname(name,_symtyp,ofs);
1684         consttype:=aitconst_farptr;
1685       end;
1686 {$endif i8086}
1687 
1688 
1689     constructor tai_const.Create_sym_offset(_sym:tasmsymbol;ofs:asizeint);
1690       begin
1691          inherited Create;
1692          typ:=ait_const;
1693 {$ifdef i8086}
1694          if assigned(_sym) and (_sym.typ=AT_DATA) then
1695            begin
1696              if current_settings.x86memorymodel in x86_far_data_models then
1697                consttype:=aitconst_farptr
1698              else
1699                consttype:=aitconst_ptr;
1700            end
1701          else
1702            begin
1703              if current_settings.x86memorymodel in x86_far_code_models then
1704                consttype:=aitconst_farptr
1705              else
1706                consttype:=aitconst_ptr;
1707            end;
1708 {$else i8086}
1709 {$ifdef avr}
thennull1710          if assigned(_sym) and (_sym.typ=AT_FUNCTION) then
1711            consttype:=aitconst_gs
1712          else
1713 {$endif avr}
1714          consttype:=aitconst_ptr;
1715 {$endif i8086}
1716          { sym is allowed to be nil, this is used to write nil pointers }
1717          sym:=_sym;
1718          endsym:=nil;
1719          { store the original offset in symofs so that we can recalculate the
1720            value field in the assembler }
1721          symofs:=ofs;
1722          value:=ofs;
1723          { update sym info }
1724          if assigned(sym) then
1725            sym.increfs;
1726       end;
1727 
1728 
1729     constructor tai_const.Create_type_sym_offset(_typ : taiconst_type;_sym : tasmsymbol; ofs : asizeint);
1730       begin
1731          inherited Create;
1732          typ:=ait_const;
1733          consttype:=_typ;
1734          { sym is allowed to be nil, this is used to write nil pointers }
1735          sym:=_sym;
1736          endsym:=nil;
1737          { store the original offset in symofs so that we can recalculate the
1738            value field in the assembler }
1739          symofs:=ofs;
1740          value:=ofs;
1741          { update sym info }
1742          if assigned(sym) then
1743            sym.increfs;
1744       end;
1745 
1746 
1747     constructor tai_const.Create_rel_sym(_typ:taiconst_type;_sym,_endsym:tasmsymbol);
1748       begin
1749          self.create_sym_offset(_sym,0);
1750          consttype:=_typ;
1751          endsym:=_endsym;
1752          endsym.increfs;
1753       end;
1754 
1755 
1756     constructor tai_const.Create_rel_sym_offset(_typ: taiconst_type; _sym,_endsym: tasmsymbol; _ofs: int64);
1757        begin
1758          self.create_sym_offset(_sym,_ofs);
1759          consttype:=_typ;
1760          endsym:=_endsym;
1761          endsym.increfs;
1762        end;
1763 
1764 
1765     constructor tai_const.Create_rva_sym(_sym:tasmsymbol);
1766       begin
1767          self.create_sym_offset(_sym,0);
1768          consttype:=aitconst_rva_symbol;
1769       end;
1770 
1771 
1772     constructor tai_const.Createname(const name:string;ofs:asizeint);
1773       begin
1774          self.Createname(name,AT_NONE,ofs);
1775       end;
1776 
1777 
1778     constructor tai_const.Createname(const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
1779       begin
1780          self.create_sym_offset(current_asmdata.RefAsmSymbol(name,_symtyp),ofs);
1781       end;
1782 
1783 
1784     constructor tai_const.Create_type_name(_typ:taiconst_type;const name:string;ofs:asizeint);
1785       begin
1786          self.Create_type_name(_typ,name,AT_NONE,ofs);
1787       end;
1788 
1789 
1790     constructor tai_const.Create_type_name(_typ:taiconst_type;const name:string;_symtyp:Tasmsymtype;ofs:asizeint);
1791       begin
1792          self.create_sym_offset(current_asmdata.RefAsmSymbol(name,_symtyp),ofs);
1793          consttype:=_typ;
1794       end;
1795 
1796 
1797     constructor tai_const.Create_nil_codeptr;
1798       begin
1799         self.Create_int_codeptr(0);
1800       end;
1801 
1802 
1803     constructor tai_const.Create_nil_codeptr_unaligned;
1804       begin
1805         self.Create_int_codeptr_unaligned(0);
1806       end;
1807 
1808 
1809     constructor tai_const.Create_nil_dataptr;
1810       begin
1811         self.Create_int_dataptr(0);
1812       end;
1813 
1814 
1815     constructor tai_const.Create_nil_dataptr_unaligned;
1816       begin
1817         self.Create_int_dataptr_unaligned(0);
1818       end;
1819 
1820 
1821     constructor tai_const.Create_int_codeptr(_value: int64);
1822       begin
1823         inherited Create;
1824         typ:=ait_const;
1825 {$ifdef i8086}
1826         if current_settings.x86memorymodel in x86_far_code_models then
1827           consttype:=aitconst_farptr
1828         else
1829 {$endif i8086}
1830 {$ifdef avr}
1831           consttype:=aitconst_gs;
1832 {$else avr}
1833           consttype:=aitconst_ptr;
1834 {$endif avr}
1835         sym:=nil;
1836         endsym:=nil;
1837         symofs:=0;
1838         value:=_value;
1839       end;
1840 
1841 
1842     constructor tai_const.Create_int_codeptr_unaligned(_value: int64);
1843       begin
1844         inherited Create;
1845         typ:=ait_const;
1846 {$ifdef i8086}
1847         if current_settings.x86memorymodel in x86_far_code_models then
1848           consttype:=aitconst_farptr
1849         else
1850 {$endif i8086}
1851 {$ifdef avr}
1852           consttype:=aitconst_gs;
1853 {$else avr}
1854           consttype:=aitconst_ptr_unaligned;
1855 {$endif avr}
1856         sym:=nil;
1857         endsym:=nil;
1858         symofs:=0;
1859         value:=_value;
1860       end;
1861 
1862 
1863     constructor tai_const.Create_int_dataptr(_value: int64);
1864       begin
1865         inherited Create;
1866         typ:=ait_const;
1867 {$ifdef i8086}
1868         if current_settings.x86memorymodel in x86_far_data_models then
1869           consttype:=aitconst_farptr
1870         else
1871 {$endif i8086}
1872           consttype:=aitconst_ptr;
1873         sym:=nil;
1874         endsym:=nil;
1875         symofs:=0;
1876         value:=_value;
1877       end;
1878 
1879 
1880     constructor tai_const.Create_int_dataptr_unaligned(_value: int64);
1881       begin
1882         inherited Create;
1883         typ:=ait_const;
1884 {$ifdef i8086}
1885         if current_settings.x86memorymodel in x86_far_data_models then
1886           consttype:=aitconst_farptr
1887         else
1888 {$endif i8086}
1889           consttype:=aitconst_ptr_unaligned;
1890         sym:=nil;
1891         endsym:=nil;
1892         symofs:=0;
1893         value:=_value;
1894       end;
1895 
1896 
1897 {$ifdef i8086}
1898     constructor tai_const.Create_seg_name(const name:string);
1899       begin
1900         self.Createname(name,0);
1901         self.consttype:=aitconst_seg;
1902       end;
1903 
1904 
1905     constructor tai_const.Create_dgroup;
1906       begin
1907         self.Create_16bit(0);
1908         self.consttype:=aitconst_dgroup;
1909       end;
1910 
1911 
1912     constructor tai_const.Create_fardataseg;
1913       begin
1914         self.Create_16bit(0);
1915         self.consttype:=aitconst_fardataseg;
1916       end;
1917 {$endif i8086}
1918 
1919 
1920     constructor tai_const.ppuload(t:taitype;ppufile:tcompilerppufile);
1921       begin
1922         inherited ppuload(t,ppufile);
1923         consttype:=taiconst_type(ppufile.getbyte);
1924         sym:=ppufile.getasmsymbol;
1925         endsym:=ppufile.getasmsymbol;
1926         value:=ppufile.getint64;
1927       end;
1928 
1929 
1930     procedure tai_const.ppuwrite(ppufile:tcompilerppufile);
1931       begin
1932         inherited ppuwrite(ppufile);
1933         ppufile.putbyte(byte(consttype));
1934         ppufile.putasmsymbol(sym);
1935         ppufile.putasmsymbol(endsym);
1936         ppufile.putint64(value);
1937       end;
1938 
1939 
1940     procedure tai_const.derefimpl;
1941       begin
1942       end;
1943 
1944 
tai_const.getcopynull1945     function tai_const.getcopy:tlinkedlistitem;
1946       begin
1947         getcopy:=inherited getcopy;
1948         { we need to increase the reference number }
1949         if assigned(sym) then
1950           sym.increfs;
1951         if assigned(endsym) then
1952           endsym.increfs;
1953       end;
1954 
1955 
tai_const.sizenull1956     function tai_const.size:longint;
1957       begin
1958         case consttype of
1959           aitconst_8bit :
1960             result:=1;
1961           aitconst_16bit,aitconst_16bit_unaligned :
1962             result:=2;
1963           aitconst_32bit,aitconst_darwin_dwarf_delta32,
1964 	  aitconst_32bit_unaligned:
1965             result:=4;
1966           aitconst_64bit,aitconst_darwin_dwarf_delta64,
1967 	  aitconst_64bit_unaligned:
1968             result:=8;
1969           aitconst_secrel32_symbol,
1970           aitconst_rva_symbol :
1971             if target_info.system=system_x86_64_win64 then
1972               result:=sizeof(longint)
1973             else
1974               result:=sizeof(pint);
1975           aitconst_uleb128bit :
1976             result:=LengthUleb128(qword(value));
1977           aitconst_sleb128bit :
1978             result:=LengthSleb128(value);
1979           aitconst_half16bit,
1980           aitconst_gs:
1981             result:=2;
1982           aitconst_farptr:
1983             result:=4;
1984           aitconst_dgroup,
1985           aitconst_fardataseg,
1986           aitconst_seg:
1987             result:=2;
1988           aitconst_got:
1989             result:=sizeof(pint);
1990           aitconst_gotoff_symbol:
1991             result:=4;
1992           else
1993             internalerror(200603253);
1994         end;
1995       end;
1996 
1997 
1998 {****************************************************************************
1999                                TAI_realconst
2000  ****************************************************************************}
2001 
2002     constructor tai_realconst.create_s32real(val: ts32real);
2003       begin
2004         inherited create;
2005         typ:=ait_realconst;
2006         realtyp:=aitrealconst_s32bit;
2007         savesize:=4;
2008         value.s32val:=val;
2009       end;
2010 
2011 
2012     constructor tai_realconst.create_s64real(val: ts64real);
2013       begin
2014         inherited create;
2015         typ:=ait_realconst;
2016         realtyp:=aitrealconst_s64bit;
2017         savesize:=8;
2018         value.s64val:=val;
2019       end;
2020 
2021 {$ifdef ARM}
2022     constructor tai_realconst.create_s64real_hiloswapped(val : ts64real);
2023       begin
2024         inherited create;
2025         typ:=ait_realconst;
2026         realtyp:=aitrealconst_s64bit;
2027         value.s64val:=val;
2028         savesize:=8;
2029         formatoptions:=fo_hiloswapped;
2030       end;
2031 
2032 {$endif ARM}
2033 
2034     constructor tai_realconst.create_s80real(val: ts80real; _savesize: byte);
2035       begin
2036         inherited create;
2037         typ:=ait_realconst;
2038         realtyp:=aitrealconst_s80bit;
2039         savesize:=_savesize;
2040         value.s80val:=val;
2041       end;
2042 
2043 
2044     constructor tai_realconst.create_s128real(val: ts128real);
2045       begin
2046         inherited create;
2047         typ:=ait_realconst;
2048         realtyp:=aitrealconst_s128bit;
2049         savesize:=16;
2050         value.s128val:=val;
2051       end;
2052 
2053 
2054     constructor tai_realconst.create_s64compreal(val: ts64comp);
2055       begin
2056         inherited create;
2057         typ:=ait_realconst;
2058         realtyp:=aitrealconst_s64comp;
2059         savesize:=8;
2060         value.s64compval:=val;
2061       end;
2062 
2063 
2064         constructor tai_realconst.ppuload(t: taitype; ppufile: tcompilerppufile);
2065       begin
2066         inherited;
2067         realtyp:=tairealconsttype(ppufile.getbyte);
2068 {$ifdef ARM}
2069         formatoptions:=tformatoptions(ppufile.getbyte);
2070 {$endif ARM}
2071         case realtyp of
2072           aitrealconst_s32bit:
2073             value.s32val:=ppufile.getreal;
2074           aitrealconst_s64bit:
2075             value.s64val:=ppufile.getreal;
2076           aitrealconst_s80bit:
2077             value.s80val:=ppufile.getreal;
2078           aitrealconst_s128bit:
2079             value.s128val:=ppufile.getreal;
2080           aitrealconst_s64comp:
2081             value.s64compval:=comp(ppufile.getint64);
2082           else
2083             internalerror(2014050602);
2084         end;
2085       end;
2086 
2087 
2088     procedure tai_realconst.ppuwrite(ppufile: tcompilerppufile);
2089       var
2090         c: comp;
2091       begin
2092         inherited ppuwrite(ppufile);
2093         ppufile.putbyte(byte(realtyp));
2094 {$ifdef ARM}
2095         ppufile.putbyte(byte(formatoptions));
2096 {$endif ARM}
2097         case realtyp of
2098           aitrealconst_s32bit:
2099             ppufile.putreal(value.s32val);
2100           aitrealconst_s64bit:
2101             ppufile.putreal(value.s64val);
2102           aitrealconst_s80bit:
2103             ppufile.putreal(value.s80val);
2104           aitrealconst_s128bit:
2105             ppufile.putreal(value.s128val);
2106           aitrealconst_s64comp:
2107             begin
2108               c:=comp(value.s64compval);
2109               ppufile.putint64(int64(c));
2110             end
2111           else
2112             internalerror(2014050601);
2113         end;
2114       end;
2115 
2116 
tai_realconst.getcopynull2117     function tai_realconst.getcopy: tlinkedlistitem;
2118       begin
2119         result:=inherited getcopy;
2120         tai_realconst(result).value:=value;
2121         tai_realconst(result).realtyp:=realtyp;
2122         tai_realconst(result).savesize:=savesize;
2123 {$ifdef ARM}
2124         tai_realconst(result).formatoptions:=formatoptions;
2125 {$endif ARM}
2126       end;
2127 
2128 
tai_realconst.datasizenull2129     function tai_realconst.datasize: word;
2130       begin
2131         case realtyp of
2132           aitrealconst_s32bit:
2133             result:=4;
2134           aitrealconst_s64bit,
2135           aitrealconst_s64comp:
2136             result:=8;
2137           aitrealconst_s80bit:
2138             result:=10;
2139           aitrealconst_s128bit:
2140             result:=16;
2141           else
2142             internalerror(2014050603);
2143         end;
2144       end;
2145 
2146 
2147 {****************************************************************************
2148                                TAI_STRING
2149  ****************************************************************************}
2150 
2151      constructor tai_string.Create(const _str : string);
2152        begin
2153           inherited Create;
2154           typ:=ait_string;
2155           len:=length(_str);
2156           getmem(str,len+1);
2157           move(_str[1],str^,len);
2158           str[len]:=#0;
2159        end;
2160 
2161 
2162     constructor tai_string.Create_pchar(_str : pchar;length : longint);
2163        begin
2164           inherited Create;
2165           typ:=ait_string;
2166           str:=_str;
2167           len:=length;
2168        end;
2169 
2170 
2171     destructor tai_string.destroy;
2172       begin
2173          if str<>nil then
2174            freemem(str);
2175          inherited Destroy;
2176       end;
2177 
2178 
2179     constructor tai_string.ppuload(t:taitype;ppufile:tcompilerppufile);
2180       begin
2181         inherited ppuload(t,ppufile);
2182         len:=ppufile.getlongint;
2183         getmem(str,len+1);
2184         ppufile.getdata(str^,len);
2185         str[len]:=#0
2186       end;
2187 
2188 
2189     procedure tai_string.ppuwrite(ppufile:tcompilerppufile);
2190       begin
2191         inherited ppuwrite(ppufile);
2192         ppufile.putlongint(len);
2193         ppufile.putdata(str^,len);
2194       end;
2195 
2196 
tai_string.getcopynull2197     function tai_string.getcopy : tlinkedlistitem;
2198       var
2199         p : tlinkedlistitem;
2200       begin
2201         p:=inherited getcopy;
2202         getmem(tai_string(p).str,len);
2203         move(str^,tai_string(p).str^,len);
2204         getcopy:=p;
2205       end;
2206 
2207 
2208 {****************************************************************************
2209                                TAI_LABEL
2210  ****************************************************************************}
2211 
2212     constructor tai_label.Create(_labsym : tasmlabel);
2213       begin
2214         inherited Create;
2215         typ:=ait_label;
2216         labsym:=_labsym;
2217         labsym.is_set:=true;
2218       end;
2219 
2220 
2221     constructor tai_label.ppuload(t:taitype;ppufile:tcompilerppufile);
2222       begin
2223         inherited ppuload(t,ppufile);
2224         labsym:=tasmlabel(ppufile.getasmsymbol);
2225         ppufile.getbyte; { was is_global flag, now unused }
2226       end;
2227 
2228 
2229     procedure tai_label.ppuwrite(ppufile:tcompilerppufile);
2230       begin
2231         inherited ppuwrite(ppufile);
2232         ppufile.putasmsymbol(labsym);
2233         ppufile.putbyte(0); { was is_global flag, now unused }
2234       end;
2235 
2236 
2237     procedure tai_label.derefimpl;
2238       begin
2239         labsym.is_set:=true;
2240       end;
2241 
2242 {****************************************************************************
2243           tai_comment  comment to be inserted in the assembler file
2244  ****************************************************************************}
2245 
2246      constructor tai_comment.Create(_str : pchar);
2247 
2248        begin
2249           inherited Create;
2250           typ:=ait_comment;
2251           str:=_str;
2252        end;
2253 
2254     destructor tai_comment.destroy;
2255 
2256       begin
2257          freemem(str);
2258          inherited Destroy;
2259       end;
2260 
2261     constructor tai_comment.ppuload(t:taitype;ppufile:tcompilerppufile);
2262       var
2263         len : longint;
2264       begin
2265         inherited ppuload(t,ppufile);
2266         len:=ppufile.getlongint;
2267         getmem(str,len+1);
2268         ppufile.getdata(str^,len);
2269         str[len]:=#0;
2270       end;
2271 
2272 
2273     procedure tai_comment.ppuwrite(ppufile:tcompilerppufile);
2274       var
2275         len : longint;
2276       begin
2277         inherited ppuwrite(ppufile);
2278         len:=strlen(str);
2279         ppufile.putlongint(len);
2280         ppufile.putdata(str^,len);
2281       end;
2282 
2283 
tai_comment.getcopynull2284     function tai_comment.getcopy : tlinkedlistitem;
2285       var
2286         p : tlinkedlistitem;
2287       begin
2288         p:=inherited getcopy;
2289         getmem(tai_comment(p).str,strlen(str)+1);
2290         move(str^,tai_comment(p).str^,strlen(str)+1);
2291         getcopy:=p;
2292       end;
2293 
2294 
2295 {****************************************************************************
2296                               TAI_STABS
2297  ****************************************************************************}
2298 
2299     constructor tai_stab.create(_stabtype:TStabType;_str : pchar);
2300       begin
2301          inherited create;
2302          typ:=ait_stab;
2303          str:=_str;
2304          stabtype:=_stabtype;
2305       end;
2306 
2307     constructor tai_stab.create_str(_stabtype:TStabType;const s:string);
2308       begin
2309          self.create(_stabtype,strpnew(s));
2310       end;
2311 
2312     constructor tai_stab.create_ansistr(_stabtype:TStabType;const s:ansistring);
2313       begin
2314          inherited create;
2315          typ:=ait_stab;
2316          stabtype:=_stabtype;
2317          getmem(str,length(s)+1);
2318          if length(s)>0 then
2319            move(s[1],str^,length(s)+1)
2320          else
2321            str^:=#0;
2322       end;
2323 
2324     destructor tai_stab.destroy;
2325       begin
2326          freemem(str);
2327          inherited destroy;
2328       end;
2329 
2330 
2331 {****************************************************************************
2332                             TAI_FORCE_LINE
2333  ****************************************************************************}
2334 
2335     constructor tai_force_line.create;
2336       begin
2337          inherited create;
2338          typ:=ait_force_line;
2339       end;
2340 
2341 
2342 {****************************************************************************
2343                               TAI_FUNCTION_NAME
2344  ****************************************************************************}
2345 
2346     constructor tai_function_name.create(const s:string);
2347       begin
2348          inherited create;
2349          typ:=ait_function_name;
2350          funcname:=stringdup(s);
2351       end;
2352 
2353     destructor tai_function_name.destroy;
2354       begin
2355          stringdispose(funcname);
2356          inherited destroy;
2357       end;
2358 
2359 
2360 {****************************************************************************
2361                               TAI_CUTOBJECT
2362  ****************************************************************************}
2363 
2364      constructor tai_cutobject.Create;
2365        begin
2366           inherited Create;
2367           typ:=ait_cutobject;
2368           place:=cut_normal;
2369        end;
2370 
2371 
2372      constructor tai_cutobject.Create_begin;
2373        begin
2374           inherited Create;
2375           typ:=ait_cutobject;
2376           place:=cut_begin;
2377        end;
2378 
2379 
2380      constructor tai_cutobject.Create_end;
2381        begin
2382           inherited Create;
2383           typ:=ait_cutobject;
2384           place:=cut_end;
2385        end;
2386 
2387 
2388     constructor tai_cutobject.ppuload(t:taitype;ppufile:tcompilerppufile);
2389       begin
2390         inherited ppuload(t,ppufile);
2391         place:=TCutPlace(ppufile.getbyte);
2392       end;
2393 
2394 
2395     procedure tai_cutobject.ppuwrite(ppufile:tcompilerppufile);
2396       begin
2397         inherited ppuwrite(ppufile);
2398         ppufile.putbyte(byte(place));
2399       end;
2400 
2401 
2402 {****************************************************************************
2403                              Tai_Marker
2404  ****************************************************************************}
2405 
2406     constructor Tai_Marker.Create(_Kind: TAsmMarker);
2407       begin
2408         Inherited Create;
2409         typ := ait_marker;
2410         Kind := _Kind;
2411       end;
2412 
2413 
2414     constructor Tai_Marker.ppuload(t:taitype;ppufile:tcompilerppufile);
2415       begin
2416         inherited ppuload(t,ppufile);
2417         kind:=TAsmMarker(ppufile.getbyte);
2418       end;
2419 
2420 
2421     procedure Tai_Marker.ppuwrite(ppufile:tcompilerppufile);
2422       begin
2423         inherited ppuwrite(ppufile);
2424         ppufile.putbyte(byte(kind));
2425       end;
2426 
2427 
2428 {*****************************************************************************
2429                                 tai_tempalloc
2430 *****************************************************************************}
2431 
2432     constructor tai_tempalloc.alloc(pos,size:longint);
2433       begin
2434         inherited Create;
2435         typ:=ait_tempalloc;
2436         allocation:=true;
2437         temppos:=pos;
2438         tempsize:=size;
2439 {$ifdef EXTDEBUG}
2440         problem:=nil;
2441 {$endif EXTDEBUG}
2442       end;
2443 
2444 
2445     destructor tai_tempalloc.destroy;
2446       begin
2447 {$ifdef EXTDEBUG}
2448         stringdispose(problem);
2449 {$endif EXTDEBUG}
2450         inherited destroy;
2451       end;
2452 
2453 
2454     constructor tai_tempalloc.dealloc(pos,size:longint);
2455       begin
2456         inherited Create;
2457         typ:=ait_tempalloc;
2458         allocation:=false;
2459         temppos:=pos;
2460         tempsize:=size;
2461 {$ifdef EXTDEBUG}
2462         problem:=nil;
2463 {$endif EXTDEBUG}
2464       end;
2465 
2466 
2467 {$ifdef EXTDEBUG}
2468     constructor tai_tempalloc.allocinfo(pos,size:longint;const st:string);
2469       begin
2470         inherited Create;
2471         typ:=ait_tempalloc;
2472         allocation:=false;
2473         temppos:=pos;
2474         tempsize:=size;
2475         problem:=stringdup(st);
2476       end;
2477 {$endif EXTDEBUG}
2478 
2479 
2480     constructor tai_tempalloc.ppuload(t:taitype;ppufile:tcompilerppufile);
2481       begin
2482         inherited ppuload(t,ppufile);
2483         temppos:=ppufile.getlongint;
2484         tempsize:=ppufile.getlongint;
2485         allocation:=ppufile.getboolean;
2486 {$ifdef EXTDEBUG}
2487         problem:=nil;
2488 {$endif EXTDEBUG}
2489       end;
2490 
2491 
2492     procedure tai_tempalloc.ppuwrite(ppufile:tcompilerppufile);
2493       begin
2494         inherited ppuwrite(ppufile);
2495         ppufile.putlongint(temppos);
2496         ppufile.putlongint(tempsize);
2497         ppufile.putboolean(allocation);
2498       end;
2499 
2500 
2501 {*****************************************************************************
2502                                  tai_regalloc
2503 *****************************************************************************}
2504 
2505     constructor tai_regalloc.alloc(r : tregister;ainstr:tai);
2506       begin
2507         inherited create;
2508         typ:=ait_regalloc;
2509         ratype:=ra_alloc;
2510         reg:=r;
2511         { ainstr must be an instruction }
2512         if assigned(ainstr) and
2513            (ainstr.typ<>ait_instruction) then
2514           internalerror(200411011);
2515         instr:=ainstr;
2516       end;
2517 
2518 
2519     constructor tai_regalloc.dealloc(r : tregister;ainstr:tai);
2520       begin
2521         inherited create;
2522         typ:=ait_regalloc;
2523         ratype:=ra_dealloc;
2524         reg:=r;
2525         { ainstr must be an instruction }
2526         if assigned(ainstr) and
2527            (ainstr.typ<>ait_instruction) then
2528           internalerror(200411012);
2529         instr:=ainstr;
2530       end;
2531 
2532 
2533     constructor tai_regalloc.sync(r : tregister);
2534       begin
2535         inherited create;
2536         typ:=ait_regalloc;
2537         ratype:=ra_sync;
2538         reg:=r;
2539       end;
2540 
2541 
2542     constructor tai_regalloc.resize(r : tregister);
2543       begin
2544         inherited create;
2545         typ:=ait_regalloc;
2546         ratype:=ra_resize;
2547         reg:=r;
2548       end;
2549 
2550 
2551     constructor tai_regalloc.markused(r : tregister);
2552       begin
2553         inherited create;
2554         typ:=ait_regalloc;
2555         ratype:=ra_markused;
2556         reg:=r;
2557       end;
2558 
2559 
2560     constructor tai_regalloc.ppuload(t:taitype;ppufile:tcompilerppufile);
2561       begin
2562         inherited ppuload(t,ppufile);
2563         ppufile.getdata(reg,sizeof(Tregister));
2564         ratype:=tregalloctype(ppufile.getbyte);
2565         keep:=ppufile.getboolean;
2566       end;
2567 
2568 
2569     procedure tai_regalloc.ppuwrite(ppufile:tcompilerppufile);
2570       begin
2571         inherited ppuwrite(ppufile);
2572         ppufile.putdata(reg,sizeof(Tregister));
2573         ppufile.putbyte(byte(ratype));
2574         ppufile.putboolean(keep);
2575       end;
2576 
2577 
2578 {*****************************************************************************
2579                                TaiInstruction
2580 *****************************************************************************}
2581 
2582     constructor tai_cpu_abstract.Create(op : tasmop);
2583 
2584       begin
2585          inherited create;
2586          typ:=ait_instruction;
2587          is_jmp:=false;
2588          opcode:=op;
2589          ops:=0;
2590       end;
2591 
2592 
2593     destructor tai_cpu_abstract.Destroy;
2594       var
2595         i : integer;
2596       begin
2597         for i:=0 to opercnt-1 do
2598           freeop(i);
2599         inherited destroy;
2600       end;
2601 
2602 
2603 { ---------------------------------------------------------------------
2604     Loading of operands.
2605   ---------------------------------------------------------------------}
2606 
2607     procedure tai_cpu_abstract.allocate_oper(opers:longint);
2608       begin
2609         while (opers>opercnt) do
2610           begin
2611             new(oper[opercnt]);
2612             fillchar(oper[opercnt]^,sizeof(toper),0);
2613             inc(opercnt);
2614           end;
2615       end;
2616 
2617 
2618     procedure tai_cpu_abstract.loadconst(opidx:longint;l:tcgint);
2619       begin
2620         allocate_oper(opidx+1);
2621         with oper[opidx]^ do
2622          begin
2623            if typ<>top_const then
2624              clearop(opidx);
2625            val:=l;
2626            typ:=top_const;
2627          end;
2628       end;
2629 
2630 
2631     procedure tai_cpu_abstract.loadsymbol(opidx:longint;s:tasmsymbol;sofs:longint);
2632       var
2633         r : treference;
2634       begin
2635         reference_reset_symbol(r,s,sofs,1,[]);
2636         r.refaddr:=addr_full;
2637         loadref(opidx,r);
2638       end;
2639 
2640 
2641     procedure tai_cpu_abstract.loadlocal(opidx:longint;s:pointer;sofs:longint;indexreg:tregister;scale:byte;getoffset,forceref:boolean);
2642       begin
2643         if not assigned(s) then
2644          internalerror(200204251);
2645         allocate_oper(opidx+1);
2646         with oper[opidx]^ do
2647          begin
2648            if typ<>top_local then
2649              begin
2650                clearop(opidx);
2651                new(localoper);
2652              end;
2653            with oper[opidx]^.localoper^ do
2654              begin
2655                localsym:=s;
2656                localsymofs:=sofs;
2657                localindexreg:=indexreg;
2658                localscale:=scale;
2659                localgetoffset:=getoffset;
2660                localforceref:=forceref;
2661 {$ifdef x86}
2662                localsegment:=NR_NO;
2663 {$endif x86}
2664              end;
2665            typ:=top_local;
2666          end;
2667       end;
2668 
2669 
2670     procedure tai_cpu_abstract.loadref(opidx:longint;const r:treference);
2671 {$ifdef x86}
2672       var
2673         si_param: ShortInt;
2674 {$endif}
2675       begin
2676         allocate_oper(opidx+1);
2677         with oper[opidx]^ do
2678           begin
2679             if typ<>top_ref then
2680               begin
2681                 clearop(opidx);
2682                 new(ref);
2683               end;
2684 
2685             ref^:=r;
2686 {$ifdef x86}
2687             { We allow this exception for x86, since overloading this would be
2688               too much of a a speed penalty}
2689             if is_x86_parameterized_string_op(opcode) then
2690               begin
2691                 si_param:=get_x86_string_op_si_param(opcode);
2692                 if (si_param<>-1) and (taicpu(self).OperandOrder=op_att) then
2693                   si_param:=x86_parameterized_string_op_param_count(opcode)-si_param-1;
2694                 if (si_param=opidx) and (ref^.segment<>NR_NO) and (ref^.segment<>NR_DS) then
2695                   segprefix:=ref^.segment;
2696               end
2697             else if (opcode=A_XLAT) and (ref^.segment<>NR_NO) and (ref^.segment<>NR_DS) then
2698               segprefix:=ref^.segment
2699             else if (ref^.segment<>NR_NO) and (ref^.segment<>get_default_segment_of_ref(ref^)) then
2700               segprefix:=ref^.segment;
2701 {$endif}
2702 {$ifndef llvm}
2703             if (cs_create_pic in current_settings.moduleswitches) and
2704               assigned(r.symbol) and
2705               not assigned(r.relsymbol) and
2706               (r.refaddr=addr_no)
2707 {$ifdef ARM}
2708               and not(r.base=NR_R15)
2709 {$endif ARM}
2710 {$ifdef aarch64}
2711               and not(r.refaddr in [addr_full,addr_gotpageoffset,addr_gotpage])
2712 {$endif aarch64}
2713               then
2714               internalerror(200502052);
2715 {$endif not llvm}
2716             typ:=top_ref;
2717             if assigned(add_reg_instruction_hook) then
2718               begin
2719                 add_reg_instruction_hook(self,ref^.base);
2720                 add_reg_instruction_hook(self,ref^.index);
2721               end;
2722             { mark symbol as used }
2723             if assigned(ref^.symbol) then
2724               ref^.symbol.increfs;
2725             if assigned(ref^.relsymbol) then
2726               ref^.relsymbol.increfs;
2727           end;
2728       end;
2729 
2730 
2731     procedure tai_cpu_abstract.loadreg(opidx:longint;r:tregister);
2732       begin
2733         allocate_oper(opidx+1);
2734         with oper[opidx]^ do
2735          begin
2736            if typ<>top_reg then
2737              clearop(opidx);
2738            reg:=r;
2739            typ:=top_reg;
2740          end;
2741         if assigned(add_reg_instruction_hook) then
2742           add_reg_instruction_hook(self,r);
2743 {$ifdef ARM}
2744         { R15 is the PC on the ARM thus moves to R15 are jumps.
2745           Due to speed considerations we don't use a virtual overridden method here.
2746           Because the pc/r15 isn't handled by the reg. allocator this should never cause
2747           problems with iregs getting r15.
2748         }
2749         is_jmp:=(opcode=A_MOV) and (opidx=0) and (r=NR_R15);
2750 {$endif ARM}
2751       end;
2752 
2753 
2754     procedure tai_cpu_abstract.loadoper(opidx:longint;o:toper);
2755 {$ifdef x86}
2756       var
2757         si_param: ShortInt;
2758 {$endif x86}
2759       begin
2760         allocate_oper(opidx+1);
2761         clearop(opidx);
2762         oper[opidx]^:=o;
2763         { copy also the reference }
2764         with oper[opidx]^ do
2765           begin
2766             case typ of
2767               top_reg:
2768                 begin
2769                   if assigned(add_reg_instruction_hook) then
2770                     add_reg_instruction_hook(self,reg);
2771                 end;
2772               top_ref:
2773                 begin
2774                   new(ref);
2775                   ref^:=o.ref^;
2776 {$ifdef x86}
2777                   { We allow this exception for x86, since overloading this would be
2778                     too much of a a speed penalty}
2779                   if is_x86_parameterized_string_op(opcode) then
2780                     begin
2781                       si_param:=get_x86_string_op_si_param(opcode);
2782                       if (si_param<>-1) and (taicpu(self).OperandOrder=op_att) then
2783                         si_param:=x86_parameterized_string_op_param_count(opcode)-si_param-1;
2784                       if (si_param=opidx) and (ref^.segment<>NR_NO) and (ref^.segment<>NR_DS) then
2785                         segprefix:=ref^.segment;
2786                     end
2787                   else if (opcode=A_XLAT) and (ref^.segment<>NR_NO) and (ref^.segment<>NR_DS) then
2788                     segprefix:=ref^.segment
2789                   else if (ref^.segment<>NR_NO) and (ref^.segment<>get_default_segment_of_ref(ref^)) then
2790                     segprefix:=ref^.segment;
2791 {$endif x86}
2792                   if assigned(add_reg_instruction_hook) then
2793                     begin
2794                       add_reg_instruction_hook(self,ref^.base);
2795                       add_reg_instruction_hook(self,ref^.index);
2796                     end;
2797                 end;
2798 {$ifdef ARM}
2799               top_shifterop:
2800                 begin
2801                   new(shifterop);
2802                   shifterop^:=o.shifterop^;
2803                   if assigned(add_reg_instruction_hook) then
2804                     add_reg_instruction_hook(self,shifterop^.rs);
2805                 end;
2806 {$endif ARM}
2807              end;
2808           end;
2809       end;
2810 
2811     procedure tai_cpu_abstract.clearop(opidx:longint);
2812       begin
2813         with oper[opidx]^ do
2814           begin
2815             case typ of
2816               top_ref:
2817                 dispose(ref);
2818               top_local:
2819                 dispose(localoper);
2820 {$ifdef ARM}
2821               top_shifterop:
2822                 dispose(shifterop);
2823               top_regset:
2824                 dispose(regset);
2825 {$endif ARM}
2826 {$ifdef jvm}
2827               top_string:
2828                 freemem(pcval);
2829               top_wstring:
2830                 donewidestring(pwstrval);
2831 {$endif jvm}
2832             end;
2833             typ:=top_none;
2834           end;
2835       end;
2836 
2837 
2838     procedure tai_cpu_abstract.freeop(opidx:longint);
2839       begin
2840         clearop(opidx);
2841         dispose(oper[opidx]);
2842       end;
2843 
2844 
2845 { ---------------------------------------------------------------------
2846     Miscellaneous methods.
2847   ---------------------------------------------------------------------}
2848 
2849     procedure tai_cpu_abstract.SetCondition(const c:TAsmCond);
2850       begin
2851          condition:=c;
2852       end;
2853 
2854 
tai_cpu_abstract.getcopynull2855     Function tai_cpu_abstract.getcopy:TLinkedListItem;
2856       var
2857         i : longint;
2858         p : tai_cpu_abstract;
2859       begin
2860         p:=tai_cpu_abstract(inherited getcopy);
2861         { make a copy of the references }
2862         p.opercnt:=0;
2863         p.allocate_oper(ops);
2864         for i:=0 to ops-1 do
2865           begin
2866             p.oper[i]^:=oper[i]^;
2867             case oper[i]^.typ of
2868               top_local :
2869                 begin
2870                   new(p.oper[i]^.localoper);
2871                   p.oper[i]^.localoper^:=oper[i]^.localoper^;
2872                 end;
2873               top_ref :
2874                 begin
2875                   new(p.oper[i]^.ref);
2876                   p.oper[i]^.ref^:=oper[i]^.ref^;
2877                 end;
2878 {$ifdef ARM}
2879               top_shifterop:
2880                 begin
2881                   new(p.oper[i]^.shifterop);
2882                   p.oper[i]^.shifterop^:=oper[i]^.shifterop^;
2883                 end;
2884 {$endif ARM}
2885             end;
2886           end;
2887         getcopy:=p;
2888       end;
2889 
2890 
tai_cpu_abstract.is_same_reg_movenull2891     function tai_cpu_abstract.is_same_reg_move(regtype: Tregistertype):boolean;
2892       begin
2893         { When the generic RA is used this needs to be overridden, we don't use
2894           virtual;abstract; to prevent a lot of warnings of unimplemented abstract methods
2895           when tai_cpu is created (PFV) }
2896         internalerror(2004040901);
2897         result:=false;
2898       end;
2899 
2900 
tai_cpu_abstract.spilling_get_operation_typenull2901     function tai_cpu_abstract.spilling_get_operation_type(opnr: longint): topertype;
2902       begin
2903         internalerror(2004040902);
2904         result:=operand_readwrite;
2905       end;
2906 
2907 
tai_cpu_abstract.spilling_get_operation_type_refnull2908     function tai_cpu_abstract.spilling_get_operation_type_ref(opnr: longint; reg: tregister): topertype;
2909       begin
2910         result := operand_read;
2911       end;
2912 
2913 
2914     constructor tai_cpu_abstract.ppuload(t:taitype;ppufile:tcompilerppufile);
2915       var
2916         i : integer;
2917       begin
2918         inherited ppuload(t,ppufile);
2919         { hopefully, we don't get problems with big/litte endian here when cross compiling :/ }
2920         ppufile.getdata(condition,sizeof(tasmcond));
2921         allocate_oper(ppufile.getbyte);
2922         for i:=0 to ops-1 do
2923           ppuloadoper(ppufile,oper[i]^);
2924         opcode:=tasmop(ppufile.getword);
2925 {$ifdef x86}
2926         ppufile.getdata(segprefix,sizeof(Tregister));
2927 {$endif x86}
2928         is_jmp:=ppufile.getboolean;
2929       end;
2930 
2931 
2932     procedure tai_cpu_abstract.ppuwrite(ppufile:tcompilerppufile);
2933       var
2934         i : integer;
2935       begin
2936         inherited ppuwrite(ppufile);
2937         ppufile.putdata(condition,sizeof(tasmcond));
2938         ppufile.putbyte(ops);
2939         for i:=0 to ops-1 do
2940           ppuwriteoper(ppufile,oper[i]^);
2941         ppufile.putword(word(opcode));
2942 {$ifdef x86}
2943         ppufile.putdata(segprefix,sizeof(Tregister));
2944 {$endif x86}
2945         ppufile.putboolean(is_jmp);
2946       end;
2947 
2948 
2949     procedure tai_cpu_abstract.buildderefimpl;
2950       var
2951         i : integer;
2952       begin
2953         for i:=0 to ops-1 do
2954           ppubuildderefimploper(oper[i]^);
2955       end;
2956 
2957 
2958     procedure tai_cpu_abstract.derefimpl;
2959       var
2960         i : integer;
2961       begin
2962         for i:=0 to ops-1 do
2963           ppuderefoper(oper[i]^);
2964       end;
2965 
2966 
2967     procedure tai_cpu_abstract.resetpass1;
2968       begin
2969       end;
2970 
2971 
2972     procedure tai_cpu_abstract.resetpass2;
2973       begin
2974       end;
2975 
2976 
tai_cpu_abstract.Pass1null2977    function tai_cpu_abstract.Pass1(objdata:TObjData):longint;
2978       begin
2979         result:=0;
2980       end;
2981 
2982 
2983     procedure tai_cpu_abstract.Pass2(objdata:TObjData);
2984       begin
2985       end;
2986 
2987 
2988     procedure tai_cpu_abstract.ppuloadoper(ppufile:tcompilerppufile;var o:toper);
2989       begin
2990         o.typ:=toptype(ppufile.getbyte);
2991         o.ot:=ppufile.getlongint;
2992         case o.typ of
2993           top_reg :
2994             ppufile.getdata(o.reg,sizeof(Tregister));
2995           top_ref :
2996             begin
2997               new(o.ref);
2998 {$ifdef x86}
2999               ppufile.getdata(o.ref^.segment,sizeof(Tregister));
3000 {$endif x86}
3001               ppufile.getdata(o.ref^.base,sizeof(Tregister));
3002               ppufile.getdata(o.ref^.index,sizeof(Tregister));
3003               ppufile.getdata(o.ref^.refaddr,sizeof(o.ref^.refaddr));
3004               o.ref^.scalefactor:=ppufile.getbyte;
3005               o.ref^.offset:=ppufile.getaint;
3006               o.ref^.symbol:=ppufile.getasmsymbol;
3007               o.ref^.relsymbol:=ppufile.getasmsymbol;
3008             end;
3009           top_const :
3010             o.val:=ppufile.getaint;
3011           top_local :
3012             begin
3013               new(o.localoper);
3014               with o.localoper^ do
3015                 begin
3016                   ppufile.getderef(localsymderef);
3017                   localsymofs:=ppufile.getaint;
3018 {$ifdef x86}
3019                   localsegment:=tregister(ppufile.getlongint);
3020 {$endif x86}
3021                   localindexreg:=tregister(ppufile.getlongint);
3022                   localscale:=ppufile.getbyte;
3023                   localgetoffset:=(ppufile.getbyte<>0);
3024                 end;
3025             end;
3026           else
3027             internalerror(2007010210);
3028         end;
3029       end;
3030 
3031 
3032     procedure tai_cpu_abstract.ppuwriteoper(ppufile:tcompilerppufile;const o:toper);
3033       begin
3034         ppufile.putbyte(byte(o.typ));
3035         ppufile.putlongint(o.ot);
3036         case o.typ of
3037           top_reg :
3038             ppufile.putdata(o.reg,sizeof(Tregister));
3039           top_ref :
3040             begin
3041 {$ifdef x86}
3042               ppufile.putdata(o.ref^.segment,sizeof(Tregister));
3043 {$endif x86}
3044               ppufile.putdata(o.ref^.base,sizeof(Tregister));
3045               ppufile.putdata(o.ref^.index,sizeof(Tregister));
3046               ppufile.putdata(o.ref^.refaddr,sizeof(o.ref^.refaddr));
3047               ppufile.putbyte(o.ref^.scalefactor);
3048               ppufile.putaint(o.ref^.offset);
3049               ppufile.putasmsymbol(o.ref^.symbol);
3050               ppufile.putasmsymbol(o.ref^.relsymbol);
3051             end;
3052           top_const :
3053             ppufile.putaint(o.val);
3054           top_local :
3055             begin
3056               with o.localoper^ do
3057                 begin
3058                   ppufile.putderef(localsymderef);
3059                   ppufile.putaint(localsymofs);
3060 {$ifdef x86}
3061                   ppufile.putlongint(longint(localsegment));
3062 {$endif x86}
3063                   ppufile.putlongint(longint(localindexreg));
3064                   ppufile.putbyte(localscale);
3065                   ppufile.putbyte(byte(localgetoffset));
3066                 end;
3067             end;
3068           else
3069             internalerror(2007010211);
3070         end;
3071       end;
3072 
3073 {****************************************************************************
3074                               tai_align_abstract
3075  ****************************************************************************}
3076 
3077      constructor tai_align_abstract.Create(b: byte);
3078        begin
3079           inherited Create;
3080           typ:=ait_align;
3081 {$ifdef EXTDEBUG}
3082           if upper(classname)='TAI_ALIGN_ABSTRACT' then
3083             internalerror(200709191);
3084 {$endif EXTDEBUG}
3085           if b in [1,2,4,8,16,32,64] then
3086             aligntype := b
3087           else
3088             aligntype := 1;
3089           fillsize:=0;
3090           fillop:=0;
3091           use_op:=false;
3092        end;
3093 
3094 
3095      constructor tai_align_abstract.Create_op(b: byte; _op: byte);
3096        begin
3097           inherited Create;
3098           typ:=ait_align;
3099           if b in [1,2,4,8,16,32] then
3100             aligntype := b
3101           else
3102             aligntype := 1;
3103           fillsize:=0;
3104           fillop:=_op;
3105           use_op:=true;
3106        end;
3107 
3108 
3109      constructor tai_align_abstract.Create_zeros(b: byte);
3110        begin
3111           inherited Create;
3112           typ:=ait_align;
3113           if b in [1,2,4,8,16,32] then
3114             aligntype := b
3115           else
3116             aligntype := 1;
3117          use_op:=true;
3118          fillsize:=0;
3119          fillop:=0;
3120        end;
3121 
3122 
tai_align_abstract.calculatefillbufnull3123      function tai_align_abstract.calculatefillbuf(var buf : tfillbuffer;executable : boolean):pchar;
3124        begin
3125          if fillsize>sizeof(buf) then
3126            internalerror(200404293);
3127          fillchar(buf,high(buf),fillop);
3128          calculatefillbuf:=pchar(@buf);
3129        end;
3130 
3131 
3132     constructor tai_align_abstract.ppuload(t:taitype;ppufile:tcompilerppufile);
3133       begin
3134         inherited ppuload(t,ppufile);
3135         aligntype:=ppufile.getbyte;
3136         fillsize:=0;
3137         fillop:=ppufile.getbyte;
3138         use_op:=ppufile.getboolean;
3139       end;
3140 
3141 
3142     procedure tai_align_abstract.ppuwrite(ppufile:tcompilerppufile);
3143       begin
3144         inherited ppuwrite(ppufile);
3145         ppufile.putbyte(aligntype);
3146         ppufile.putbyte(fillop);
3147         ppufile.putboolean(use_op);
3148       end;
3149 
3150 
3151 {****************************************************************************
3152                               tai_seh_directive
3153  ****************************************************************************}
3154 
3155     const
3156       datatypemap: array[TAsmSehDirective] of TSehDirectiveDatatype=(
3157         sd_string,     { proc }
3158         sd_none,       { endproc }
3159         sd_none,       { endprologue }
3160         sd_string,     { handler }
3161         sd_none,       { handlerdata }
3162         sd_none,sd_none,sd_none,  { eh, 32, no32 }
3163         sd_regoffset,  { setframe }
3164         sd_offset,     { stackalloc }
3165         sd_reg,        { pushreg }
3166         sd_regoffset,  { savereg }
3167         sd_regoffset,  { savexmm }
3168         sd_none,       { pushframe }
3169         sd_reg,        { pushnv }
3170         sd_none        { savenv }
3171       );
3172 
3173     constructor tai_seh_directive.create(_kind:TAsmSehDirective);
3174       begin
3175         inherited Create;
3176         typ:=ait_seh_directive;
3177         kind:=_kind;
3178         data.typ:=datatypemap[_kind];
3179       end;
3180 
3181     constructor tai_seh_directive.create_name(_kind:TAsmSehDirective;const _name:string);
3182       begin
3183         create(_kind);
3184         data.name:=stringdup(_name);
3185       end;
3186 
3187     constructor tai_seh_directive.create_reg(_kind:TAsmSehDirective;r:TRegister);
3188       begin
3189         create(_kind);
3190         data.reg:=r;
3191       end;
3192 
3193     constructor tai_seh_directive.create_offset(_kind:TAsmSehDirective;ofs:dword);
3194       begin
3195         create(_kind);
3196         data.offset:=ofs;
3197       end;
3198 
3199     constructor tai_seh_directive.create_reg_offset(_kind:TAsmSehDirective;
3200       r:TRegister;ofs:dword);
3201       begin
3202         create(_kind);
3203         data.offset:=ofs;
3204         data.reg:=r;
3205       end;
3206 
3207     constructor tai_seh_directive.ppuload(t:taitype;ppufile:tcompilerppufile);
3208       begin
3209         inherited ppuload(t, ppufile);
3210         kind:=TAsmSehDirective(ppufile.getbyte);
3211         data.typ:=datatypemap[kind];
3212         case data.typ of
3213           sd_none: ;
3214           sd_string:
3215             begin
3216               data.name:=ppufile.getpshortstring;
3217               data.flags:=ppufile.getbyte;
3218             end;
3219 
3220           sd_reg,sd_offset,sd_regoffset:
3221             begin
3222               ppufile.getdata(data.reg,sizeof(TRegister));
3223               data.offset:=ppufile.getdword;
3224             end;
3225         else
3226           InternalError(2011091201);
3227         end;
3228       end;
3229 
3230     destructor tai_seh_directive.destroy;
3231       begin
3232         if data.typ=sd_string then
3233           stringdispose(data.name);
3234         inherited destroy;
3235       end;
3236 
3237     procedure tai_seh_directive.ppuwrite(ppufile:tcompilerppufile);
3238       begin
3239         inherited ppuwrite(ppufile);
3240         ppufile.putbyte(ord(kind));
3241         case data.typ of
3242           sd_none: ;
3243           sd_string:
3244             begin
3245               ppufile.putstring(data.name^);
3246               ppufile.putbyte(data.flags);
3247             end;
3248 
3249           sd_reg,sd_offset,sd_regoffset:
3250             begin
3251               ppufile.putdata(data.reg,sizeof(TRegister));
3252               ppufile.putdword(data.offset);
3253             end;
3254         else
3255           InternalError(2011091202);
3256         end;
3257       end;
3258 
3259     procedure tai_seh_directive.generate_code(objdata:TObjData);
3260       begin
3261       end;
3262 
3263 {$ifdef JVM}
3264 
3265 {****************************************************************************
3266                               tai_jvar
3267  ****************************************************************************}
3268 
3269     constructor tai_jvar.Create(_stackslot: longint; const _desc: shortstring; _startlab, _stoplab: TAsmSymbol);
3270       begin
3271         Inherited create;
3272         typ:=ait_jvar;
3273         stackslot:=_stackslot;
3274         desc:=stringdup(_desc);
3275         startlab:=_startlab;
3276         stoplab:=_stoplab;
3277       end;
3278 
3279 
3280     constructor tai_jvar.ppuload(t: taitype; ppufile: tcompilerppufile);
3281       begin
3282         inherited ppuload(t, ppufile);
3283         stackslot:=ppufile.getlongint;
3284         desc:=ppufile.getpshortstring;
3285         startlab:=ppufile.getasmsymbol;
3286         stoplab:=ppufile.getasmsymbol;
3287       end;
3288 
3289 
3290     procedure tai_jvar.ppuwrite(ppufile: tcompilerppufile);
3291       begin
3292         inherited ppuwrite(ppufile);
3293         ppufile.putlongint(stackslot);
3294         ppufile.putstring(desc^);
3295         ppufile.putasmsymbol(startlab);
3296         ppufile.putasmsymbol(stoplab);
3297       end;
3298 
3299 
3300     destructor tai_jvar.destroy;
3301       begin
3302         stringdispose(desc);
3303         inherited destroy;
3304       end;
3305 
3306 
3307 {****************************************************************************
3308                               tai_jcatch
3309  ****************************************************************************}
3310 
3311     constructor tai_jcatch.Create(const _name: shortstring; _startlab, _stoplab, _handlerlab: TAsmSymbol);
3312       begin
3313         Inherited create;
3314         typ:=ait_jcatch;
3315         name:=stringdup(_name);
3316         startlab:=_startlab;
3317         startlab.increfs;
3318         stoplab:=_stoplab;
3319         stoplab.increfs;
3320         handlerlab:=_handlerlab;
3321         handlerlab.increfs;
3322       end;
3323 
3324 
3325     destructor tai_jcatch.destroy;
3326       begin
3327         stringdispose(name);
3328         inherited destroy;
3329       end;
3330 
3331 
3332     constructor tai_jcatch.ppuload(t: taitype; ppufile: tcompilerppufile);
3333       begin
3334         inherited ppuload(t, ppufile);
3335         name:=ppufile.getpshortstring;
3336         startlab:=ppufile.getasmsymbol;
3337         startlab.increfs;
3338         stoplab:=ppufile.getasmsymbol;
3339         stoplab.increfs;
3340         handlerlab:=ppufile.getasmsymbol;
3341         handlerlab.increfs;
3342       end;
3343 
3344 
3345     procedure tai_jcatch.ppuwrite(ppufile: tcompilerppufile);
3346       begin
3347         inherited ppuwrite(ppufile);
3348         ppufile.putstring(name^);
3349         ppufile.putasmsymbol(startlab);
3350         ppufile.putasmsymbol(stoplab);
3351         ppufile.putasmsymbol(handlerlab);
3352       end;
3353 
3354 {$endif JVM}
3355 
3356 begin
3357 {$push}{$warnings off}
3358   { taitype should fit into a 4 byte set for speed reasons }
3359   if ord(high(taitype))>31 then
3360     internalerror(201108181);
3361 {$pop}
3362 end.
3363