1 {
2     Copyright (c) 1998-2002 by Carl Eric Codere and Peter Vreman
3 
4     Handles the common x86 assembler reader routines
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 {
23   Contains the common x86 (i386 and x86-64) assembler reader routines.
24 }
25 unit rax86;
26 
27 {$i fpcdefs.inc}
28 
29 interface
30 
31 uses
32   aasmbase,aasmtai,aasmdata,aasmcpu,
33   cpubase,rautils,cclasses;
34 
35 { Parser helpers }
is_prefixnull36 function is_prefix(t:tasmop):boolean;
is_overridenull37 function is_override(t:tasmop):boolean;
CheckPrefixnull38 Function CheckPrefix(prefixop,op:tasmop): Boolean;
CheckOverridenull39 Function CheckOverride(overrideop,op:tasmop): Boolean;
40 Procedure FWaitWarning;
41 
42 type
43   Tx86Operand=class(TOperand)
44     opsize  : topsize;
45     Procedure SetSize(_size:longint;force:boolean);override;
46     Procedure SetCorrectSize(opcode:tasmop);override;
CheckOperandnull47     Function CheckOperand: boolean; override;
48     { handles the @Code symbol }
49     Procedure SetupCode;
50     { handles the @Data symbol }
51     Procedure SetupData;
52   end;
53 
54   { Operands are always in AT&T order.
55     Intel reader attaches them right-to-left, then shifts to start with 1 }
56   Tx86Instruction=class(TInstruction)
57     opsize  : topsize;
58     constructor Create(optype : tcoperand);override;
59     { Operand sizes }
60     procedure AddReferenceSizes; virtual;
61     procedure SetInstructionOpsize;
62     procedure CheckOperandSizes;
63     procedure CheckNonCommutativeOpcodes;
64     { Additional actions required by specific reader }
65     procedure FixupOpcode;virtual;
66     { opcode adding }
ConcatInstructionnull67     function ConcatInstruction(p : TAsmList) : tai;override;
68   end;
69 
70 const
71   AsmPrefixes = 8{$ifdef i8086}+2{$endif i8086};
72   AsmPrefix : array[0..AsmPrefixes-1] of TasmOP =(
73     A_LOCK,A_REP,A_REPE,A_REPNE,A_REPNZ,A_REPZ,A_XACQUIRE,A_XRELEASE{$ifdef i8086},A_REPC,A_REPNC{$endif i8086}
74   );
75 
76   AsmOverrides = 6;
77   AsmOverride : array[0..AsmOverrides-1] of TasmOP =(
78     A_SEGCS,A_SEGES,A_SEGDS,A_SEGFS,A_SEGGS,A_SEGSS
79   );
80 
81   CondAsmOps=3;
82   CondAsmOp:array[0..CondAsmOps-1] of TasmOp=(
83     A_CMOVcc, A_Jcc, A_SETcc
84   );
85   CondAsmOpStr:array[0..CondAsmOps-1] of string[4]=(
86     'CMOV','J','SET'
87   );
88 
89 implementation
90 
91 uses
92   globtype,globals,systems,verbose,
93   procinfo,
94   cgbase,cgutils,
95   itcpugas,cgx86, cutils;
96 
97 
98 {*****************************************************************************
99                               Parser Helpers
100 *****************************************************************************}
101 
is_prefixnull102 function is_prefix(t:tasmop):boolean;
103 var
104   i : longint;
105 Begin
106   is_prefix:=false;
107   for i:=1 to AsmPrefixes do
108    if t=AsmPrefix[i-1] then
109     begin
110       is_prefix:=true;
111       exit;
112     end;
113 end;
114 
115 
is_overridenull116 function is_override(t:tasmop):boolean;
117 var
118   i : longint;
119 Begin
120   is_override:=false;
121   for i:=1 to AsmOverrides do
122    if t=AsmOverride[i-1] then
123     begin
124       is_override:=true;
125       exit;
126     end;
127 end;
128 
129 
CheckPrefixnull130 Function CheckPrefix(prefixop,op:tasmop): Boolean;
131 { Checks if the prefix is valid with the following opcode }
132 { return false if not, otherwise true                          }
133 Begin
134   CheckPrefix := TRUE;
135 (*  Case prefix of
136     A_REP,A_REPNE,A_REPE:
137       Case opcode Of
138         A_SCASB,A_SCASW,A_SCASD,
139         A_INS,A_OUTS,A_MOVS,A_CMPS,A_LODS,A_STOS:;
140         Else
141           Begin
142             CheckPrefix := FALSE;
143             exit;
144           end;
145       end; { case }
146     A_LOCK:
147       Case opcode Of
148         A_BT,A_BTS,A_BTR,A_BTC,A_XCHG,A_ADD,A_OR,A_ADC,A_SBB,A_AND,A_SUB,
149         A_XOR,A_NOT,A_NEG,A_INC,A_DEC:;
150         Else
151           Begin
152             CheckPrefix := FALSE;
153             Exit;
154           end;
155       end; { case }
156     A_NONE: exit; { no prefix here }
157     else
158       CheckPrefix := FALSE;
159    end; { end case } *)
160 end;
161 
162 
CheckOverridenull163 Function CheckOverride(overrideop,op:tasmop): Boolean;
164 { Check if the override is valid, and if so then }
165 { update the instr variable accordingly.         }
166 Begin
167   CheckOverride := true;
168 {     Case instr.getinstruction of
169     A_MOVS,A_XLAT,A_CMPS:
170       Begin
171         CheckOverride := TRUE;
172         Message(assem_e_segment_override_not_supported);
173       end
174   end }
175 end;
176 
177 
178 Procedure FWaitWarning;
179 begin
180   if (target_info.system=system_i386_GO32V2) and (cs_fp_emulation in current_settings.moduleswitches) then
181    Message(asmr_w_fwait_emu_prob);
182 end;
183 
184 {*****************************************************************************
185                               TX86Operand
186 *****************************************************************************}
187 
188 Procedure Tx86Operand.SetSize(_size:longint;force:boolean);
189 begin
190   inherited SetSize(_size,force);
191   { OS_64 will be set to S_L and be fixed later
192     in SetCorrectSize }
193 
194   // multimedia register
195   case _size of
196     16: size := OS_M128;
197     32: size := OS_M256;
198   end;
199 
200 {$ifdef i8086}
201   { allows e.g. using 32-bit registers in i8086 inline asm }
202   if size in [OS_32,OS_S32] then
203     opsize:=S_L
204   else
205 {$endif i8086}
206     opsize:=TCGSize2Opsize[size];
207 end;
208 
209 
210 Procedure Tx86Operand.SetCorrectSize(opcode:tasmop);
211 begin
212   if gas_needsuffix[opcode]=attsufFPU then
213     begin
214      case size of
215        OS_32 : opsize:=S_FS;
216        OS_64 : opsize:=S_FL;
217      end;
218     end
219   else if gas_needsuffix[opcode]=attsufFPUint then
220     begin
221       case size of
222         OS_16 : opsize:=S_IS;
223         OS_32 : opsize:=S_IL;
224         OS_64 : opsize:=S_IQ;
225       end;
226     end
227   else if gas_needsuffix[opcode]=AttSufMM then
228   begin
229     if (opr.typ=OPR_Reference) then
230     begin
231       case size of
232         OS_32 : size := OS_M32;
233         OS_64 : size := OS_M64;
234       end;
235     end;
236   end
237   else
238     begin
239       if size=OS_64 then
240         opsize:=S_Q;
241     end;
242 end;
243 
Tx86Operand.CheckOperandnull244 Function Tx86Operand.CheckOperand: boolean;
245 
246 begin
247   result:=true;
248   if (opr.typ=OPR_Reference) then
249     begin
250       if not hasvar then
251         begin
252           if (getsupreg(opr.ref.base)=RS_EBP) and (opr.ref.offset>0) then
253             begin
254               if current_procinfo.procdef.proccalloption=pocall_register then
255                 message(asmr_w_no_direct_ebp_for_parameter)
256               else
257                 message(asmr_w_direct_ebp_for_parameter_regcall);
258             end
259           else if (getsupreg(opr.ref.base)=RS_EBP) and (opr.ref.offset<0) then
260             message(asmr_w_direct_ebp_neg_offset)
261           else if (getsupreg(opr.ref.base)=RS_ESP) and (opr.ref.offset<0) then
262             message(asmr_w_direct_esp_neg_offset);
263         end;
264       if (cs_create_pic in current_settings.moduleswitches) and
265          assigned(opr.ref.symbol) and
266          not assigned(opr.ref.relsymbol) then
267         begin
268           if not(opr.ref.refaddr in [addr_pic,addr_pic_no_got]) then
269             begin
270               if (opr.ref.symbol.name <> '_GLOBAL_OFFSET_TABLE_') then
271                 begin
272                   message(asmr_e_need_pic_ref);
273                   result:=false;
274                 end
275               else
276                 opr.ref.refaddr:=addr_pic;
277             end
278           else
279             begin
280 {$ifdef x86_64}
281               { should probably be extended to i386, but there the situation
282                 is more complex and ELF-style PIC still need to be
283                 tested/debugged }
284               if (opr.ref.symbol.bind in [AB_LOCAL,AB_PRIVATE_EXTERN]) and
285                  (opr.ref.refaddr=addr_pic) then
286                 message(asmr_w_useless_got_for_local)
287               else if (opr.ref.symbol.bind in [AB_GLOBAL,AB_EXTERNAL,AB_COMMON,AB_WEAK_EXTERNAL]) and
288                  (opr.ref.refaddr=addr_pic_no_got) then
289                 message(asmr_w_global_access_without_got);
290 {$endif x86_64}
291             end;
292         end;
293     end;
294 end;
295 
296 
297 procedure Tx86Operand.SetupCode;
298 begin
299 {$ifdef i8086}
300   opr.typ:=OPR_SYMBOL;
301   opr.symofs:=0;
302   opr.symbol:=current_asmdata.RefAsmSymbol(current_procinfo.procdef.mangledname,AT_FUNCTION);
opr.symsegnull303   opr.symseg:=true;
304   opr.sym_farproc_entry:=false;
305 {$else i8086}
306   Message(asmr_w_CODE_and_DATA_not_supported);
307 {$endif i8086}
308 end;
309 
310 
311 procedure Tx86Operand.SetupData;
312 begin
313 {$ifdef i8086}
314   InitRef;
315   if current_settings.x86memorymodel=mm_huge then
316     opr.ref.refaddr:=addr_fardataseg
317   else
318     opr.ref.refaddr:=addr_dgroup;
319 {$else i8086}
320   Message(asmr_w_CODE_and_DATA_not_supported);
321 {$endif i8086}
322 end;
323 
324 
325 {*****************************************************************************
326                               T386Instruction
327 *****************************************************************************}
328 
329 constructor Tx86Instruction.Create(optype : tcoperand);
330 begin
331   inherited Create(optype);
332   Opsize:=S_NO;
333 end;
334 
335 procedure Tx86Instruction.AddReferenceSizes;
336 { this will add the sizes for references like [esi] which do not
337   have the size set yet, it will take only the size if the other
338   operand is a register }
339 var
340   operand2,i,j : longint;
341   s : tasmsymbol;
342   so : aint;
343   ExistsMemRefNoSize: boolean;
344   ExistsMemRef: boolean;
345   ExistsConstNoSize: boolean;
346   ExistsLocalSymSize: boolean;
347   memrefsize: integer;
348   memopsize: integer;
349   memoffset: asizeint;
350 begin
351   ExistsMemRefNoSize := false;
352   ExistsMemRef       := false;
353   ExistsConstNoSize  := false;
354   ExistsLocalSymSize := false;
355 
356   // EXIST A MEMORY- OR CONSTANT-OPERAND WITHOUT SIZE ?
357   for i := 1 to ops do
358   begin
359     if operands[i].Opr.Typ in [OPR_REFERENCE, OPR_LOCAL] then
360     begin
361       ExistsMemRef := true;
362 
363       if (tx86operand(operands[i]).opsize = S_NO) then
364       begin
365         ExistsMemRefNoSize := true;
366 
367         case operands[i].opr.Typ of
368               OPR_LOCAL: ExistsLocalSymSize := tx86operand(operands[i]).opr.localsym.getsize > 0;
369           OPR_REFERENCE: ExistsLocalSymSize := true;
370         end;
371 
372       end;
373     end
374     else if operands[i].Opr.Typ in [OPR_CONSTANT] then
375     begin
376       ExistsConstNoSize := tx86operand(operands[i]).opsize = S_NO;
377     end;
378   end;
379 
380   // ONLY SUPPORTED OPCODES WITH SSE- OR AVX-REGISTERS
381   if (ExistsMemRef) and
382      (MemRefInfo(opcode).ExistsSSEAVX) then
383   begin
384     // 1. WE HAVE AN SSE- OR AVX-OPCODE WITH MEMORY OPERAND
385     if (not(ExistsMemRefNoSize)) or
386        (ExistsLocalSymSize) then
387     begin
388       // 2. WE KNOWN THE MEMORYSIZE OF THE MEMORY-OPERAND OR WE CAN
389       //    CALC THE MEMORYSIZE
390 
391       // 3. CALC THE SIZE OF THE MEMORYOPERAND BY OPCODE-DEFINITION
392       // 4. COMPARE THE SIZE FROM OPCODE-DEFINITION AND THE REAL MEMORY-OPERAND-SIZE
393 
394       // - validate memory-reference-size
395       for i := 1 to ops do
396       begin
397         if (operands[i].Opr.Typ in [OPR_REFERENCE, OPR_LOCAL]) then
398         begin
399           memrefsize := -1;
400 
401           case MemRefInfo(opcode).MemRefSize of
402               msiMem8: memrefsize := 8;
403              msiMem16: memrefsize := 16;
404              msiMem32: memrefsize := 32;
405              msiMem64: memrefsize := 64;
406             msiMem128: memrefsize := 128;
407             msiMem256: memrefsize := 256;
408             msiMemRegSize
409                      : for j := 1 to ops do
410                        begin
411                          if operands[j].Opr.Typ = OPR_REGISTER then
412                          begin
413                            if (tx86operand(operands[j]).opsize <> S_NO) and
414                               (tx86operand(operands[j]).size <> OS_NO) then
415                            begin
416                              case tx86operand(operands[j]).opsize of
417                                S_B   : memrefsize := 8;
418                                S_W   : memrefsize := 16;
419                                S_L   : memrefsize := 32;
420                                S_Q   : memrefsize := 64;
421                                S_XMM : memrefsize := 128;
422                                S_YMM : memrefsize := 256;
423                                   else Internalerror(777200);
424                              end;
425                              break;
426                            end;
427                          end;
428                        end;
429           end;
430 
431           if memrefsize > -1 then
432           begin
433             // CALC REAL-MEMORY-OPERAND-SIZE AND A POSSIBLE OFFSET
434 
435             // OFFSET:
436             // e.g. PAND  XMM0, [RAX + 16] =>> OFFSET = 16 BYTES
437             //      PAND  XMM0, [RAX + a.b + 10] =>> OFFSET = 10 BYTES   (a = record-variable)
438 
439             memopsize := 0;
440             case operands[i].opr.typ of
441                   OPR_LOCAL: memopsize := operands[i].opr.localvarsize * 8;
442               OPR_REFERENCE:
443                   if operands[i].opr.ref.refaddr = addr_pic then
444                     memopsize := sizeof(pint) * 8
445                   else
446                     memopsize := operands[i].opr.varsize * 8;
447             end;
448 
449             if memopsize = 0 then memopsize := topsize2memsize[tx86operand(operands[i]).opsize];
450 
451             if (memopsize > 0) and
452                (memrefsize > 0) then
453             begin
454               memoffset := 0;
455 
456               case operands[i].opr.typ of
457                 OPR_LOCAL:
458                    memoffset := operands[i].opr.localconstoffset;
459                 OPR_REFERENCE:
460                    memoffset := operands[i].opr.constoffset;
461               end;
462 
463               if memoffset < 0 then
464               begin
465                 Message2(asmr_w_check_mem_operand_negative_offset,
466                          std_op2str[opcode],
467                          ToStr(memoffset));
468               end
469               else if (memopsize < (memrefsize + memoffset * 8)) then
470               begin
471                 if memoffset = 0 then
472                 begin
473                   Message3(asmr_w_check_mem_operand_size3,
474                            std_op2str[opcode],
475                            ToStr(memopsize),
476                            ToStr(memrefsize)
477                            );
478                 end
479                 else
480                 begin
481                   Message4(asmr_w_check_mem_operand_size_offset,
482                            std_op2str[opcode],
483                            ToStr(memopsize),
484                            ToStr(memrefsize),
485                            ToStr(memoffset)
486                            );
487                 end;
488               end;
489             end;
490           end;
491 
492 
493         end;
494       end;
495     end;
496   end;
497 
498   if (ExistsMemRefNoSize or ExistsConstNoSize) and
499      (MemRefInfo(opcode).ExistsSSEAVX) then
500   begin
501     for i := 1 to ops do
502     begin
503       if (tx86operand(operands[i]).opsize = S_NO) then
504       begin
505         case operands[i].Opr.Typ of
506           OPR_REFERENCE:
507                 case MemRefInfo(opcode).MemRefSize of
508                     msiMem8:
509                             begin
510                               tx86operand(operands[i]).opsize := S_B;
511                               tx86operand(operands[i]).size   := OS_8;
512                             end;
513                     msiMultiple8:
514                             begin
515                               tx86operand(operands[i]).opsize := S_B;
516                               tx86operand(operands[i]).size   := OS_8;
517 
518                               Message2(asmr_w_check_mem_operand_automap_multiple_size, std_op2str[opcode], '"8 bit memory operand"');
519                             end;
520                     msiMem16:
521                             begin
522                               tx86operand(operands[i]).opsize := S_W;
523                               tx86operand(operands[i]).size   := OS_16;
524                             end;
525                     msiMultiple16:
526                              begin
527                                tx86operand(operands[i]).opsize := S_W;
528                                tx86operand(operands[i]).size   := OS_16;
529 
530                                Message2(asmr_w_check_mem_operand_automap_multiple_size, std_op2str[opcode], '"16 bit memory operand"');
531                              end;
532                     msiMem32:
533                              begin
534                                tx86operand(operands[i]).opsize := S_L;
535                                tx86operand(operands[i]).size   := OS_32;
536                              end;
537                     msiMultiple32:
538                              begin
539                                tx86operand(operands[i]).opsize := S_L;
540                                tx86operand(operands[i]).size   := OS_32;
541 
542                                Message2(asmr_w_check_mem_operand_automap_multiple_size, std_op2str[opcode], '"32 bit memory operand"');
543                              end;
544                     msiMem64:
545                              begin
546                                tx86operand(operands[i]).opsize := S_Q;
547                                tx86operand(operands[i]).size   := OS_M64;
548                              end;
549                     msiMultiple64:
550                              begin
551                                tx86operand(operands[i]).opsize := S_Q;
552                                tx86operand(operands[i]).size   := OS_M64;
553 
554                                Message2(asmr_w_check_mem_operand_automap_multiple_size, std_op2str[opcode], '"64 bit memory operand"');
555                              end;
556                     msiMem128:
557                              begin
558                                tx86operand(operands[i]).opsize := S_XMM;
559                                tx86operand(operands[i]).size   := OS_M128;
560                              end;
561                     msiMultiple128:
562                              begin
563                                tx86operand(operands[i]).opsize := S_XMM;
564                                tx86operand(operands[i]).size   := OS_M128;
565 
566                                Message2(asmr_w_check_mem_operand_automap_multiple_size, std_op2str[opcode], '"128 bit memory operand"');
567                              end;
568                     msiMem256:
569                              begin
570                                tx86operand(operands[i]).opsize := S_YMM;
571                                tx86operand(operands[i]).size   := OS_M256;
572                                opsize := S_YMM;
573                              end;
574                     msiMultiple256:
575                              begin
576                                tx86operand(operands[i]).opsize := S_YMM;
577                                tx86operand(operands[i]).size   := OS_M256;
578                                opsize := S_YMM;
579 
580                                Message2(asmr_w_check_mem_operand_automap_multiple_size, std_op2str[opcode], '"256 bit memory operand"');
581                              end;
582                   msiMemRegSize:
583                              begin
584                                // mem-ref-size = register size
585                                for j := 1 to ops do
586                                begin
587                                  if operands[j].Opr.Typ = OPR_REGISTER then
588                                  begin
589                                    if (tx86operand(operands[j]).opsize <> S_NO) and
590                                       (tx86operand(operands[j]).size <> OS_NO) then
591                                    begin
592                                      tx86operand(operands[i]).opsize := tx86operand(operands[j]).opsize;
593                                      tx86operand(operands[i]).size   := tx86operand(operands[j]).size;
594                                      break;
595                                    end
596                                    else Message(asmr_e_unable_to_determine_reference_size);
597                                  end;
598                                end;
599                              end;
600                     msiMemRegx16y32:
601                       begin
602                         for j := 1 to ops do
603                         begin
604                           if operands[j].Opr.Typ = OPR_REGISTER then
605                           begin
606                             case getsubreg(operands[j].opr.reg) of
607                               R_SUBMMX: begin
608                                           tx86operand(operands[i]).opsize := S_L;
609                                           tx86operand(operands[i]).size   := OS_M16;
610                                           break;
611                                         end;
612                               R_SUBMMY: begin
613                                           tx86operand(operands[i]).opsize := S_Q;
614                                           tx86operand(operands[i]).size   := OS_M32;
615                                           break;
616                                         end;
617                                    else Message(asmr_e_unable_to_determine_reference_size);
618                             end;
619                           end;
620                         end;
621                       end;
622 
623                     msiMemRegx32y64:
624                       begin
625                         for j := 1 to ops do
626                         begin
627                           if operands[j].Opr.Typ = OPR_REGISTER then
628                           begin
629                             case getsubreg(operands[j].opr.reg) of
630                               R_SUBMMX: begin
631                                           tx86operand(operands[i]).opsize := S_L;
632                                           tx86operand(operands[i]).size   := OS_M32;
633                                           break;
634                                         end;
635                               R_SUBMMY: begin
636                                           tx86operand(operands[i]).opsize := S_Q;
637                                           tx86operand(operands[i]).size   := OS_M64;
638                                           break;
639                                         end;
640                                    else Message(asmr_e_unable_to_determine_reference_size);
641                             end;
642                           end;
643                         end;
644                       end;
645                    msiMemRegx64y128:
646                              begin
647                                for j := 1 to ops do
648                                begin
649                                  if operands[j].Opr.Typ = OPR_REGISTER then
650                                  begin
651                                    case getsubreg(operands[j].opr.reg) of
652                                      R_SUBMMX: begin
653                                                  tx86operand(operands[i]).opsize := S_Q;
654                                                  tx86operand(operands[i]).size   := OS_M64;
655                                                  break;
656                                                end;
657                                      R_SUBMMY: begin
658                                                  tx86operand(operands[i]).opsize := S_XMM;
659                                                  tx86operand(operands[i]).size   := OS_M128;
660                                                  break;
661                                                end;
662                                           else Message(asmr_e_unable_to_determine_reference_size);
663                                    end;
664                                  end;
665                                end;
666                              end;
667                    msiMemRegx64y256:
668                              begin
669                                for j := 1 to ops do
670                                begin
671                                  if operands[j].Opr.Typ = OPR_REGISTER then
672                                  begin
673                                    case getsubreg(operands[j].opr.reg) of
674                                      R_SUBMMX: begin
675                                                  tx86operand(operands[i]).opsize := S_Q;
676                                                  tx86operand(operands[i]).size   := OS_M64;
677                                                  break;
678                                                end;
679                                      R_SUBMMY: begin
680                                                  tx86operand(operands[i]).opsize := S_YMM;
681                                                  tx86operand(operands[i]).size   := OS_M256;
682                                                  break;
683                                                end;
684                                           else Message(asmr_e_unable_to_determine_reference_size);
685                                    end;
686                                  end;
687                                end;
688                              end;
689                    msiNoSize: ; //  all memory-sizes are ok
690                    msiMultiple: Message(asmr_e_unable_to_determine_reference_size); // TODO individual message
691                 end;
692           OPR_CONSTANT:
693                 case MemRefInfo(opcode).ConstSize of
694                    csiMem8: begin
695                               tx86operand(operands[i]).opsize := S_B;
696                               tx86operand(operands[i]).size   := OS_8;
697                             end;
698                   csiMem16: begin
699                               tx86operand(operands[i]).opsize := S_W;
700                               tx86operand(operands[i]).size   := OS_16;
701                             end;
702                   csiMem32: begin
703                               tx86operand(operands[i]).opsize := S_L;
704                               tx86operand(operands[i]).size   := OS_32;
705                             end;
706                 end;
707         end;
708       end;
709     end;
710   end;
711 
712 
713   for i:=1 to ops do
714     begin
715       operands[i].SetCorrectSize(opcode);
716       if tx86operand(operands[i]).opsize=S_NO then
717         begin
718 {$ifdef x86_64}
719           if (opcode=A_MOVQ) and
720              (ops=2) and
721              (operands[1].opr.typ=OPR_CONSTANT) then
722              opsize:=S_Q
723           else
724 {$endif x86_64}
725             case operands[i].Opr.Typ of
726               OPR_LOCAL,
727               OPR_REFERENCE :
728                 begin
729                   { for 3-operand opcodes, operand #1 (in ATT order) is always an immediate,
730                     don't consider it. }
731                   if i=ops then
732                     operand2:=i-1
733                   else
734                     operand2:=i+1;
735                   if operand2>0 then
736                    begin
737                      { Only allow register as operand to take the size from }
738                      if operands[operand2].opr.typ=OPR_REGISTER then
739                        begin
740                          if ((opcode<>A_MOVD) and
741                              (opcode<>A_CVTSI2SS)) then
742                       begin
743                         //tx86operand(operands[i]).opsize:=tx86operand(operands[operand2]).opsize;
744 
745                         // torsten - 31.01.2012
746                         // old: xmm/ymm-register operands have a opsize = "S_NO"
747                         // new: xmm/ymm-register operands have a opsize = "S_XMM/S_YMM"
748 
749                         // any SSE- and AVX-opcodes have mixed operand sizes (e.g. cvtsd2ss xmmreg, xmmreg/m32)
750                         // in this case is we need the old handling ("S_NO")
751                         // =>> ignore
752                         if (tx86operand(operands[operand2]).opsize <> S_XMM) and
753                            (tx86operand(operands[operand2]).opsize <> S_YMM) then
754                           tx86operand(operands[i]).opsize:=tx86operand(operands[operand2]).opsize
755                         else tx86operand(operands[operand2]).opsize := S_NO;
756                       end;
757                     end
758                      else
759                       begin
760                         { if no register then take the opsize (which is available with ATT),
761                           if not availble then give an error }
762                         if opsize<>S_NO then
763                           tx86operand(operands[i]).opsize:=opsize
764                         else
765                          begin
766                            if (m_delphi in current_settings.modeswitches) then
767                              Message(asmr_w_unable_to_determine_reference_size_using_dword)
768                            else
769                              Message(asmr_e_unable_to_determine_reference_size);
770                            { recovery }
771                            tx86operand(operands[i]).opsize:=S_L;
772                          end;
773                       end;
774                    end
775                   else
776                    begin
777                      if opsize<>S_NO then
778                        tx86operand(operands[i]).opsize:=opsize
779                    end;
780                 end;
781               OPR_SYMBOL :
782                 begin
783                   { Fix lea which need a reference }
784                   if opcode=A_LEA then
785                    begin
786                      s:=operands[i].opr.symbol;
787                      so:=operands[i].opr.symofs;
788                      operands[i].opr.typ:=OPR_REFERENCE;
789                      Fillchar(operands[i].opr.ref,sizeof(treference),0);
790                      operands[i].opr.ref.symbol:=s;
791                      operands[i].opr.ref.offset:=so;
792                    end;
793   {$if defined(x86_64)}
794                   tx86operand(operands[i]).opsize:=S_Q;
795   {$elseif defined(i386)}
796                   tx86operand(operands[i]).opsize:=S_L;
797   {$elseif defined(i8086)}
798                   tx86operand(operands[i]).opsize:=S_W;
799   {$endif}
800                 end;
801             end;
802         end;
803     end;
804 end;
805 
806 
807 procedure Tx86Instruction.SetInstructionOpsize;
808 begin
809   if opsize<>S_NO then
810    exit;
811   case ops of
812     0 : ;
813     1 :
814       begin
815         { "push es" must be stored as a long PM }
816         if ((opcode=A_PUSH) or
817             (opcode=A_POP)) and
818            (operands[1].opr.typ=OPR_REGISTER) and
819            is_segment_reg(operands[1].opr.reg) then
820 {$ifdef i8086}
821           opsize:=S_W
822 {$else i8086}
823           opsize:=S_L
824 {$endif i8086}
825         else
826           opsize:=tx86operand(operands[1]).opsize;
827       end;
828     2 :
829       begin
830         case opcode of
831           A_MOVZX,A_MOVSX :
832             begin
833               if tx86operand(operands[1]).opsize=S_NO then
834                 begin
835                   tx86operand(operands[1]).opsize:=S_B;
836                   if (m_delphi in current_settings.modeswitches) then
837                     Message(asmr_w_unable_to_determine_reference_size_using_byte)
838                   else
839                     Message(asmr_e_unable_to_determine_reference_size);
840                 end;
841               case tx86operand(operands[1]).opsize of
842                 S_W :
843                   case tx86operand(operands[2]).opsize of
844                     S_L :
845                       opsize:=S_WL;
846 {$ifdef x86_64}
847                     S_Q :
848                       opsize:=S_WQ;
849 {$endif}
850                   end;
851                 S_B :
852                   begin
853                     case tx86operand(operands[2]).opsize of
854                       S_W :
855                         opsize:=S_BW;
856                       S_L :
857                         opsize:=S_BL;
858 {$ifdef x86_64}
859                       S_Q :
860                         opsize:=S_BQ;
861 {$endif}
862                     end;
863                   end;
864               end;
865             end;
866           A_MOVSS,
867           A_VMOVSS,
868           A_MOVD : { movd is a move from a mmx register to a
869                      32 bit register or memory, so no opsize is correct here PM }
870             exit;
871           A_MOVQ :
872             opsize:=S_IQ;
873           A_CVTSI2SS,
874           A_CVTSI2SD,
875           A_OUT :
876             opsize:=tx86operand(operands[1]).opsize;
877           else
878             opsize:=tx86operand(operands[2]).opsize;
879         end;
880       end;
881     3 :
882       begin
883         case opcode of
884           A_VCVTSI2SS,
885           A_VCVTSI2SD:
886             opsize:=tx86operand(operands[1]).opsize;
887         else
888           opsize:=tx86operand(operands[ops]).opsize;
889         end;
890       end;
891     4 :
892         opsize:=tx86operand(operands[ops]).opsize;
893 
894   end;
895 end;
896 
897 
898 procedure Tx86Instruction.CheckOperandSizes;
899 var
900   sizeerr : boolean;
901   i : longint;
902 begin
903   { Check only the most common opcodes here, the others are done in
904     the assembler pass }
905   case opcode of
906     A_PUSH,A_POP,A_DEC,A_INC,A_NOT,A_NEG,
907     A_CMP,A_MOV,
908     A_ADD,A_SUB,A_ADC,A_SBB,
909     A_AND,A_OR,A_TEST,A_XOR: ;
910   else
911     exit;
912   end;
913   { Handle the BW,BL,WL separatly }
914   sizeerr:=false;
915   { special push/pop selector case }
916   if ((opcode=A_PUSH) or
917       (opcode=A_POP)) and
918      (operands[1].opr.typ=OPR_REGISTER) and
919      is_segment_reg(operands[1].opr.reg) then
920     exit;
921   if opsize in [S_BW,S_BL,S_WL] then
922    begin
923      if ops<>2 then
924       sizeerr:=true
925      else
926       begin
927         case opsize of
928           S_BW :
929             sizeerr:=(tx86operand(operands[1]).opsize<>S_B) or (tx86operand(operands[2]).opsize<>S_W);
930           S_BL :
931             sizeerr:=(tx86operand(operands[1]).opsize<>S_B) or (tx86operand(operands[2]).opsize<>S_L);
932           S_WL :
933             sizeerr:=(tx86operand(operands[1]).opsize<>S_W) or (tx86operand(operands[2]).opsize<>S_L);
934         end;
935       end;
936    end
937   else
938    begin
939      for i:=1 to ops do
940       begin
941         if (operands[i].opr.typ<>OPR_CONSTANT) and
942            (tx86operand(operands[i]).opsize in [S_B,S_W,S_L]) and
943            (tx86operand(operands[i]).opsize<>opsize) then
944          sizeerr:=true;
945       end;
946    end;
947   if sizeerr then
948    begin
949      { if range checks are on then generate an error }
950      if (cs_compilesystem in current_settings.moduleswitches) or
951         not (cs_check_range in current_settings.localswitches) then
952        Message(asmr_w_size_suffix_and_dest_dont_match)
953      else
954        Message(asmr_e_size_suffix_and_dest_dont_match);
955    end;
956 end;
957 
958 
959 { This check must be done with the operand in ATT order
960   i.e.after swapping in the intel reader
961   but before swapping in the NASM and TASM writers PM }
962 procedure Tx86Instruction.CheckNonCommutativeOpcodes;
963 begin
964   if (
965       (ops=2) and
966       (operands[1].opr.typ=OPR_REGISTER) and
967       (operands[2].opr.typ=OPR_REGISTER) and
968       { if the first is ST and the second is also a register
969         it is necessarily ST1 .. ST7 }
970       ((operands[1].opr.reg=NR_ST) or
971        (operands[1].opr.reg=NR_ST0))
972      ) or
973      (ops=0) then
974       if opcode=A_FSUBR then
975         opcode:=A_FSUB
976       else if opcode=A_FSUB then
977         opcode:=A_FSUBR
978       else if opcode=A_FDIVR then
979         opcode:=A_FDIV
980       else if opcode=A_FDIV then
981         opcode:=A_FDIVR
982       else if opcode=A_FSUBRP then
983         opcode:=A_FSUBP
984       else if opcode=A_FSUBP then
985         opcode:=A_FSUBRP
986       else if opcode=A_FDIVRP then
987         opcode:=A_FDIVP
988       else if opcode=A_FDIVP then
989         opcode:=A_FDIVRP;
990   if  (
991        (ops=1) and
992        (operands[1].opr.typ=OPR_REGISTER) and
993        (getregtype(operands[1].opr.reg)=R_FPUREGISTER) and
994        (operands[1].opr.reg<>NR_ST) and
995        (operands[1].opr.reg<>NR_ST0)
996       ) then
997       if opcode=A_FSUBRP then
998         opcode:=A_FSUBP
999       else if opcode=A_FSUBP then
1000         opcode:=A_FSUBRP
1001       else if opcode=A_FDIVRP then
1002         opcode:=A_FDIVP
1003       else if opcode=A_FDIVP then
1004         opcode:=A_FDIVRP;
1005 end;
1006 
1007 procedure Tx86Instruction.FixupOpcode;
1008 begin
1009   { does nothing by default }
1010 end;
1011 
1012 {*****************************************************************************
1013                               opcode Adding
1014 *****************************************************************************}
1015 
Tx86Instruction.ConcatInstructionnull1016 function Tx86Instruction.ConcatInstruction(p : TAsmList) : tai;
1017 var
1018   siz  : topsize;
1019   i,asize : longint;
1020   ai   : taicpu;
1021 begin
1022   ConcatInstruction:=nil;
1023 
1024   ai:=nil;
1025   for i:=1 to Ops do
1026     if not operands[i].CheckOperand then
1027       exit;
1028 
1029 { Get Opsize }
1030   if (opsize<>S_NO) or (Ops=0) then
1031    siz:=opsize
1032   else
1033    begin
1034      if (Ops=2) and (operands[1].opr.typ=OPR_REGISTER) then
1035       siz:=tx86operand(operands[1]).opsize
1036      else
1037       siz:=tx86operand(operands[Ops]).opsize;
1038      { MOVD should be of size S_LQ or S_QL, but these do not exist PM }
1039      if (ops=2) and
1040         (tx86operand(operands[1]).opsize<>S_NO) and
1041         (tx86operand(operands[2]).opsize<>S_NO) and
1042         (tx86operand(operands[1]).opsize<>tx86operand(operands[2]).opsize) then
1043        siz:=S_NO;
1044    end;
1045 
1046    if ((opcode=A_MOVD)or
1047        (opcode=A_CVTSI2SS)) and
1048       ((tx86operand(operands[1]).opsize=S_NO) or
1049        (tx86operand(operands[2]).opsize=S_NO)) then
1050      siz:=S_NO;
1051    { NASM does not support FADD without args
1052      as alias of FADDP
1053      and GNU AS interprets FADD without operand differently
1054      for version 2.9.1 and 2.9.5 !! }
1055    if (ops=0) and
1056       ((opcode=A_FADD) or
1057        (opcode=A_FMUL) or
1058        (opcode=A_FSUB) or
1059        (opcode=A_FSUBR) or
1060        (opcode=A_FDIV) or
1061        (opcode=A_FDIVR)) then
1062      begin
1063        if opcode=A_FADD then
1064          opcode:=A_FADDP
1065        else if opcode=A_FMUL then
1066          opcode:=A_FMULP
1067        else if opcode=A_FSUB then
1068          opcode:=A_FSUBP
1069        else if opcode=A_FSUBR then
1070          opcode:=A_FSUBRP
1071        else if opcode=A_FDIV then
1072          opcode:=A_FDIVP
1073        else if opcode=A_FDIVR then
1074          opcode:=A_FDIVRP;
1075        message1(asmr_w_fadd_to_faddp,std_op2str[opcode]);
1076      end;
1077 
1078   {It is valid to specify some instructions without operand size.}
1079   if siz=S_NO then
1080     begin
1081       if (ops=1) and (opcode=A_INT) then
1082         siz:=S_B;
1083       if (ops=1) and (opcode=A_XABORT) then
1084         siz:=S_B;
1085 {$ifdef i8086}
1086       if (ops=1) and (opcode=A_BRKEM) then
1087         siz:=S_B;
1088 {$endif i8086}
1089       if (ops=1) and (opcode=A_RET) or (opcode=A_RETN) or (opcode=A_RETF) or
1090                      (opcode=A_RETW) or (opcode=A_RETNW) or (opcode=A_RETFW) or
1091 {$ifndef x86_64}
1092                      (opcode=A_RETD) or (opcode=A_RETND) or
1093 {$endif x86_64}
1094                      (opcode=A_RETFD)
1095 {$ifdef x86_64}
1096                   or (opcode=A_RETQ) or (opcode=A_RETNQ) or (opcode=A_RETFQ)
1097 {$endif x86_64}
1098           then
1099         siz:=S_W;
1100       if (ops=1) and (opcode=A_PUSH) then
1101         begin
1102 {$ifdef i8086}
1103           if (tx86operand(operands[1]).opr.val>=-128) and (tx86operand(operands[1]).opr.val<=127) then
1104             begin
1105               siz:=S_B;
1106               message(asmr_w_unable_to_determine_constant_size_using_byte);
1107             end
1108           else
1109             begin
1110               siz:=S_W;
1111               message(asmr_w_unable_to_determine_constant_size_using_word);
1112             end;
1113 {$else i8086}
1114           { We are a 32 compiler, assume 32-bit by default. This is Delphi
1115             compatible but bad coding practise.}
1116 
1117           siz:=S_L;
1118           message(asmr_w_unable_to_determine_reference_size_using_dword);
1119 {$endif i8086}
1120         end;
1121       if (opcode=A_JMP) or (opcode=A_JCC) or (opcode=A_CALL) then
1122         if ops=1 then
1123           siz:=S_NEAR
1124         else
1125           siz:=S_FAR;
1126     end;
1127 
1128    { GNU AS interprets FDIV without operand differently
1129      for version 2.9.1 and 2.10
1130      we add explicit args to it !! }
1131   if (ops=0) and
1132      ((opcode=A_FSUBP) or
1133       (opcode=A_FSUBRP) or
1134       (opcode=A_FDIVP) or
1135       (opcode=A_FDIVRP) or
1136       (opcode=A_FSUB) or
1137       (opcode=A_FSUBR) or
1138       (opcode=A_FADD) or
1139       (opcode=A_FADDP) or
1140       (opcode=A_FDIV) or
1141       (opcode=A_FDIVR)) then
1142      begin
1143        message1(asmr_w_adding_explicit_args_fXX,std_op2str[opcode]);
1144        ops:=2;
1145        operands[1].opr.typ:=OPR_REGISTER;
1146        operands[2].opr.typ:=OPR_REGISTER;
1147        operands[1].opr.reg:=NR_ST0;
1148        operands[2].opr.reg:=NR_ST1;
1149      end;
1150   if (ops=1) and
1151      (
1152       (operands[1].opr.typ=OPR_REGISTER) and
1153       (getregtype(operands[1].opr.reg)=R_FPUREGISTER) and
1154       (operands[1].opr.reg<>NR_ST) and
1155       (operands[1].opr.reg<>NR_ST0)
1156      ) and
1157      (
1158       (opcode=A_FSUBP) or
1159       (opcode=A_FSUBRP) or
1160       (opcode=A_FDIVP) or
1161       (opcode=A_FDIVRP) or
1162       (opcode=A_FADDP) or
1163       (opcode=A_FMULP)
1164      ) then
1165      begin
1166        message1(asmr_w_adding_explicit_first_arg_fXX,std_op2str[opcode]);
1167        ops:=2;
1168        operands[2].opr.typ:=OPR_REGISTER;
1169        operands[2].opr.reg:=operands[1].opr.reg;
1170        operands[1].opr.reg:=NR_ST0;
1171      end;
1172 
1173   if (ops=1) and
1174      (
1175       (operands[1].opr.typ=OPR_REGISTER) and
1176       (getregtype(operands[1].opr.reg)=R_FPUREGISTER) and
1177       (operands[1].opr.reg<>NR_ST) and
1178       (operands[1].opr.reg<>NR_ST0)
1179      ) and
1180      (
1181       (opcode=A_FSUB) or
1182       (opcode=A_FSUBR) or
1183       (opcode=A_FDIV) or
1184       (opcode=A_FDIVR) or
1185       (opcode=A_FADD) or
1186       (opcode=A_FMUL)
1187      ) then
1188      begin
1189        message1(asmr_w_adding_explicit_second_arg_fXX,std_op2str[opcode]);
1190        ops:=2;
1191        operands[2].opr.typ:=OPR_REGISTER;
1192        operands[2].opr.reg:=NR_ST0;
1193      end;
1194 
1195    { Check for 'POP CS' }
1196    if (opcode=A_POP) and (ops=1) and (operands[1].opr.typ=OPR_REGISTER) and
1197       (operands[1].opr.reg=NR_CS) then
1198 {$ifdef i8086}
1199      { On i8086 we print only a warning, because 'POP CS' works on 8086 and 8088
1200        CPUs, but isn't supported on any later CPU }
1201      Message(asmr_w_pop_cs_not_portable);
1202 {$else i8086}
1203      { On the i386 and x86_64 targets, we print out an error, because no CPU,
1204        supported by these targets support 'POP CS' }
1205      Message(asmr_e_pop_cs_not_valid);
1206 {$endif i8086}
1207 
1208    { I tried to convince Linus Torvalds to add
1209      code to support ENTER instruction
1210      (when raising a stack page fault)
1211      but he replied that ENTER is a bad instruction and
1212      Linux does not need to support it
1213      So I think its at least a good idea to add a warning
1214      if someone uses this in assembler code
1215      FPC itself does not use it at all PM }
1216    if (opcode=A_ENTER) and
1217       (target_info.system in [system_i386_linux,system_i386_FreeBSD,system_i386_android]) then
1218      Message(asmr_w_enter_not_supported_by_linux);
1219 
1220 
1221 
1222 
1223   ai:=taicpu.op_none(opcode,siz);
1224   ai.fileinfo:=filepos;
1225   ai.SetOperandOrder(op_att);
1226   ai.Ops:=Ops;
1227   ai.Allocate_oper(Ops);
1228   for i:=1 to Ops do
1229     case operands[i].opr.typ of
1230        OPR_CONSTANT :
1231          ai.loadconst(i-1,operands[i].opr.val);
1232        OPR_REGISTER:
1233          ai.loadreg(i-1,operands[i].opr.reg);
1234        OPR_SYMBOL:
1235 {$ifdef i8086}
1236         if operands[i].opr.symseg then
1237           taicpu(ai).loadsegsymbol(i-1,operands[i].opr.symbol)
1238         else
1239 {$endif i8086}
1240           ai.loadsymbol(i-1,operands[i].opr.symbol,operands[i].opr.symofs);
1241        OPR_LOCAL :
1242          with operands[i].opr do
1243            begin
1244              ai.loadlocal(i-1,localsym,localsymofs,localindexreg,
1245                           localscale,localgetoffset,localforceref);
1246              ai.oper[i-1]^.localoper^.localsegment:=localsegment;
1247            end;
1248        OPR_REFERENCE:
1249          begin
1250            if (opcode<>A_XLAT) and not is_x86_string_op(opcode) then
1251              optimize_ref(operands[i].opr.ref,true);
1252            ai.loadref(i-1,operands[i].opr.ref);
1253            if operands[i].size<>OS_NO then
1254              begin
1255                asize:=0;
1256                case operands[i].size of
1257                    OS_8,OS_S8 :
1258                      asize:=OT_BITS8;
1259                    OS_16,OS_S16, OS_M16:
1260                      asize:=OT_BITS16;
1261                    OS_32,OS_S32 :
1262 {$ifdef i8086}
1263                      if siz=S_FAR then
1264                        asize:=OT_FAR
1265                      else
1266                        asize:=OT_BITS32;
1267 {$else i8086}
1268                      asize:=OT_BITS32;
1269 {$endif i8086}
1270                    OS_F32,OS_M32 :
1271                      asize:=OT_BITS32;
1272                    OS_64,OS_S64:
1273                      begin
1274                        { Only FPU operations know about 64bit values, for all
1275                          integer operations it is seen as 32bit
1276 
1277                          this applies only to i386, see tw16622}
1278 
1279                        if gas_needsuffix[opcode] in [attsufFPU,attsufFPUint] then
1280                          asize:=OT_BITS64
1281 {$ifdef i386}
1282                        else
1283                          asize:=OT_BITS32
1284 {$endif i386}
1285                          ;
1286                      end;
1287                    OS_F64,OS_C64, OS_M64 :
1288                      asize:=OT_BITS64;
1289                    OS_F80 :
1290                      asize:=OT_BITS80;
1291                    OS_128,OS_M128,OS_MS128:
1292                      asize := OT_BITS128;
1293                    OS_M256,OS_MS256:
1294                      asize := OT_BITS256;
1295                  end;
1296                if asize<>0 then
1297                  ai.oper[i-1]^.ot:=(ai.oper[i-1]^.ot and not OT_SIZE_MASK) or asize;
1298              end;
1299          end;
1300     end;
1301 
1302  { Condition ? }
1303   if condition<>C_None then
1304    ai.SetCondition(condition);
1305 
1306   { Set is_jmp, it enables asmwriter to emit short jumps if appropriate }
1307   if (opcode=A_JMP) or (opcode=A_JCC) then
1308     ai.is_jmp := True;
1309 
1310  { Concat the opcode or give an error }
1311   if assigned(ai) then
1312     p.concat(ai)
1313   else
1314    Message(asmr_e_invalid_opcode_and_operand);
1315   result:=ai;
1316 end;
1317 
1318 end.
1319