FreeBASIC  0.91.0
emit_x86.bas
Go to the documentation of this file.
1 '' code generation for x86, GNU assembler (GAS/Intel arch)
2 ''
3 '' chng: sep/2004 written [v1ctor]
4 '' mar/2005 longint support added [v1ctor]
5 '' may/2008 SSE/SSE2 instructions [Bryan Stoeberl]
6 
7 
8 #include once "fb.bi"
9 #include once "fbint.bi"
10 #include once "reg.bi"
11 #include once "ir.bi"
12 #include once "rtl.bi"
13 #include once "emit.bi"
14 #include once "emitdbg.bi"
15 #include once "hash.bi"
16 #include once "symb.bi"
17 #include once "emit-private.bi"
18 
19 declare sub hDeclVariable _
20  ( _
21  byval s as FBSYMBOL ptr _
22  )
23 
24 declare function _getSectionString _
25  ( _
26  byval section as integer, _
27  byval priority as integer _
28  ) as const zstring ptr
29 
30 declare sub _setSection _
31  ( _
32  byval section as integer, _
33  byval priority as integer _
34  )
35 
36 declare function _getTypeString( byval dtype as integer ) as const zstring ptr
37 
38 ''globals
39 
40  '' same order as EMITREG_ENUM
41  dim shared rnameTB(0 to EMIT_MAXRTABLES-1, 0 to EMIT_MAXRNAMES-1) as zstring * 7+1 => _
42  { _
43  { "dl", "di", "si", "cl", "bl", "al", "bp", "sp" }, _
44  { "dx", "di", "si", "cx", "bx", "ax", "bp", "sp" }, _
45  { "edx", "edi", "esi", "ecx", "ebx", "eax", "ebp", "esp" }, _
46  { "st(0)","st(1)","st(2)","st(3)","st(4)","st(5)","st(6)","st(7)" } _
47  }
48 
49  '' same order as FB_DATATYPE
50  dim shared dtypeTB(0 to FB_DATATYPES-1) as EMITDATATYPE => _
51  { _
52  ( 0, "void ptr" ), _ '' void
53  ( 0, "byte ptr" ), _ '' byte
54  ( 0, "byte ptr" ), _ '' ubyte
55  ( 0, "byte ptr" ), _ '' char
56  ( 1, "word ptr" ), _ '' short
57  ( 1, "word ptr" ), _ '' ushort
58  ( 1, "word ptr" ), _ '' wchar
59  ( 2, "dword ptr" ), _ '' int
60  ( 2, "dword ptr" ), _ '' uint
61  ( 2, "dword ptr" ), _ '' enum
62  ( 2, "dword ptr" ), _ '' bitfield
63  ( 2, "dword ptr" ), _ '' long
64  ( 2, "dword ptr" ), _ '' ulong
65  ( 2, "qword ptr" ), _ '' longint
66  ( 2, "qword ptr" ), _ '' ulongint
67  ( 3, "dword ptr" ), _ '' single
68  ( 3, "qword ptr" ), _ '' double
69  ( 0, "" ), _ '' string
70  ( 0, "byte ptr" ), _ '' fix-len string
71  ( 2, "dword ptr" ), _ '' struct
72  ( 0, "" ), _ '' namespace
73  ( 2, "dword ptr" ), _ '' function
74  ( 0, "byte ptr" ), _ '' fwd-ref
75  ( 2, "dword ptr" ), _ '' pointer
76  ( 3, "xmmword ptr" ) _ '' 128-bit
77  }
78 
79 const EMIT_MAXKEYWORDS = 600
80 
81  dim shared keywordTb(0 to EMIT_MAXKEYWORDS-1) as const zstring ptr => _
82  { _
83  @"st", @"cs", @"ds", @"es", @"fs", @"gs", @"ss", _
84  @"mm0", @"mm1", @"mm2", @"mm3", @"mm4", @"mm5", @"mm6", @"mm7", _
85  @"xmm0", @"xmm1", @"xmm2", @"xmm3", @"xmm4", @"xmm5", @"xmm6", @"xmm7", _
86  @"byte", @"word", @"dword", @"qword", _
87  @"ptr", @"offset", _
88  @"aaa", @"aad", @"aam", @"aas", @"adc", @"add", @"addpd", @"addps", @"addsd", @"addss", @"and", @"andpd", @"andps", _
89  @"andnpd", @"andnps", @"arpl", @"bound", @"bsf", @"bsr", @"bswap", @"bt", @"btc", @"btr", @"bts", @"call", @"cbw", _
90  @"cwde", @"cdq", @"clc", @"cld", @"clflush", @"cli", @"clts", @"cmc", @"cmova", @"cmovae", @"cmovb", @"cmovbe", _
91  @"cmovc", @"cmove", @"cmovg", @"cmovge", @"cmovl", @"cmovle", @"cmovna", @"cmovnae", @"cmovnb", @"cmovnbe", _
92  @"cmovnc", @"cmovne", @"cmovng", @"cmovnge", @"cmovnl", @"cmovnle", @"cmovno", @"cmovnp", @"cmovns", @"cmovnz", _
93  @"cmovo", @"cmovp", @"cmovpe", @"cmovpe", @"cmovpo", @"cmovs", @"cmovz", @"cmp", @"cmppd", @"cmpps", @"cmps", _
94  @"cmpsb", @"cmpsw", @"cmpsd", @"cmpss", @"cmpxchg", @"cmpxchg8b", @"comisd", @"comiss", @"cpuid", @"cvtdq2pd", _
95  @"cvtdq2ps", @"cvtpd2dq", @"cvtpd2pi", @"cvtpd2ps", @"cvtpi2pd", @"cvtpi2ps", @"cvtps2dq", @"cvtps2pd", _
96  @"cvtps2pi", @"cvtsd2si", @"cvtsd2ss", @"cvtsi2sd", @"cvtsi2ss", @"cvtss2sd", @"cvtss2si", @"cvttpd2pi", _
97  @"cvttpd2dq", @"cvttps2dq", @"cvttps2pi", @"cvttsd2si", @"cvttss2si", @"cwd", @"daa", @"das", @"dec", @"div", _
98  @"divpd", @"divps", @"divss", @"emms", @"enter", @"f2xm1", @"fabs", @"fadd", @"faddp", @"fiadd", @"fbld", _
99  @"fbstp", @"fchs", @"fclex", @"fnclex", @"fcmovb", @"fcmove", @"fcmovbe", @"fcmovu", @"fcmovnb", @"fcmovne", _
100  @"fcmovnbe", @"fcmovnu", @"fcom", @"fcomp", @"fcompp", @"fcomi", @"fcomip", @"fucomi", @"fucomip", @"fcos", _
101  @"fdecstp", @"fdiv", @"fdivp", @"fidiv", @"fdivr", @"fdivrp", @"fidivr", @"ffree", @"ficom", @"ficomp", _
102  @"fild", @"fincstp", @"finit", @"fninit", @"fist", @"fistp", @"fld", @"fld1", @"fldl2t", @"fldl2e", @"fldpi", _
103  @"fldlg2", @"fldln2", @"fldz", @"fldcw", @"fldenv", @"fmul", @"fmulp", @"fimul", @"fnop", @"fpatan", @"fprem", _
104  @"fprem1", @"fptan", @"frndint", @"frstor", @"fsave", @"fnsave", @"fscale", @"fsin", @"fsincos", @"fsqrt", _
105  @"fst", @"fstp", @"fstcw", @"fnstcw", @"fstenv", @"fnstenv", @"fstsw", @"fnstsw", @"fsub", @"fsubp", @"fisub", _
106  @"fsubr", @"fsubrp", @"fisubr", @"ftst", @"fucom", @"fucomp", @"fucompp", @"fwait", @"fxam", @"fxch", @"fxrstor", _
107  @"fxsave", @"fxtract", @"fyl2x", @"fyl2xp1", @"hlt", @"idiv", @"imul", @"in", @"inc", @"ins", @"insb", @"insw", _
108  @"insd", @"int", @"into", @"invd", @"invlpg", @"iret", @"iretd", @"ja", @"jae", @"jb", @"jbe", @"jc", @"jcxz", _
109  @"jecxz", @"je", @"jg", @"jge", @"jl", @"jle", @"jna", @"jnae", @"jnb", @"jnbe", @"jnc", @"jne", @"jng", @"jnge", _
110  @"jnl", @"jnle", @"jno", @"jnp", @"jns", @"jnz", @"jo", @"jp", @"jpe", @"jpo", @"js", @"jz", @"jmp", @"lahf", @"lar", _
111  @"ldmxcsr", @"lds", @"les", @"lfs", @"lgs", @"lss", @"lea", @"leave", @"lfence", @"lgdt", @"lidt", @"lldt", @"lmsw", _
112  @"lock", @"lods", @"lodsb", @"lodsw", @"lodsd", @"loop", @"loope", @"loopz", @"loopne", @"loopnz", @"lsl", @"ltr", _
113  @"maskmovdqu", @"maskmovq", @"maxpd", @"maxps", @"maxsd", @"maxss", @"mfence", @"minpd", @"minps", @"minsd", _
114  @"minss", @"mov", @"movapd", @"movaps", @"movd", @"movdqa", @"movdqu", @"movdq2q", @"movhlps", @"movhpd", _
115  @"movhps", @"movlhps", @"movlpd", @"movlps", @"movmskpd", @"movmskps", @"movntdq", @"movnti", @"movntpd", _
116  @"movntps", @"movntq", @"movq", @"movq2dq", @"movs", @"movsb", @"movsw", @"movsd", @"movss", @"movsx", @"movupd", _
117  @"movups", @"movzx", @"mul", @"mulpd", @"mulps", @"mulsd", @"mulss", @"neg", @"nop", @"not", @"or", @"orpd", _
118  @"orps", @"out", @"outs", @"outsb", @"outsw", @"outsd", @"packsswb", @"packssdw", @"packuswb", @"paddb", _
119  @"paddw", @"paddd", @"paddq", @"paddsb", @"paddsw", @"paddusb", @"paddusw", @"pand", @"pandn", @"pause", _
120  @"pavgb", @"pavgw", @"pcmpeqb", @"pcmpeqw", @"pcmpeqd", @"pcmpgtb", @"pcmpgtw", @"pcmpgtd", @"pextrw", _
121  @"pinsrw", @"pmaddwd", @"pmaxsw", @"pmaxub", @"pminsw", @"pminub", @"pmovmskb", @"pmulhuv", @"pmulhw", _
122  @"pmullw", @"pmuludq", @"pop", @"popa", @"popad", @"popf", @"popfd", @"por", @"prefetcht0", @"prefetcht1", _
123  @"prefetcht2", @"prefetchnta", @"psadbw", @"pshufd", @"pshufhw", @"pshuflw", @"pshufw", @"psllw", @"pslld", _
124  @"psllq", @"psraw", @"psrad", @"psrldq", @"psrlw", @"psrld", @"psrlq", @"psubb", @"psubw", @"psubd", @"psubq", _
125  @"psubsb", @"psubsw", @"psubusb", @"psubusw", @"punpckhbw", @"punpckhwd", @"punpckhdq", @"punpckhqdq", _
126  @"punpcklbw", @"punpcklwd", @"punpckldq", @"punpcklqdq", @"push", @"pusha", @"pushad", @"pushf", @"pushfd", _
127  @"pxor", @"rcl", @"rcr", @"rol", @"ror", @"rcpps", @"rcpss", @"rdmsr", @"rdpmc", @"rdtsc", @"rep", @"repe", _
128  @"repz", @"repne", @"repnz", @"ret", @"rsm", @"rsqrtps", @"rsqrtss", @"sahf", @"sal", @"sar", @"shl", @"shr", _
129  @"sbb", @"scas", @"scasb", @"scasw", @"scasd", @"seta", @"setae", @"setb", @"setbe", @"setc", @"sete", @"setg", _
130  @"setge", @"setl", @"setle", @"setna", @"setnae", @"setnb", @"setnbe", @"setnc", @"setne", @"setng", @"setnge", _
131  @"setnl", @"setnle", @"setno", @"setnp", @"setns", @"setnz", @"seto", @"setp", @"setpe", @"setpo", @"sets", _
132  @"setz", @"sfence", @"sgdt", @"sidt", @"shld", @"shrd", @"shufpd", @"shufps", @"sldt", @"smsw", @"sqrtpd", _
133  @"sqrtps", @"sqrtsd", @"sqrtss", @"stc", @"std", @"sti", @"stmxcsr", @"stos", @"stosb", @"stosw", @"stosd", _
134  @"str", @"sub", @"subpd", @"subps", @"subsd", @"subss", @"sysenter", @"sysexit", @"test", @"ucomisd", _
135  @"ucomiss", @"ud2", @"unpckhpd", @"unpckhps", @"unpcklpd", @"unpcklps", @"verr", @"verw", @"wait", @"wbinvd", _
136  @"wrmsr", @"xadd", @"xchg", @"xlat", @"xlatb", @"xor", @"xorpd", @"xorps", _
137  @"pavgusb", @"pfadd", @"pfsub", @"pfsubr", @"pfacc", @"pfcmpge", @"pfcmpgt", @"pfcmpeq", @"pfmin", @"pfmax", _
138  @"pi2fw", @"pi2fd", @"pf2iw", @"pf2id", @"pfrcp", @"pfrsqrt", @"pfmul", @"pfrcpit1", @"pfrsqit1", @"pfrcpit2", _
139  @"pmulhrw", @"pswapw", @"femms", @"prefetch", @"prefetchw", @"pfnacc", @"pfpnacc", @"pswapd", @"pmulhuw", _
140  NULL _
141  }
142 
143 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
144 '' helper functions
145 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
146 
147 '':::::
148 #define hEmitBssHeader( ) _setSection( IR_SECTION_BSS, 0 )
149 
150 '':::::
151 #ifdef __FB_LINUX__
152 ''
153 '' !!!FIXME!!!
154 ''
155 '' Linux appears to support .rodata section, but I'm not sure about other platforms, and that's
156 '' probably the reason FB used to output a normal .data section in any case...
157 ''
158 #define hEmitConstHeader( ) _setSection( IR_SECTION_CONST, 0 )
159 #else
160 #define hEmitConstHeader( ) _setSection( IR_SECTION_DATA, 0 )
161 #endif
162 
163 '':::::
164 #define hEmitDataHeader( ) _setSection( IR_SECTION_DATA, 0 )
165 
166 '':::::
167 #define hEmitExportHeader( ) _setSection( IR_SECTION_DIRECTIVE, 0 )
168 
169 #if __FB_DEBUG__
170 function emitDumpRegName( byval dtype as integer, byval reg as integer ) as string
171  function = *hGetRegName( dtype, reg )
172 end function
173 #endif
174 
175 '':::::
176 function hIsRegFree _
177  ( _
178  byval dclass as integer, _
179  byval reg as integer _
180  ) as integer static
181 
182  '' if EBX, EDI or ESI and if they weren't ever used, return false,
183  '' because hCreateFrame didn't preserve them
184  if( dclass = FB_DATACLASS_INTEGER ) then
185  select case reg
186  case EMIT_REG_EBX, EMIT_REG_ESI, EMIT_REG_EDI
187  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, reg ) = FALSE ) then
188  return FALSE
189  end if
190  end select
191  end if
192 
193  assert( dclass < EMIT_REGCLASSES )
194 
195  '' assume it will be trashed
196  EMIT_REGSETUSED( dclass, reg )
197 
198  function = REG_ISFREE( emit.curnode->regFreeTB(dclass), reg )
199 
200 end function
201 
202 '' This will always find a reg that is not used by the given vreg,
203 '' because a single vreg can only use 2 regs at most (longints),
204 '' and x86 has more regs than that.
205 '' Free regs are preferred; however, if all regs are used, the returned reg
206 '' won't be free.
207 function hFindRegNotInVreg _
208  ( _
209  byval vreg as IRVREG ptr, _
210  byval noSIDI as integer = FALSE _
211  ) as integer
212 
213  dim as integer r = any, reg = any, reg2 = any, regs = any
214 
215  function = INVALID '' shouldn't ever happen, getMaxRegs() should be > 0
216 
217  reg = INVALID
218 
219  select case vreg->typ
220  case IR_VREGTYPE_REG
221  reg = vreg->reg
222  case IR_VREGTYPE_IDX, IR_VREGTYPE_PTR
223  if( vreg->vidx <> NULL ) then
224  if( vreg->vidx->typ = IR_VREGTYPE_REG ) then
225  reg = vreg->vidx->reg
226  end if
227  end if
228  end select
229 
230  '' longint..
231  reg2 = INVALID
232  if( vreg->vaux <> NULL ) then
233  if( vreg->vaux->typ = IR_VREGTYPE_REG ) then
234  reg2 = vreg->vaux->reg
235  end if
236  end if
237 
238  regs = emit.regTB(FB_DATACLASS_INTEGER)->getMaxRegs( emit.regTB(FB_DATACLASS_INTEGER) )
239 
240  if( reg2 = INVALID ) then
241  if( noSIDI = FALSE ) then
242  for r as integer = regs-1 to 0 step -1
243  if( r <> reg ) then
244  function = r
245  if( hIsRegFree( FB_DATACLASS_INTEGER, r ) ) then
246  exit for
247  end if
248  end if
249  next
250  '' SI/DI as byte..
251  else
252  for r as integer = regs-1 to 0 step -1
253  if( r <> reg ) then
254  if( r <> EMIT_REG_ESI ) then
255  if( r <> EMIT_REG_EDI ) then
256  function = r
257  if( hIsRegFree( FB_DATACLASS_INTEGER, r ) ) then
258  exit for
259  end if
260  end if
261  end if
262  end if
263  next
264  end if
265  '' longints..
266  else
267  if( noSIDI = FALSE ) then
268  for r as integer = regs-1 to 0 step -1
269  if( (r <> reg) and (r <> reg2) ) then
270  function = r
271  if( hIsRegFree( FB_DATACLASS_INTEGER, r ) ) then
272  exit for
273  end if
274  end if
275  next
276  '' SI/DI as byte..
277  else
278  for r = regs-1 to 0 step -1
279  if( (r <> reg) and (r <> reg2) ) then
280  if( r <> EMIT_REG_ESI ) then
281  if( r <> EMIT_REG_EDI ) then
282  function = r
283  if( hIsRegFree( FB_DATACLASS_INTEGER, r ) ) then
284  exit for
285  end if
286  end if
287  end if
288  end if
289  next
290  end if
291  end if
292 
293 end function
294 
295 '' Returns a free reg or INVALID if there are no free regs
296 function hFindFreeReg( byval dclass as integer ) as integer
297  function = INVALID
298 
299  for r as integer = emit.regTB(dclass)->getMaxRegs( emit.regTB(dclass) )-1 to 0 step -1
300  if( hIsRegFree( dclass, r ) ) then
301  return r
302  end if
303  next
304 end function
305 
306 '':::::
307 function hIsRegInVreg _
308  ( _
309  byval vreg as IRVREG ptr, _
310  byval reg as integer _
311  ) as integer static
312 
313  function = FALSE
314 
315  select case vreg->typ
316  case IR_VREGTYPE_REG
317  if( vreg->reg = reg ) then
318  return TRUE
319  end if
320 
321  case IR_VREGTYPE_IDX, IR_VREGTYPE_PTR
322  if( vreg->vidx <> NULL ) then
323  if( vreg->vidx->typ = IR_VREGTYPE_REG ) then
324  if( vreg->vidx->reg = reg ) then
325  return TRUE
326  end if
327  end if
328  end if
329  end select
330 
331  '' longints..
332  if( vreg->vaux <> NULL ) then
333  if( vreg->vaux->typ = IR_VREGTYPE_REG ) then
334  if( vreg->vaux->reg = reg ) then
335  return TRUE
336  end if
337  end if
338  end if
339 
340 end function
341 
342 '':::::
343 function hGetRegName _
344  ( _
345  byval dtype as integer, _
346  byval reg as integer _
347  ) as zstring ptr
348 
349  if( reg = INVALID ) then
350  function = NULL
351  else
352  dim as integer tb = dtypeTB(typeGet( dtype )).rnametb
353 
354  function = @rnameTB(tb, reg)
355  end if
356 
357 end function
358 
359 '':::::
360 function hGetIdxName _
361  ( _
362  byval vreg as IRVREG ptr _
363  ) as zstring ptr static
364 
365  static as zstring * FB_MAXINTNAMELEN+1+8+1+1+1+8+1 iname
366  dim as FBSYMBOL ptr sym
367  dim as IRVREG ptr vi
368  dim as integer addone, mult
369  dim as zstring ptr rname
370 
371  sym = vreg->sym
372  vi = vreg->vidx
373 
374  if( sym = NULL ) then
375  '' no var or index?
376  if( vi = NULL ) then
377  return NULL
378  end if
379 
380  iname = ""
381 
382  else
383  iname = *symbGetMangledName( sym )
384  if( vi <> NULL ) then
385  iname += "+"
386  end if
387  end if
388 
389  rname = hGetRegName( vi->dtype, vi->reg )
390 
391  iname += *rname
392 
393  if( vi <> NULL ) then
394  mult = vreg->mult
395  ''
396  '' For x86 ASM, a multiplier/scaling factor can be given right
397  '' as part of address/indexing expression. It can be a power
398  '' of two in the range 1..8, i.e. one of {1, 2, 4, 8}.
399  ''
400  '' For example, assuming a variable at ebp-N, holding a valid array index,
401  '' and the corresponding dword array at ebp-M:
402  ''
403  '' mov eax, dword ptr [ebp-N] ; Load array index variable from stack
404  '' mov dword ptr [ebp+eax*4-M], 0 ; Store 0 into element eax of the dword array
405  ''
406  '' instead of:
407  ''
408  '' mov eax, dword ptr [ebp-N]
409  '' imul eax, 4
410  '' mov dword ptr [ebp+eax-M], 0
411  ''
412  '' We can support {3, 5, 9} multipliers by emitting them as
413  '' *2+1, *4+1, *8+1 respectively (with addone = TRUE).
414  ''
415  '' 6 and 7 cannot be supported.
416  ''
417  '' Besides that, since the "addone" form uses up the "offset"
418  '' part from the [base + (index*mult) + offset] form, it can
419  '' only be used if the offset isn't needed in combination with
420  '' the base. This means the "addone" form cannot be used with
421  '' things from stack (ebp-N), but only globals.
422  ''
423 
424  assert( (mult >= 1) and (mult <= 9) )
425  assert( (mult <> 6) and (mult <> 7) )
426 
427  if( mult > 1 ) then
428  addone = FALSE
429  select case mult
430  case 3, 5, 9
431  mult -= 1
432  addone = TRUE
433  end select
434 
435  iname += "*"
436  iname += str( mult )
437 
438  if( addone ) then
439  assert( vreg->ofs = 0 )
440  iname += "+"
441  iname += *rname
442  end if
443  end if
444  end if
445 
446  function = @iname
447 
448 end function
449 
450 '':::::
451 sub hPrepOperand _
452  ( _
453  byval vreg as IRVREG ptr, _
454  byref operand as string, _
455  byval dtype as FB_DATATYPE = FB_DATATYPE_INVALID, _
456  byval ofs as integer = 0, _
457  byval isaux as integer = FALSE, _
458  byval addprefix as integer = TRUE _
459  ) static
460 
461  if( vreg = NULL ) then
462  operand = ""
463  exit sub
464  end if
465 
466  if( dtype = FB_DATATYPE_INVALID ) then
467  dtype = vreg->dtype
468  end if
469 
470  select case as const vreg->typ
471  case IR_VREGTYPE_VAR, IR_VREGTYPE_IDX, IR_VREGTYPE_PTR
472 
473  '' prefix
474  if( addprefix ) then
475  operand = dtypeTB(dtype).mname
476  operand += " ["
477  else
478  operand = "["
479  end if
480 
481  '' base + (index*mult) + offset
482 
483  '' variable or index
484  dim as zstring ptr idx_op
485  if( vreg->typ = IR_VREGTYPE_VAR ) then
486  idx_op = symbGetMangledName( vreg->sym )
487  else
488  idx_op = hGetIdxName( vreg )
489  end if
490 
491  if( idx_op <> NULL ) then
492  operand += *idx_op
493  end if
494 
495  '' offset
496  ofs += vreg->ofs
497  if( isaux ) then
498  ofs += 4
499  end if
500 
501  if( ofs > 0 ) then
502  if( idx_op <> NULL ) then
503  operand += "+"
504  end if
505  operand += str( ofs )
506 
507  elseif( ofs < 0 ) then
508  operand += str( ofs )
509 
510  else
511  if( idx_op = NULL ) then
512  operand += "0"
513  end if
514  end if
515 
516  operand += "]"
517 
518  case IR_VREGTYPE_OFS
519  operand = "offset "
520  operand += *symbGetMangledName( vreg->sym )
521  if( vreg->ofs <> 0 ) then
522  operand += " + "
523  operand += str( vreg->ofs )
524  end if
525 
526  case IR_VREGTYPE_REG
527  if( isaux = FALSE ) then
528  operand = *hGetRegName( dtype, vreg->reg )
529  else
530  operand = *hGetRegName( dtype, vreg->vaux->reg )
531  end if
532 
533  case IR_VREGTYPE_IMM
534  if( isaux = FALSE ) then
535  operand = str( vreg->value.i )
536  else
537  operand = str( vreg->vaux->value.i )
538  end if
539 
540  case else
541  operand = ""
542  end select
543 
544 end sub
545 
546 '':::::
547 sub hPrepOperand64 _
548  ( _
549  byval vreg as IRVREG ptr, _
550  byref operand1 as string, _
551  byref operand2 as string _
552  ) static
553 
554  hPrepOperand( vreg, operand1, FB_DATATYPE_UINT , 0, FALSE )
555  hPrepOperand( vreg, operand2, FB_DATATYPE_INTEGER, 0, TRUE )
556 
557 end sub
558 
559 '':::::
560 sub outEx _
561  ( _
562  byval s as zstring ptr, _
563  byval bytes as integer = 0 _
564  ) static
565 
566  if( bytes = 0 ) then
567  bytes = len( *s )
568  end if
569 
570  if( put( #env.outf.num, , *s, bytes ) = 0 ) then
571  end if
572 
573 end sub
574 
575 '':::::
576 sub outp _
577  ( _
578  byval s as zstring ptr _
579  )
580 
581  static as string ostr
582 
583  if( env.clopt.debug ) then
584  ostr = TABCHAR
585  ostr += *s
586  else
587  ostr = *s
588  end if
589 
590  ostr += NEWLINE
591 
592  outEX( ostr, len( ostr ) )
593 
594 end sub
595 
596 '':::::
597 sub hBRANCH _
598  ( _
599  byval mnemonic as zstring ptr, _
600  byval label as zstring ptr _
601  ) static
602 
603  dim ostr as string
604 
605  ostr = *mnemonic
606  ostr += " "
607  ostr += *label
608  outp( ostr )
609 
610 end sub
611 
612 '':::::
613 sub hPUSH _
614  ( _
615  byval rname as zstring ptr _
616  ) static
617 
618  dim ostr as string
619 
620  ostr = "push "
621  ostr += *rname
622  outp( ostr )
623 
624 end sub
625 
626 '':::::
627 sub hPOP _
628  ( _
629  byval rname as zstring ptr _
630  ) static
631 
632  dim ostr as string
633 
634  ostr = "pop "
635  ostr += *rname
636  outp( ostr )
637 
638 end sub
639 
640 '':::::
641 sub hMOV _
642  ( _
643  byval dname as zstring ptr, _
644  byval sname as zstring ptr _
645  ) static
646 
647  dim ostr as string
648 
649  ostr = "mov "
650  ostr += *dname
651  ostr += ", "
652  ostr += *sname
653  outp( ostr )
654 
655 end sub
656 
657 '':::::
658 sub hXCHG _
659  ( _
660  byval dname as zstring ptr, _
661  byval sname as zstring ptr _
662  ) static
663 
664  dim ostr as string
665 
666  ostr = "xchg "
667  ostr += *dname
668  ostr += ", "
669  ostr += *sname
670  outp( ostr )
671 
672 end sub
673 
674 '':::::
675 sub hCOMMENT _
676  ( _
677  byval s as zstring ptr _
678  ) static
679 
680  dim ostr as string
681 
682  ostr = TABCHAR + "#"
683  ostr += *s
684  ostr += NEWLINE
685  outEX( ostr )
686 
687 end sub
688 
689 '':::::
690 sub hPUBLIC _
691  ( _
692  byval label as zstring ptr, _
693  byval isexport as integer _
694  ) static
695 
696  dim ostr as string
697 
698  ostr = NEWLINE + ".globl "
699  ostr += *label
700 
701 ' PENDING: shared lib compatibility between win32/linux
702 ' rtlib/gfxlib needs -fvisibility=hidden, only available in gcc 4
703 ' if( env.clopt.target = FB_COMPTARGET_LINUX ) then
704 ' if( isexport ) then
705 ' ostr += NEWLINE + ".protected "
706 ' ostr += *label
707 ' else
708 ' ostr += NEWLINE + ".hidden "
709 ' ostr += *label
710 ' end if
711 ' end if
712 
713  ostr += NEWLINE
714  outEx( ostr )
715 
716 end sub
717 
718 '':::::
719 sub hLABEL _
720  ( _
721  byval label as zstring ptr _
722  ) static
723 
724  dim ostr as string
725 
726  ostr = *label
727  ostr += ":" + NEWLINE
728  outEx( ostr )
729 
730 end sub
731 
732 '':::::
733 sub hALIGN _
734  ( _
735  byval bytes as integer _
736  ) static
737 
738  dim ostr as string
739 
740  ostr = ".balign " + str( bytes ) + NEWLINE
741  outEx( ostr )
742 
743 end sub
744 
745 '':::::
747  dim as integer lastclass, regs, i
748 
749  '' ebp and esp are reserved
750  const int_regs = 6
751 
752  static as REG_SIZEMASK int_bitsmask(0 to int_regs-1) = _
753  { _
754  REG_SIZEMASK_8 or REG_SIZEMASK_16 or REG_SIZEMASK_32, _ '' edx
755  REG_SIZEMASK_16 or REG_SIZEMASK_32, _ '' edi
756  REG_SIZEMASK_16 or REG_SIZEMASK_32, _ '' esi
757  REG_SIZEMASK_8 or REG_SIZEMASK_16 or REG_SIZEMASK_32, _ '' ecx
758  REG_SIZEMASK_8 or REG_SIZEMASK_16 or REG_SIZEMASK_32, _ '' ebx
759  REG_SIZEMASK_8 or REG_SIZEMASK_16 or REG_SIZEMASK_32 _ '' eax
760  }
761 
762  emit.regTB(FB_DATACLASS_INTEGER) = _
763  regNewClass( FB_DATACLASS_INTEGER, _
764  int_regs, _
765  int_bitsmask( ), _
766  FALSE )
767 
768  '' no st(7) as STORE/LOAD/POW/.. need a free reg to work
769  const flt_regs = 7
770 
771  static as REG_SIZEMASK flt_bitsmask(0 to flt_regs-1) = _
772  { _
773  REG_SIZEMASK_32 or REG_SIZEMASK_64, _ '' st(0)
774  REG_SIZEMASK_32 or REG_SIZEMASK_64, _ '' st(1)
775  REG_SIZEMASK_32 or REG_SIZEMASK_64, _ '' st(2)
776  REG_SIZEMASK_32 or REG_SIZEMASK_64, _ '' st(3)
777  REG_SIZEMASK_32 or REG_SIZEMASK_64, _ '' st(4)
778  REG_SIZEMASK_32 or REG_SIZEMASK_64, _ '' st(5)
779  REG_SIZEMASK_32 or REG_SIZEMASK_64 _ '' st(6)
780  }
781 
782  '' create non-stacked floating-point registers
783  if( env.clopt.fputype = FB_FPUTYPE_SSE ) then
784  emit.regTB(FB_DATACLASS_FPOINT) = _
785  regNewClass( FB_DATACLASS_FPOINT, _
786  flt_regs, _
787  flt_bitsmask( ), _
788  FALSE )
789 
790  '' change floating-point register names to SSE registers
791  for i = 0 to EMIT_MAXRNAMES - 1
792  rnameTB(EMIT_MAXRTABLES-1, i) = "xmm" + Str(i)
793  next i
794  else
795  emit.regTB(FB_DATACLASS_FPOINT) = _
796  regNewClass( FB_DATACLASS_FPOINT, _
797  flt_regs, _
798  flt_bitsmask( ), _
799  TRUE )
800  end if
801 
802 end sub
803 
804 '':::::
806  dim i as integer
807 
808  for i = 0 to EMIT_REGCLASSES-1
809  regDelClass( emit.regTB(i) )
810  next
811 
812 end sub
813 
814 '':::::
816  dim as integer t, i
817 
818  hashInit( @emit.keyhash, EMIT_MAXKEYWORDS )
819 
820  '' add reg names
821  for t = 0 to EMIT_MAXRTABLES-1
822  for i = 0 to EMIT_MAXRNAMES-1
823  if( len( rnameTB(t,i) ) > 0 ) then
824  hashAdd( @emit.keyhash, @rnameTB(t,i), cast( any ptr, INVALID ), INVALID )
825  end if
826  next
827  next
828 
829  '' add asm keywords
830  for i = 0 to EMIT_MAXKEYWORDS-1
831  if( keywordTb(i) = NULL ) then
832  exit for
833  end if
834 
835  hashAdd( @emit.keyhash, keywordTb(i), cast( any ptr, INVALID ), INVALID )
836  next
837 
838  emit.keyinited = TRUE
839 
840 end sub
841 
842 '':::::
844 
845  if( emit.keyinited ) then
846  hashEnd( @emit.keyhash )
847  end if
848 
849  emit.keyinited = FALSE
850 
851 end sub
852 
853 '':::::
854 sub hEmitVarBss _
855  ( _
856  byval s as FBSYMBOL ptr _
857  ) static
858 
859  dim as string alloc, ostr
860  dim as integer attrib, elements
861 
862  attrib = symbGetAttrib( s )
863 
864  elements = 1
865  if( symbGetArrayDimensions( s ) > 0 ) then
866  elements = symbGetArrayElements( s )
867  end if
868 
869  hEmitBssHeader( )
870 
871  '' allocation modifier
872  if( (attrib and FB_SYMBATTRIB_COMMON) = 0 ) then
873  if( (attrib and FB_SYMBATTRIB_PUBLIC) > 0 ) then
875  end if
876  alloc = ".lcomm"
877  else
879  alloc = ".comm"
880  end if
881 
882  '' align
883  if( symbGetType( s ) = FB_DATATYPE_DOUBLE ) then
884  hALIGN( 8 )
885  emitWriteStr( ".balign 8", TRUE )
886  else
887  hALIGN( 4 )
888  end if
889 
890  '' emit
891  ostr = alloc + TABCHAR
892  ostr += *symbGetMangledName( s )
893  ostr += "," + str( symbGetLen( s ) * elements )
894  emitWriteStr( ostr, TRUE )
895 
896  '' add dbg info, if public or shared
897  if( (attrib and (FB_SYMBATTRIB_SHARED or _
898  FB_SYMBATTRIB_COMMON or _
899  FB_SYMBATTRIB_PUBLIC)) > 0 ) then
900  edbgEmitGlobalVar( s, IR_SECTION_BSS )
901  end if
902 
903 end sub
904 
905 '':::::
906 sub hWriteHeader( ) static
907 
908  ''
909  edbgEmitHeader( env.inf.name )
910 
911  ''
912  emitWriteStr( ".intel_syntax noprefix", TRUE )
913  emitWriteStr( "" )
914  hCOMMENT( env.inf.name + "' compilation started at " + time + " (" + FB_SIGN + ")" )
915 
916 end sub
917 
918 sub hWriteBss( byval s as FBSYMBOL ptr )
919  while( s )
920  select case( symbGetClass( s ) )
921  '' name space?
922  case FB_SYMBCLASS_NAMESPACE
923  hWriteBss( symbGetNamespaceTbHead( s ) )
924 
925  '' UDT namespace? (static member vars)
926  case FB_SYMBCLASS_STRUCT
927  '' "Class"?
928  if( symbGetIsUnique( s ) ) then
929  hWriteBss( symbGetCompSymbTb( s ).head )
930  end if
931 
932  '' scope block?
933  case FB_SYMBCLASS_SCOPE
934  hWriteBss( symbGetScopeSymbTbHead( s ) )
935 
936  '' variable?
937  case FB_SYMBCLASS_VAR
938  hDeclVariable( s )
939 
940  end select
941 
942  s = s->next
943  wend
944 end sub
945 
946 '':::::
947 sub hEmitVarConst _
948  ( _
949  byval s as FBSYMBOL ptr _
950  ) static
951 
952  dim as string stext, stype, ostr
953  dim as integer dtype
954 
955  dtype = symbGetType( s )
956 
957  select case as const dtype
958  case FB_DATATYPE_CHAR
959  stext = QUOTE
960  stext += *hEscape( symbGetVarLitText( s ) )
961  stext += RSLASH + "0" + QUOTE
962 
963  case FB_DATATYPE_WCHAR
964  stext = QUOTE
965  stext += *hEscapeW( symbGetVarLitTextW( s ) )
966  for i as integer = 1 to typeGetSize( FB_DATATYPE_WCHAR )
967  stext += RSLASH + "0"
968  next
969  stext += QUOTE
970 
971  case else
972  stext = *symbGetVarLitText( s )
973  end select
974 
975  hEmitConstHeader( )
976 
977  '' some SSE instructions require operands to be 16-byte aligned
978  if( s->var_.align ) then
979  hALIGN ( s->var_.align )
980  else
981  if( dtype = FB_DATATYPE_DOUBLE ) then
982  hALIGN( 8 )
983  else
984  hALIGN( 4 )
985  end if
986  end if
987 
988 
989  stype = *_getTypeString( dtype )
990  ostr = *symbGetMangledName( s )
991  ostr += (":" + TABCHAR) + stype + TABCHAR + stext
992  emitWriteStr( ostr )
993 
994 end sub
995 
996 sub hWriteConst( byval s as FBSYMBOL ptr )
997  while( s )
998  select case( symbGetClass( s ) )
999  '' name space?
1000  case FB_SYMBCLASS_NAMESPACE
1001  hWriteConst( symbGetNamespaceTbHead( s ) )
1002 
1003  '' UDT namespace? (static member vars)
1004  case FB_SYMBCLASS_STRUCT
1005  '' "Class"?
1006  if( symbGetIsUnique( s ) ) then
1007  hWriteConst( symbGetCompSymbTb( s ).head )
1008  end if
1009 
1010  '' scope block?
1011  case FB_SYMBCLASS_SCOPE
1012  hWriteConst( symbGetScopeSymbTbHead( s ) )
1013 
1014  '' variable?
1015  case FB_SYMBCLASS_VAR
1016  hDeclVariable( s )
1017  end select
1018 
1019  s = s->next
1020  wend
1021 end sub
1022 
1023 sub hWriteData( byval s as FBSYMBOL ptr )
1024  while( s )
1025  select case( symbGetClass( s ) )
1026  '' name space?
1027  case FB_SYMBCLASS_NAMESPACE
1028  hWriteData( symbGetNamespaceTbHead( s ) )
1029 
1030  '' UDT namespace? (static member vars)
1031  case FB_SYMBCLASS_STRUCT
1032  '' "Class"?
1033  if( symbGetIsUnique( s ) ) then
1034  hWriteData( symbGetCompSymbTb( s ).head )
1035  end if
1036 
1037  '' scope block?
1038  case FB_SYMBCLASS_SCOPE
1039  hWriteData( symbGetScopeSymbTbHead( s ) )
1040 
1041  '' variable?
1042  case FB_SYMBCLASS_VAR
1043  hDeclVariable( s )
1044 
1045  end select
1046 
1047  s = s->next
1048  wend
1049 end sub
1050 
1051 '':::::
1052 sub hWriteCtor _
1053  ( _
1054  byval proc_head as FB_GLOBCTORLIST_ITEM ptr, _
1055  byval is_ctor as integer _
1056  )
1057 
1058  if( proc_head = NULL ) then
1059  exit sub
1060  end if
1061 
1062  do
1063  '' was it emitted?
1064  if( symbGetProcIsEmitted( proc_head->sym ) ) then
1065  _setSection( iif( is_ctor, _
1066  IR_SECTION_CONSTRUCTOR, _
1067  IR_SECTION_DESTRUCTOR ), _
1068  symbGetProcPriority( proc_head->sym ) )
1069  emitVARINIOFS( symbGetMangledName( proc_head->sym ), 0 )
1070  end if
1071 
1072  proc_head = proc_head->next
1073  loop while( proc_head <> NULL )
1074 
1075 end sub
1076 
1077 sub hEmitExport( byval s as FBSYMBOL ptr )
1078  if( symbIsExport( s ) ) then
1079  hEmitExportHeader( )
1080 
1081  dim as zstring ptr sname = symbGetMangledName( s )
1082  if( env.target.options and FB_TARGETOPT_UNDERSCORE ) then
1083  sname += 1
1084  end if
1085 
1086  emitWriteStr( ".ascii " + QUOTE + " -export:" + _
1087  *sname + (QUOTE + NEWLINE), _
1088  TRUE )
1089  end if
1090 end sub
1091 
1092 sub hWriteExport( byval s as FBSYMBOL ptr )
1093 
1094  '' for each proc exported..
1095  do while( s )
1096 
1097  select case symbGetClass( s )
1098  '' name space?
1099  case FB_SYMBCLASS_NAMESPACE
1100  hWriteExport( symbGetNamespaceTbHead( s ) )
1101 
1102  case FB_SYMBCLASS_STRUCT
1103  '' does struct have exports?
1104  dim as FBSYMBOL ptr walk = symbGetUDTSymbTbHead( s )
1105  while( walk )
1106  hEmitExport( walk )
1107  walk = symbGetNext( walk )
1108  wend
1109 
1110  case FB_SYMBCLASS_PROC
1111  if( symbGetIsDeclared( s ) ) then
1112  hEmitExport( s )
1113  end if
1114  end select
1115 
1116  s = s->next
1117  loop
1118 
1119 end sub
1120 
1121 '':::::
1122 sub hDeclVariable _
1123  ( _
1124  byval s as FBSYMBOL ptr _
1125  ) static
1126 
1127  '' already allocated?
1128  if( symbGetVarIsAllocated( s ) ) then
1129  return
1130  end if
1131 
1132  symbSetVarIsAllocated( s )
1133 
1134  '' literal?
1135  if( symbGetIsLiteral( s ) ) then
1136 
1137  select case symbGetType( s )
1138  '' udt? don't emit
1139  case FB_DATATYPE_STRUCT
1140  return
1141 
1142  '' string? check if ever referenced
1143  case FB_DATATYPE_CHAR, FB_DATATYPE_WCHAR
1144  if( symbGetIsAccessed( s ) = FALSE ) then
1145  return
1146  end if
1147 
1148  '' anything else, only if len > 0
1149  case else
1150  if( symbGetLen( s ) <= 0 ) then
1151  return
1152  end if
1153  end select
1154 
1155  hEmitVarConst( s )
1156 
1157  return
1158  end if
1159 
1160  '' initialized?
1161  if( symbGetIsInitialized( s ) ) then
1162 
1163  '' extern or jump-tb?
1164  if( symbIsExtern( s ) ) then
1165  return
1166  elseif( symbGetIsJumpTb( s ) ) then
1167  return
1168  end if
1169 
1170  '' never referenced?
1171  if( symbGetIsAccessed( s ) = FALSE ) then
1172  '' not public?
1173  if( symbIsPublic( s ) = FALSE ) then
1174  return
1175  end if
1176  end if
1177 
1178  hEmitDataHeader( )
1179  astTypeIniFlush( s->var_.initree, _
1180  s, _
1181  AST_INIOPT_ISINI or AST_INIOPT_ISSTATIC )
1182 
1183  return
1184  end if
1185 
1186  '' extern or dynamic (for the latter, only the array descriptor is emitted)?
1187  if( (s->attrib and (FB_SYMBATTRIB_EXTERN or _
1188  FB_SYMBATTRIB_DYNAMIC)) <> 0 ) then
1189  return
1190  end if
1191 
1192  '' a string or array descriptor?
1193  if( symbGetLen( s ) <= 0 ) then
1194  return
1195  end if
1196 
1197  hEmitVarBss( s )
1198 
1199 end sub
1200 
1201 '':::::
1202 sub hClearLocals _
1203  ( _
1204  byval bytestoclear as integer, _
1205  byval baseoffset as integer _
1206  ) static
1207 
1208  dim as integer i
1209  dim as string lname
1210 
1211  if( bytestoclear = 0 ) then
1212  exit sub
1213  end if
1214 
1215  if( env.clopt.cputype >= FB_CPUTYPE_686 ) then
1216  if( cunsg(bytestoclear) \ 8 > 7 ) then
1217 
1218  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EDI ) = FALSE ) then
1219  hPUSH( "edi" )
1220  end if
1221 
1222  outp( "lea edi, [ebp-" & baseoffset + bytestoclear & "]" )
1223  outp( "mov ecx," & cunsg(bytestoclear) \ 8 )
1224  outp( "pxor mm0, mm0" )
1225  lname = *symbUniqueLabel( )
1226  hLABEL( lname )
1227  outp( "movq [edi], mm0" )
1228  outp( "add edi, 8" )
1229  outp( "dec ecx" )
1230  outp( "jnz " + lname )
1231  outp( "emms" )
1232 
1233  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EDI ) = FALSE ) then
1234  hPOP( "edi" )
1235  end if
1236 
1237  elseif( cunsg(bytestoclear) \ 8 > 0 ) then
1238  outp( "pxor mm0, mm0" )
1239  for i = cunsg(bytestoclear) \ 8 to 1 step -1
1240  outp( "movq [ebp-" & ( i*8 ) & "], mm0" )
1241  next
1242  outp( "emms" )
1243 
1244  end if
1245 
1246  if( bytestoclear and 4 ) then
1247  outp( "mov dword ptr [ebp-" & baseoffset + bytestoclear & "], 0" )
1248  end if
1249 
1250  exit sub
1251  end if
1252 
1253  if( cunsg(bytestoclear) \ 4 > 6 ) then
1254 
1255  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EDI ) = FALSE ) then
1256  hPUSH( "edi" )
1257  end if
1258 
1259  outp( "lea edi, [ebp-" & baseoffset + bytestoclear & "]" )
1260  outp( "mov ecx," & cunsg(bytestoclear) \ 4 )
1261  outp( "xor eax, eax" )
1262  outp( "rep stosd" )
1263 
1264  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EDI ) = FALSE ) then
1265  hPOP( "edi" )
1266  end if
1267 
1268  else
1269  for i = cunsg(bytestoclear) \ 4 to 1 step -1
1270  outp( "mov dword ptr [ebp-" & baseoffset + ( i*4 ) & "], 0" )
1271  next
1272  end if
1273 
1274 end sub
1275 
1276 '':::::
1277 sub hCreateFrame _
1278  ( _
1279  byval proc as FBSYMBOL ptr _
1280  ) static
1281 
1282  dim as integer bytestoalloc, bytestoclear
1283  dim as zstring ptr lprof
1284 
1285  ' No frame for naked functions
1286  if( symbIsNaked( proc ) = FALSE ) then
1287 
1288  bytestoalloc = ((proc->proc.ext->stk.localmax - EMIT_LOCSTART) + 3) and (not 3)
1289 
1290  if( (bytestoalloc <> 0) or _
1291  (proc->proc.ext->stk.argofs <> EMIT_ARGSTART) or _
1292  symbGetIsMainProc( proc ) or _
1293  env.clopt.debug or _
1294  env.clopt.profile ) then
1295 
1296  hPUSH( "ebp" )
1297  outp( "mov ebp, esp" )
1298 
1299  if( symbGetIsMainProc( proc ) ) then
1300  outp( "and esp, 0xFFFFFFF0" )
1301  end if
1302 
1303  if( bytestoalloc > 0 ) then
1304  outp( "sub esp, " + str( bytestoalloc ) )
1305  end if
1306  end if
1307 
1308  if( env.clopt.target = FB_COMPTARGET_DOS ) then
1309  if( env.clopt.profile ) then
1310  lprof = symbMakeProfileLabelName( )
1311 
1312  outEx(".section .data" + NEWLINE )
1313  outEx( ".balign 4" + NEWLINE )
1314  outEx( "." + *lprof + ":" + NEWLINE )
1315  outp( ".long 0" )
1316  outEx( ".section .text" + NEWLINE )
1317  outp( "mov edx, offset ." + *lprof )
1318  outp( "call _mcount" )
1319  end if
1320  end if
1321 
1322  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EBX ) ) then
1323  hPUSH( "ebx" )
1324  end if
1325  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_ESI ) ) then
1326  hPUSH( "esi" )
1327  end if
1328  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EDI ) ) then
1329  hPUSH( "edi" )
1330  end if
1331 
1332  end if
1333 
1334  ''
1335 #if 0
1336  bytestoclear = ((proc->proc.ext->stk.localofs - EMIT_LOCSTART) + 3) and (not 3)
1337 
1338  hClearLocals( bytestoclear, 0 )
1339 #endif
1340 
1341 end sub
1342 
1343 ''::::
1344 sub hDestroyFrame _
1345  ( _
1346  byval proc as FBSYMBOL ptr, _
1347  byval bytestopop as integer _
1348  ) static
1349 
1350  ' don't do anything for naked functions, except the .size at the end
1351  if( symbIsNaked( proc ) = FALSE ) then
1352 
1353  dim as integer bytestoalloc
1354 
1355  bytestoalloc = ((proc->proc.ext->stk.localmax - EMIT_LOCSTART) + 3) and (not 3)
1356 
1357  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EDI ) ) then
1358  hPOP( "edi" )
1359  end if
1360  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_ESI ) ) then
1361  hPOP( "esi" )
1362  end if
1363  if( EMIT_REGISUSED( FB_DATACLASS_INTEGER, EMIT_REG_EBX ) ) then
1364  hPOP( "ebx" )
1365  end if
1366 
1367  if( (bytestoalloc <> 0) or _
1368  (proc->proc.ext->stk.argofs <> EMIT_ARGSTART) or _
1369  symbGetIsMainProc( proc ) or _
1370  env.clopt.debug or _
1371  env.clopt.profile ) then
1372  outp( "mov esp, ebp" )
1373  hPOP( "ebp" )
1374  end if
1375 
1376  if( bytestopop > 0 ) then
1377  outp( "ret " + str( bytestopop ) )
1378  else
1379  outp( "ret" )
1380  end if
1381 
1382  end if
1383 
1384  if( env.clopt.target = FB_COMPTARGET_LINUX ) then
1385  outEx( ".size " + *symbGetMangledName( proc ) + ", .-" + *symbGetMangledName( proc ) + NEWLINE )
1386  end if
1387 
1388 end sub
1389 
1390 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
1391 '' implementation
1392 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
1393 
1394 sub _emitLIT( byval s as zstring ptr )
1395  dim ostr as string
1396  ostr = *s + NEWLINE
1397  outEX( ostr )
1398 end sub
1399 
1400 sub _emitJMPTB _
1401  ( _
1402  byval tbsym as FBSYMBOL ptr, _
1403  byval values1 as ulongint ptr, _
1404  byval labels1 as FBSYMBOL ptr ptr, _
1405  byval labelcount as integer, _
1406  byval deflabel as FBSYMBOL ptr, _
1407  byval minval as ulongint, _
1408  byval maxval as ulongint _
1409  )
1410 
1411  dim as FBSYMBOL ptr label = any
1412  dim as string deflabelname, tb
1413  dim as integer i = any
1414 
1415  deflabelname = *symbGetMangledName( deflabel )
1416 
1417  assert( labelcount > 0 )
1418 
1419  tb = *symbGetMangledName( tbsym )
1420 
1421  ''
1422  '' Emit entries for each value from minval to maxval.
1423  '' Each value that is in the values1 array uses the corresponding label
1424  '' from the labels1 array; all other values use the default label.
1425  ''
1426  '' table:
1427  '' .int labelforvalue1
1428  '' .int labelforvalue2
1429  '' .int deflabel
1430  '' .int labelforvalue4
1431  '' ...
1432  ''
1433 
1434  outEx( tb + ":" + NEWLINE )
1435  i = 0
1436  for value as ulongint = minval to maxval
1437  assert( i < labelcount )
1438  if( value = values1[i] ) then
1439  label = labels1[i]
1440  i += 1
1441  else
1442  label = deflabel
1443  end if
1444  outp( *_getTypeString( FB_DATATYPE_UINT ) + " " + *symbGetMangledName( label ) )
1445  next
1446 
1447 end sub
1448 
1449 '':::::
1450 sub _emitCALL _
1451  ( _
1452  byval unused as IRVREG ptr, _
1453  byval label as FBSYMBOL ptr, _
1454  byval bytestopop as integer _
1455  ) static
1456 
1457  dim ostr as string
1458 
1459  ostr = "call "
1460  ostr += *symbGetMangledName( label )
1461  outp( ostr )
1462 
1463  if( bytestopop <> 0 ) then
1464  ostr = "add esp, " + str( bytestopop )
1465  outp( ostr )
1466  end if
1467 
1468 end sub
1469 
1470 '':::::
1471 sub _emitCALLPTR _
1472  ( _
1473  byval svreg as IRVREG ptr, _
1474  byval unused as FBSYMBOL ptr, _
1475  byval bytestopop as integer _
1476  ) static
1477 
1478  dim src as string
1479  dim ostr as string
1480 
1481  hPrepOperand( svreg, src )
1482 
1483  ostr = "call " + src
1484  outp( ostr )
1485 
1486  if( bytestopop <> 0 ) then
1487  ostr = "add esp, " + str( bytestopop )
1488  outp( ostr )
1489  end if
1490 
1491 end sub
1492 
1493 '':::::
1494 sub _emitBRANCH _
1495  ( _
1496  byval unused as IRVREG ptr, _
1497  byval label as FBSYMBOL ptr, _
1498  byval op as integer _
1499  ) static
1500 
1501  dim ostr as string
1502 
1503  select case as const op
1504  case AST_OP_JLE
1505  ostr = "jle "
1506  case AST_OP_JGE
1507  ostr = "jge "
1508  case AST_OP_JLT
1509  ostr = "jl "
1510  case AST_OP_JGT
1511  ostr = "jg "
1512  case AST_OP_JEQ
1513  ostr = "je "
1514  case AST_OP_JNE
1515  ostr = "jne "
1516  end select
1517 
1518  ostr += *symbGetMangledName( label )
1519  outp( ostr )
1520 
1521 end sub
1522 
1523 '':::::
1524 sub _emitJUMP _
1525  ( _
1526  byval unused1 as IRVREG ptr, _
1527  byval label as FBSYMBOL ptr, _
1528  byval unused2 as integer _
1529  ) static
1530 
1531  dim ostr as string
1532 
1533  ostr = "jmp "
1534  ostr += *symbGetMangledName( label )
1535  outp( ostr )
1536 
1537 end sub
1538 
1539 '':::::
1540 sub _emitJUMPPTR _
1541  ( _
1542  byval svreg as IRVREG ptr, _
1543  byval unused1 as FBSYMBOL ptr, _
1544  byval unused2 as integer _
1545  ) static
1546 
1547  dim src as string
1548  dim ostr as string
1549 
1550  hPrepOperand( svreg, src )
1551 
1552  ostr = "jmp " + src
1553  outp( ostr )
1554 
1555 end sub
1556 
1557 '':::::
1558 sub _emitRET _
1559  ( _
1560  byval vreg as IRVREG ptr _
1561  ) static
1562 
1563  dim ostr as string
1564 
1565  ostr = "ret " + str( vreg->value.i )
1566  outp( ostr )
1567 
1568 end sub
1569 
1570 '':::::
1571 sub _emitPUBLIC _
1572  ( _
1573  byval label as FBSYMBOL ptr _
1574  ) static
1575 
1576  dim ostr as string
1577 
1578  ostr = NEWLINE + ".globl "
1579  ostr += *symbGetMangledName( label )
1580  ostr += NEWLINE
1581  outEx( ostr )
1582 
1583 end sub
1584 
1585 '':::::
1586 sub _emitLABEL _
1587  ( _
1588  byval label as FBSYMBOL ptr _
1589  ) static
1590 
1591  dim ostr as string
1592 
1593  ostr = *symbGetMangledName( label )
1594  ostr += ":" + NEWLINE
1595  outEx( ostr )
1596 
1597 end sub
1598 
1599 '':::::
1600 sub _emitNOP _
1601  ( _
1602  _
1603  ) static
1604 
1605 end sub
1606 
1607 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
1608 '' store
1609 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
1610 
1611 '':::::
1612 sub hULONG2DBL _
1613  ( _
1614  byval svreg as IRVREG ptr _
1615  ) static
1616 
1617  dim as string label, aux, ostr
1618 
1619  label = *symbUniqueLabel( )
1620 
1621  hPrepOperand( svreg, aux, FB_DATATYPE_INTEGER, 0, TRUE )
1622  ostr = "cmp " + aux + ", 0"
1623 
1624  outp ostr
1625  ostr = "jns " + label
1626  outp ostr
1627  hPUSH( "0x403f" )
1628  hPUSH( "0x80000000" )
1629  hPUSH( "0" )
1630  outp "fldt [esp]"
1631  outp "add esp, 12"
1632  outp "faddp"
1633  hLABEL( label )
1634 
1635 end sub
1636 
1637 '':::::
1638 sub _emitSTORL2L _
1639  ( _
1640  byval dvreg as IRVREG ptr, _
1641  byval svreg as IRVREG ptr _
1642  ) static
1643 
1644  dim as string dst1, dst2, src1, src2, ostr
1645 
1646  hPrepOperand64( dvreg, dst1, dst2 )
1647  hPrepOperand64( svreg, src1, src2 )
1648 
1649  ostr = "mov " + dst1 + COMMA + src1
1650  outp ostr
1651 
1652  ostr = "mov " + dst2 + COMMA + src2
1653  outp ostr
1654 
1655 end sub
1656 
1657 '':::::
1658 sub _emitSTORI2L _
1659  ( _
1660  byval dvreg as IRVREG ptr, _
1661  byval svreg as IRVREG ptr _
1662  ) static
1663 
1664  dim as string dst1, dst2, src1, ext, ostr
1665  dim sdsize as integer
1666 
1667  sdsize = typeGetSize( svreg->dtype )
1668 
1669  hPrepOperand64( dvreg, dst1, dst2 )
1670 
1671  hPrepOperand( svreg, src1 )
1672 
1673  '' immediate?
1674  if( svreg->typ = IR_VREGTYPE_IMM ) then
1675  hMOV dst1, src1
1676 
1677  '' negative?
1678  if( typeIsSigned( svreg->dtype ) and (svreg->value.i < 0) ) then
1679  hMOV dst2, "-1"
1680  else
1681  hMOV dst2, "0"
1682  end if
1683 
1684  exit sub
1685  end if
1686 
1687  ''
1688  if( sdsize < 4 ) then
1689  ext = *hGetRegName( FB_DATATYPE_INTEGER, svreg->reg )
1690 
1691  if( typeIsSigned( svreg->dtype ) ) then
1692  ostr = "movsx "
1693  else
1694  ostr = "movzx "
1695  end if
1696  ostr += ext + COMMA + src1
1697  outp ostr
1698 
1699  else
1700  ext = src1
1701  end if
1702 
1703  ostr = "mov " + dst1 + COMMA + ext
1704  outp ostr
1705 
1706  if( typeIsSigned( svreg->dtype ) ) then
1707 
1708  hPUSH ext
1709 
1710  ostr = "sar " + ext + ", 31"
1711  outp ostr
1712 
1713  ostr = "mov " + dst2 + COMMA + ext
1714  outp ostr
1715 
1716  hPOP ext
1717 
1718  else
1719  ostr = "mov " + dst2 + ", 0"
1720  outp ostr
1721  end if
1722 
1723 end sub
1724 
1725 
1726 '':::::
1727 sub _emitSTORF2L _
1728  ( _
1729  byval dvreg as IRVREG ptr, _
1730  byval svreg as IRVREG ptr _
1731  ) static
1732 
1733  dim as string dst
1734  dim as string ostr
1735 
1736  hPrepOperand( dvreg, dst )
1737 
1738  '' signed?
1739  if( typeIsSigned( dvreg->dtype ) ) then
1740  ostr = "fistp " + dst
1741  outp ostr
1742 
1743  end if
1744 
1745 end sub
1746 
1747 
1748 '':::::
1749 sub _emitSTORI2I _
1750  ( _
1751  byval dvreg as IRVREG ptr, _
1752  byval svreg as IRVREG ptr _
1753  ) static
1754 
1755  dim as string dst, src
1756  dim as integer ddsize, sdsize
1757  dim as string ostr
1758 
1759  hPrepOperand( dvreg, dst )
1760  hPrepOperand( svreg, src )
1761 
1762  ddsize = typeGetSize( dvreg->dtype )
1763  sdsize = typeGetSize( svreg->dtype )
1764 
1765  if( ddsize = 1 ) then
1766  if( svreg->typ = IR_VREGTYPE_IMM ) then
1767  ddsize = 4
1768  end if
1769  end if
1770 
1771  '' dst size = src size
1772  if( (svreg->typ = IR_VREGTYPE_IMM) or (ddsize = sdsize) ) then
1773  ostr = "mov " + dst + COMMA + src
1774  outp ostr
1775  '' sizes are different..
1776  else
1777  dim as string aux
1778 
1779  aux = *hGetRegName( dvreg->dtype, svreg->reg )
1780 
1781  '' dst size > src size
1782  if( ddsize > sdsize ) then
1783  if( typeIsSigned( svreg->dtype ) ) then
1784  ostr = "movsx "
1785  else
1786  ostr = "movzx "
1787  end if
1788  ostr += aux + COMMA + src
1789  outp ostr
1790 
1791  ostr = "mov " + dst + COMMA + aux
1792  outp ostr
1793 
1794  '' dst size < src size
1795  else
1796  '' handle DI/SI as source stored into a byte destine
1797  dim as integer is_disi
1798 
1799  is_disi = FALSE
1800  if( ddsize = 1 ) then
1801  if( svreg->typ = IR_VREGTYPE_REG ) then
1802  is_disi = (svreg->reg = EMIT_REG_ESI) or (svreg->reg = EMIT_REG_EDI)
1803  end if
1804  end if
1805 
1806  if( is_disi ) then
1807  dim as string aux8
1808  dim as integer reg, isfree
1809 
1810  reg = hFindRegNotInVreg( dvreg, TRUE )
1811 
1812  aux8 = *hGetRegName( FB_DATATYPE_BYTE, reg )
1813  aux = *hGetRegName( svreg->dtype, reg )
1814 
1815  isfree = hIsRegFree(FB_DATACLASS_INTEGER, reg )
1816  if( isfree = FALSE ) then
1817  hPUSH aux
1818  end if
1819 
1820  ostr = "mov " + aux + COMMA + src
1821  outp ostr
1822 
1823  ostr = "mov " + dst + COMMA + aux8
1824  outp ostr
1825 
1826  if( isfree = FALSE ) then
1827  hPOP aux
1828  end if
1829 
1830  else
1831  ostr = "mov " + dst + COMMA + aux
1832  outp ostr
1833  end if
1834  end if
1835  end if
1836 
1837 end sub
1838 
1839 '':::::
1840 sub _emitSTORL2I _
1841  ( _
1842  byval dvreg as IRVREG ptr, _
1843  byval svreg as IRVREG ptr _
1844  ) static
1845 
1846  '' been too complex due the SI/DI crap, leave it to I2I
1847  _emitSTORI2I( dvreg, svreg )
1848 
1849 end sub
1850 
1851 
1852 '':::::
1853 sub _emitSTORF2I _
1854  ( _
1855  byval dvreg as IRVREG ptr, _
1856  byval svreg as IRVREG ptr _
1857  ) static
1858 
1859  dim as string dst, src
1860  dim as integer ddsize
1861  dim as string ostr
1862 
1863  hPrepOperand( dvreg, dst )
1864  hPrepOperand( svreg, src )
1865 
1866  ddsize = typeGetSize( dvreg->dtype )
1867 
1868  '' byte destine? damn..
1869  if( ddsize = 1 ) then
1870 
1871  outp "sub esp, 4"
1872  outp "fistp dword ptr [esp]"
1873 
1874  '' destine is a reg?
1875  if( dvreg->typ = IR_VREGTYPE_REG ) then
1876 
1877  hMOV dst, "byte ptr [esp]"
1878  outp "add esp, 4"
1879 
1880  '' destine is a var/idx/ptr
1881  else
1882  dim as integer reg, isfree
1883  dim as string aux, aux8
1884 
1885  reg = hFindRegNotInVreg( dvreg, TRUE )
1886 
1887  aux8 = *hGetRegName( FB_DATATYPE_BYTE, reg )
1888  aux = *hGetRegName( FB_DATATYPE_INTEGER, reg )
1889 
1890  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
1891 
1892  if( isfree = FALSE ) then
1893  hXCHG aux, "dword ptr [esp]"
1894  else
1895  hMOV aux8, "byte ptr [esp]"
1896  end if
1897 
1898  hMOV dst, aux8
1899 
1900  if( isfree = FALSE ) then
1901  hPOP aux
1902  else
1903  outp "add esp, 4"
1904  end if
1905 
1906  end if
1907 
1908  else
1909  '' signed?
1910  if( typeIsSigned( dvreg->dtype ) ) then
1911  ostr = "fistp " + dst
1912  outp ostr
1913 
1914  '' unsigned.. try a bigger type
1915  else
1916  '' uint?
1917  if( ddsize = 4 ) then
1918  outp "sub esp, 8"
1919  outp "fistp qword ptr [esp]"
1920  hPOP dst
1921  outp "add esp, 4"
1922 
1923  '' ushort..
1924  else
1925  outp "sub esp, 4"
1926  outp "fistp dword ptr [esp]"
1927  hPOP dst
1928  outp "add esp, 2"
1929  end if
1930  end if
1931 
1932  end if
1933 
1934 end sub
1935 
1936 
1937 
1938 '':::::
1939 sub _emitSTORL2F _
1940  ( _
1941  byval dvreg as IRVREG ptr, _
1942  byval svreg as IRVREG ptr _
1943  ) static
1944 
1945  dim as string dst, src, aux
1946  dim as string ostr
1947 
1948  hPrepOperand( dvreg, dst )
1949  hPrepOperand( svreg, src )
1950 
1951  if( (svreg->typ = IR_VREGTYPE_REG) or (svreg->typ = IR_VREGTYPE_IMM) ) then
1952 
1953  '' signed?
1954  if( typeIsSigned( svreg->dtype ) ) then
1955 
1956  hPrepOperand64( svreg, src, aux )
1957 
1958  hPUSH( aux )
1959  hPUSH( src )
1960 
1961  ostr = "fild " + dtypeTB(svreg->dtype).mname + " [esp]"
1962  outp ostr
1963 
1964  outp "add esp, 8"
1965 
1966  '' unsigned..
1967  else
1968  hPrepOperand64( svreg, src, aux )
1969  hPUSH aux
1970  hPUSH src
1971  outp "fild qword ptr [esp]"
1972  outp "add esp, 8"
1973  hULONG2DBL( svreg )
1974 
1975  end if
1976 
1977  '' not a reg or imm
1978  else
1979  '' signed?
1980  if( typeIsSigned( svreg->dtype ) ) then
1981  ostr = "fild " + src
1982  outp ostr
1983 
1984  '' unsigned, try a bigger type..
1985  else
1986  ostr = "fild " + src
1987  outp ostr
1988  hULONG2DBL( svreg )
1989 
1990  end if
1991  end if
1992 
1993  ostr = "fstp " + dst
1994  outp ostr
1995 
1996 end sub
1997 
1998 
1999 
2000 '':::::
2001 sub _emitSTORI2F _
2002  ( _
2003  byval dvreg as IRVREG ptr, _
2004  byval svreg as IRVREG ptr _
2005  ) static
2006 
2007  dim as string dst, src
2008  dim as integer sdsize
2009  dim as string ostr
2010 
2011  hPrepOperand( dvreg, dst )
2012  hPrepOperand( svreg, src )
2013 
2014  sdsize = typeGetSize( svreg->dtype )
2015 
2016  '' byte source? damn..
2017  if( sdsize = 1 ) then
2018  dim as string aux
2019  dim as integer reg, isfree
2020 
2021  reg = hFindRegNotInVreg( svreg )
2022 
2023  aux = *hGetRegName( FB_DATATYPE_INTEGER, reg )
2024 
2025  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
2026 
2027  if( isfree = FALSE ) then
2028  hPUSH aux
2029  end if
2030 
2031  if( typeIsSigned( svreg->dtype ) ) then
2032  ostr = "movsx "
2033  else
2034  ostr = "movzx "
2035  end if
2036  ostr += aux + COMMA + src
2037  outp ostr
2038 
2039  hPUSH aux
2040  outp "fild dword ptr [esp]"
2041  outp "add esp, 4"
2042 
2043  if( isfree = FALSE ) then
2044  hPOP aux
2045  end if
2046 
2047  ostr = "fstp " + dst
2048  outp ostr
2049 
2050  exit sub
2051  end if
2052 
2053  ''
2054  if( (svreg->typ = IR_VREGTYPE_REG) or (svreg->typ = IR_VREGTYPE_IMM) ) then
2055 
2056  '' signed?
2057  if( typeIsSigned( svreg->dtype ) ) then
2058 
2059  '' not an integer? make it
2060  if( (svreg->typ = IR_VREGTYPE_REG) and (sdsize < 4) ) then
2061  src = *hGetRegName( FB_DATATYPE_INTEGER, svreg->reg )
2062  end if
2063 
2064  hPUSH src
2065 
2066  ostr = "fild " + dtypeTB(svreg->dtype).mname + " [esp]"
2067  outp ostr
2068 
2069  outp "add esp, 4"
2070 
2071  '' unsigned..
2072  else
2073 
2074  '' uint..
2075  if( sdsize = 4 ) then
2076  hPUSH "0"
2077  hPUSH src
2078  outp "fild qword ptr [esp]"
2079  outp "add esp, 8"
2080 
2081  '' ushort..
2082  else
2083  if( svreg->typ <> IR_VREGTYPE_IMM ) then
2084  hPUSH "0"
2085  end if
2086 
2087  hPUSH src
2088  outp "fild dword ptr [esp]"
2089 
2090  if( svreg->typ <> IR_VREGTYPE_IMM ) then
2091  outp "add esp, 6"
2092  else
2093  outp "add esp, 4"
2094  end if
2095  end if
2096 
2097  end if
2098 
2099  '' not a reg or imm
2100  else
2101 
2102  '' signed?
2103  if( typeIsSigned( svreg->dtype ) ) then
2104  ostr = "fild " + src
2105  outp ostr
2106 
2107  '' unsigned, try a bigger type..
2108  else
2109  '' uint..
2110  if( sdsize = 4 ) then
2111  hPUSH "0"
2112  hPUSH src
2113  outp "fild qword ptr [esp]"
2114  outp "add esp, 8"
2115 
2116  '' ushort..
2117  else
2118  hPUSH "0"
2119  hPUSH src
2120  outp "fild dword ptr [esp]"
2121  outp "add esp, 6"
2122  end if
2123 
2124  end if
2125  end if
2126 
2127  ostr = "fstp " + dst
2128  outp ostr
2129 
2130 end sub
2131 
2132 
2133 
2134 '':::::
2135 sub _emitSTORF2F _
2136  ( _
2137  byval dvreg as IRVREG ptr, _
2138  byval svreg as IRVREG ptr _
2139  ) static
2140 
2141  dim as string dst, src
2142  dim as integer ddsize, sdsize
2143  dim as string ostr
2144 
2145  hPrepOperand( dvreg, dst )
2146  hPrepOperand( svreg, src )
2147 
2148  ddsize = typeGetSize( dvreg->dtype )
2149  sdsize = typeGetSize( svreg->dtype )
2150 
2151  '' on fpu stack?
2152  if( svreg->typ = IR_VREGTYPE_REG ) then
2153  ostr = "fstp " + dst
2154  outp ostr
2155 
2156  else
2157  '' same size? just copy..
2158  if( sdsize = ddsize ) then
2159 
2160  hPrepOperand( svreg, src, FB_DATATYPE_INTEGER, 0 )
2161  ostr = "push " + src
2162  outp ostr
2163 
2164  if( sdsize > 4 ) then
2165  hPrepOperand( svreg, src, FB_DATATYPE_INTEGER, 4 )
2166  ostr = "push " + src
2167  outp ostr
2168 
2169  hPrepOperand( dvreg, dst, FB_DATATYPE_INTEGER, 4 )
2170  ostr = "pop " + dst
2171  outp ostr
2172  end if
2173 
2174  hPrepOperand( dvreg, dst, FB_DATATYPE_INTEGER, 0 )
2175  ostr = "pop " + dst
2176  outp ostr
2177 
2178  '' diff sizes, convert..
2179  else
2180  ostr = "fld " + src
2181  outp ostr
2182 
2183  ostr = "fstp " + dst
2184  outp ostr
2185  end if
2186  end if
2187 
2188 end sub
2189 
2190 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
2191 '' load
2192 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
2193 
2194 '':::::
2195 sub _emitLOADL2L _
2196  ( _
2197  byval dvreg as IRVREG ptr, _
2198  byval svreg as IRVREG ptr _
2199  ) static
2200 
2201  dim as string dst1, dst2, src1, src2
2202  dim as string ostr
2203 
2204  hPrepOperand64( dvreg, dst1, dst2 )
2205  hPrepOperand64( svreg, src1, src2 )
2206 
2207  ostr = "mov " + dst1 + COMMA + src1
2208  outp ostr
2209 
2210  ostr = "mov " + dst2 + COMMA + src2
2211  outp ostr
2212 
2213 end sub
2214 
2215 '':::::
2216 sub _emitLOADI2L _
2217  ( _
2218  byval dvreg as IRVREG ptr, _
2219  byval svreg as IRVREG ptr _
2220  ) static
2221 
2222  dim as string dst1, dst2, src1
2223  dim as integer sdsize
2224  dim as string ostr
2225 
2226  sdsize = typeGetSize( svreg->dtype )
2227 
2228  hPrepOperand64( dvreg, dst1, dst2 )
2229 
2230  hPrepOperand( svreg, src1 )
2231 
2232  '' immediate?
2233  if( svreg->typ = IR_VREGTYPE_IMM ) then
2234  hMOV dst1, src1
2235 
2236  '' negative?
2237  if( typeIsSigned( svreg->dtype ) and (svreg->value.i < 0) ) then
2238  hMOV dst2, "-1"
2239  else
2240  hMOV dst2, "0"
2241  end if
2242 
2243  exit sub
2244  end if
2245 
2246  ''
2247  if( typeIsSigned( svreg->dtype ) ) then
2248 
2249  if( sdsize < 4 ) then
2250  ostr = "movsx " + dst1 + COMMA + src1
2251  outp ostr
2252  else
2253  hMOV dst1, src1
2254  end if
2255 
2256  hMOV dst2, dst1
2257 
2258  ostr = "sar " + dst2 + ", 31"
2259  outp ostr
2260 
2261  else
2262 
2263  if( sdsize < 4 ) then
2264  ostr = "movzx " + dst1 + COMMA + src1
2265  outp ostr
2266  else
2267  hMOV dst1, src1
2268  end if
2269 
2270  hMOV dst2, "0"
2271 
2272  end if
2273 
2274 end sub
2275 
2276 
2277 
2278 '':::::
2279 sub _emitLOADF2L _
2280  ( _
2281  byval dvreg as IRVREG ptr, _
2282  byval svreg as IRVREG ptr _
2283  ) static
2284 
2285  dim as string dst, src, aux
2286  dim as string ostr
2287 
2288  hPrepOperand( dvreg, dst )
2289  hPrepOperand( svreg, src )
2290 
2291  if( svreg->typ <> IR_VREGTYPE_REG ) then
2292  ostr = "fld " + src
2293  outp ostr
2294  end if
2295 
2296  hPrepOperand64( dvreg, dst, aux )
2297 
2298  '' signed?
2299  if( typeIsSigned( dvreg->dtype ) ) then
2300 
2301  outp "sub esp, 8"
2302 
2303  ostr = "fistp " + dtypeTB(dvreg->dtype).mname + " [esp]"
2304  outp ostr
2305 
2306  hPOP( dst )
2307  hPOP( aux )
2308 
2309  '' unsigned.. try a bigger type
2310  else
2311  dim as string label_geq, label_done
2312  dim as integer iseaxfree = any
2313 
2314  label_geq = *symbUniqueLabel( )
2315  label_done = *symbUniqueLabel( )
2316 
2317  '' eax free, or only used in dest?
2318  iseaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
2319  iseaxfree orelse= hIsRegInVreg( dvreg, EMIT_REG_EAX )
2320 
2321  outp "sub esp, 8"
2322  outp "mov dword ptr [esp], 0x5F000000" '' 2^63
2323  outp "fcom dword ptr [esp]"
2324 
2325  if( iseaxfree ) then
2326  outp "fnstsw ax"
2327  outp "test ah, 1"
2328  else
2329  hPUSH( "eax" )
2330  outp "fnstsw ax"
2331  outp "test ah, 1"
2332  hPOP( "eax" )
2333  end if
2334 
2335  hBRANCH( "jz", label_geq )
2336 
2337  '' if x < 2^63
2338  outp "fistp qword ptr [esp]"
2339  hPOP( dst )
2340  hPOP( aux )
2341 
2342  '' elseif x >= 2^63
2343  hBRANCH( "jmp", label_done )
2344  hLABEL( label_geq )
2345 
2346  outp "fsub dword ptr [esp]"
2347  outp "fistp qword ptr [esp]"
2348  hPOP( dst )
2349  hPOP( aux )
2350  outp "xor " + aux + ", 0x80000000"
2351 
2352  '' endif
2353  hLABEL( label_done )
2354 
2355  end if
2356 
2357 end sub
2358 
2359 '':::::
2360 sub _emitLOADI2I _
2361  ( _
2362  byval dvreg as IRVREG ptr, _
2363  byval svreg as IRVREG ptr _
2364  ) static
2365 
2366  dim as string dst, src
2367  dim as integer ddsize, sdsize
2368  dim as string ostr
2369 
2370  hPrepOperand( dvreg, dst )
2371  hPrepOperand( svreg, src )
2372 
2373  ddsize = typeGetSize( dvreg->dtype )
2374  sdsize = typeGetSize( svreg->dtype )
2375 
2376  if( ddsize = 1 ) then
2377  if( svreg->typ = IR_VREGTYPE_IMM ) then
2378  ddsize = 4
2379  end if
2380  end if
2381 
2382  '' dst size = src size
2383  if( ddsize = sdsize ) then
2384  ostr = "mov " + dst + COMMA + src
2385  outp ostr
2386  else
2387  '' dst size > src size
2388  if( ddsize > sdsize ) then
2389  if( typeIsSigned( svreg->dtype ) ) then
2390  ostr = "movsx "
2391  else
2392  ostr = "movzx "
2393  end if
2394  ostr += dst + COMMA + src
2395  outp ostr
2396 
2397  '' dst dize < src size
2398  else
2399  '' is src a reg too?
2400  if( svreg->typ = IR_VREGTYPE_REG ) then
2401  '' not the same?
2402  if( svreg->reg <> dvreg->reg ) then
2403  dim as string aux
2404  dim as integer dtype
2405 
2406  dtype = dvreg->dtype
2407 
2408  '' handle [E]DI/[E]SI source loaded to a byte destine
2409  if( ddsize = 1 ) then
2410  if( (svreg->reg = EMIT_REG_ESI) or _
2411  (svreg->reg = EMIT_REG_EDI) ) then
2412 
2413  dtype = FB_DATATYPE_INTEGER
2414  dst = *hGetRegName( dtype, dvreg->reg )
2415  end if
2416  end if
2417 
2418  aux = *hGetRegName( dtype, svreg->reg )
2419  ostr = "mov " + dst + COMMA + aux
2420  outp ostr
2421  end if
2422 
2423  '' src is not a reg
2424  else
2425  hPrepOperand( svreg, src, dvreg->dtype )
2426 
2427  ostr = "mov " + dst + COMMA + src
2428  outp ostr
2429  end if
2430  end if
2431  end if
2432 
2433 end sub
2434 
2435 '':::::
2436 sub _emitLOADL2I _
2437  ( _
2438  byval dvreg as IRVREG ptr, _
2439  byval svreg as IRVREG ptr _
2440  ) static
2441 
2442  '' been too complex due the SI/DI crap, leave it to I2I
2443  _emitLOADI2I( dvreg, svreg )
2444 
2445 end sub
2446 
2447 
2448 '':::::
2449 sub _emitLOADF2I _
2450  ( _
2451  byval dvreg as IRVREG ptr, _
2452  byval svreg as IRVREG ptr _
2453  ) static
2454 
2455  dim as string dst, src
2456  dim as integer ddsize
2457  dim as string ostr
2458 
2459  hPrepOperand( dvreg, dst )
2460  hPrepOperand( svreg, src )
2461 
2462  ddsize = typeGetSize( dvreg->dtype )
2463 
2464  if( svreg->typ <> IR_VREGTYPE_REG ) then
2465  ostr = "fld " + src
2466  outp ostr
2467  end if
2468 
2469  '' byte destine? damn..
2470  if( ddsize = 1 ) then
2471 
2472  outp "sub esp, 4"
2473  outp "fistp dword ptr [esp]"
2474 
2475  '' destine is a reg
2476  if( dvreg->typ = IR_VREGTYPE_REG ) then
2477  hMOV dst, "byte ptr [esp]"
2478  outp "add esp, 4"
2479 
2480  '' destine is a var/idx/ptr
2481  else
2482  dim as string aux, aux8
2483  dim as integer reg, isfree
2484 
2485  reg = hFindRegNotInVreg( dvreg, TRUE )
2486 
2487  aux8 = *hGetRegName( FB_DATATYPE_BYTE, reg )
2488  aux = *hGetRegName( FB_DATATYPE_INTEGER, reg )
2489 
2490  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
2491 
2492  if( isfree = FALSE ) then
2493  hXCHG aux, "dword ptr [esp]"
2494  else
2495  hMOV aux8, "byte ptr [esp]"
2496  end if
2497 
2498  hMOV dst, aux8
2499 
2500  if( isfree = FALSE ) then
2501  hPOP aux
2502  else
2503  outp "add esp, 4"
2504  end if
2505 
2506  end if
2507 
2508  else
2509 
2510  '' signed?
2511  if( typeIsSigned( dvreg->dtype ) ) then
2512 
2513  outp "sub esp, 4"
2514 
2515  ostr = "fistp " + dtypeTB(dvreg->dtype).mname + " [esp]"
2516  outp ostr
2517 
2518  '' not an integer? make it
2519  if( ddsize < 4 ) then
2520  dst = *hGetRegName( FB_DATATYPE_INTEGER, dvreg->reg )
2521  end if
2522 
2523  hPOP dst
2524 
2525  '' unsigned.. try a bigger type
2526  else
2527 
2528  '' uint?
2529  if( ddsize = 4 ) then
2530  outp "sub esp, 8"
2531  outp "fistp qword ptr [esp]"
2532  hPOP dst
2533  outp "add esp, 4"
2534 
2535  '' ushort..
2536  else
2537  outp "sub esp, 4"
2538  outp "fistp dword ptr [esp]"
2539  hPOP dst
2540  outp "add esp, 2"
2541  end if
2542 
2543  end if
2544 
2545  end if
2546 
2547 end sub
2548 
2549 
2550 '':::::
2551 sub _emitLOADL2F _
2552  ( _
2553  byval dvreg as IRVREG ptr, _
2554  byval svreg as IRVREG ptr _
2555  ) static
2556 
2557  dim as string dst, src, aux
2558  dim as string ostr
2559 
2560  hPrepOperand( dvreg, dst )
2561  hPrepOperand( svreg, src )
2562 
2563  if( (svreg->typ = IR_VREGTYPE_REG) or (svreg->typ = IR_VREGTYPE_IMM) ) then
2564 
2565  '' signed?
2566  if( typeIsSigned( svreg->dtype ) ) then
2567 
2568  hPrepOperand64( svreg, src, aux )
2569 
2570  hPUSH( aux )
2571  hPUSH( src )
2572 
2573  ostr = "fild " + dtypeTB(svreg->dtype).mname + " [esp]"
2574  outp ostr
2575 
2576  outp "add esp, 8"
2577 
2578  '' unsigned, try a bigger type..
2579  else
2580 
2581  hPrepOperand64( svreg, src, aux )
2582  hPUSH aux
2583  hPUSH src
2584  outp "fild qword ptr [esp]"
2585  outp "add esp, 8"
2586  hULONG2DBL( svreg )
2587 
2588  end if
2589 
2590  '' not a reg or imm
2591  else
2592 
2593  '' signed?
2594  if( typeIsSigned( svreg->dtype ) ) then
2595  ostr = "fild " + src
2596  outp ostr
2597 
2598  '' unsigned, try a bigger type..
2599  else
2600  ostr = "fild " + src
2601  outp ostr
2602  hULONG2DBL( svreg )
2603 
2604  end if
2605 
2606  end if
2607 
2608 end sub
2609 
2610 
2611 
2612 '':::::
2613 sub _emitLOADI2F _
2614  ( _
2615  byval dvreg as IRVREG ptr, _
2616  byval svreg as IRVREG ptr _
2617  ) static
2618 
2619  dim as string dst, src
2620  dim as integer sdsize
2621  dim as string ostr
2622 
2623  hPrepOperand( dvreg, dst )
2624  hPrepOperand( svreg, src )
2625 
2626  sdsize = typeGetSize( svreg->dtype )
2627 
2628  '' byte source? damn..
2629  if( sdsize = 1 ) then
2630  dim as string aux
2631  dim as integer isfree, reg
2632 
2633  reg = hFindRegNotInVreg( svreg )
2634 
2635  aux = *hGetRegName( FB_DATATYPE_INTEGER, reg )
2636 
2637  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
2638 
2639  if( isfree = FALSE ) then
2640  hPUSH aux
2641  end if
2642 
2643  if( typeIsSigned( svreg->dtype ) ) then
2644  ostr = "movsx " + aux + COMMA + src
2645  outp ostr
2646  else
2647  ostr = "movzx " + aux + COMMA + src
2648  outp ostr
2649  end if
2650 
2651  hPUSH aux
2652  outp "fild dword ptr [esp]"
2653  outp "add esp, 4"
2654 
2655  if( isfree = FALSE ) then
2656  hPOP aux
2657  end if
2658 
2659  exit sub
2660  end if
2661 
2662  ''
2663  if( (svreg->typ = IR_VREGTYPE_REG) or (svreg->typ = IR_VREGTYPE_IMM) ) then
2664 
2665  '' signed?
2666  if( typeIsSigned( svreg->dtype ) ) then
2667 
2668  '' not an integer? make it
2669  if( (svreg->typ = IR_VREGTYPE_REG) and (sdsize < 4) ) then
2670  src = *hGetRegName( FB_DATATYPE_INTEGER, svreg->reg )
2671  end if
2672 
2673  hPUSH src
2674 
2675  ostr = "fild " + dtypeTB(svreg->dtype).mname + " [esp]"
2676  outp ostr
2677 
2678  outp "add esp, 4"
2679 
2680  '' unsigned, try a bigger type..
2681  else
2682 
2683  '' uint?
2684  if( sdsize = 4 ) then
2685  hPUSH "0"
2686  hPUSH src
2687  outp "fild qword ptr [esp]"
2688  outp "add esp, 8"
2689 
2690  '' ushort..
2691  else
2692  if( svreg->typ <> IR_VREGTYPE_IMM ) then
2693  hPUSH "0"
2694  end if
2695 
2696  hPUSH src
2697  outp "fild dword ptr [esp]"
2698 
2699  if( svreg->typ <> IR_VREGTYPE_IMM ) then
2700  outp "add esp, 6"
2701  else
2702  outp "add esp, 4"
2703  end if
2704  end if
2705 
2706  end if
2707 
2708  '' not a reg or imm
2709  else
2710 
2711  '' signed?
2712  if( typeIsSigned( svreg->dtype ) ) then
2713  ostr = "fild " + src
2714  outp ostr
2715 
2716  '' unsigned, try a bigger type..
2717  else
2718  '' uint..
2719  if( sdsize = 4 ) then
2720  hPUSH "0"
2721  hPUSH src
2722  outp "fild qword ptr [esp]"
2723  outp "add esp, 8"
2724 
2725  '' ushort..
2726  else
2727  hPUSH "0"
2728  hPUSH src
2729  outp "fild dword ptr [esp]"
2730  outp "add esp, 6"
2731  end if
2732  end if
2733 
2734  end if
2735 
2736 end sub
2737 
2738 
2739 
2740 '':::::
2741 sub _emitLOADF2F _
2742  ( _
2743  byval dvreg as IRVREG ptr, _
2744  byval svreg as IRVREG ptr _
2745  ) static
2746 
2747  dim as string src
2748  dim as string ostr
2749 
2750  hPrepOperand( svreg, src )
2751 
2752  ostr = "fld " + src
2753  outp ostr
2754 
2755 end sub
2756 
2757 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
2758 '' binary ops
2759 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
2760 
2761 '':::::
2762 sub _emitMOVL _
2763  ( _
2764  byval dvreg as IRVREG ptr, _
2765  byval svreg as IRVREG ptr _
2766  ) static
2767 
2768  dim as string dst1, dst2, src1, src2, ostr
2769 
2770  hPrepOperand64( dvreg, dst1, dst2 )
2771  hPrepOperand64( svreg, src1, src2 )
2772 
2773  ostr = "mov " + dst1 + COMMA + src1
2774  outp ostr
2775 
2776  ostr = "mov " + dst2 + COMMA + src2
2777  outp ostr
2778 
2779 end sub
2780 
2781 '':::::
2782 sub _emitMOVI _
2783  ( _
2784  byval dvreg as IRVREG ptr, _
2785  byval svreg as IRVREG ptr _
2786  ) static
2787 
2788  dim as string dst, src, ostr
2789 
2790  '' byte? handle SI, DI used as bytes..
2791  if( typeGetSize( dvreg->dtype ) = 1 ) then
2792  '' MOV is only used when both operands are registers
2793  dst = *hGetRegName( FB_DATATYPE_INTEGER, dvreg->reg )
2794  src = *hGetRegName( FB_DATATYPE_INTEGER, svreg->reg )
2795  else
2796  hPrepOperand( dvreg, dst )
2797  hPrepOperand( svreg, src )
2798  end if
2799 
2800  ostr = "mov " + dst + COMMA + src
2801  outp ostr
2802 
2803 end sub
2804 
2805 
2806 '':::::
2807 sub _emitMOVF _
2808  ( _
2809  byval dvreg as IRVREG ptr, _
2810  byval svreg as IRVREG ptr _
2811  ) static
2812 
2813  '' do nothing, both are regs
2814 
2815 end sub
2816 
2817 '':::::
2818 sub _emitADDL _
2819  ( _
2820  byval dvreg as IRVREG ptr, _
2821  byval svreg as IRVREG ptr _
2822  ) static
2823 
2824  dim dst1 as string, dst2 as string, src1 as string, src2 as string
2825  dim ostr as string
2826 
2827  hPrepOperand64( dvreg, dst1, dst2 )
2828  hPrepOperand64( svreg, src1, src2 )
2829 
2830  ostr = "add " + dst1 + COMMA + src1
2831  outp ostr
2832 
2833  ostr = "adc " + dst2 + COMMA + src2
2834  outp ostr
2835 
2836 end sub
2837 
2838 '':::::
2839 sub _emitADDI _
2840  ( _
2841  byval dvreg as IRVREG ptr, _
2842  byval svreg as IRVREG ptr _
2843  ) static
2844 
2845  dim dst as string, src as string
2846  dim doinc as integer, dodec as integer
2847  dim ostr as string
2848 
2849  hPrepOperand( dvreg, dst )
2850  hPrepOperand( svreg, src )
2851 
2852  doinc = FALSE
2853  dodec = FALSE
2854  if( svreg->typ = IR_VREGTYPE_IMM ) then
2855  select case svreg->value.i
2856  case 1
2857  doinc = TRUE
2858  case -1
2859  dodec = TRUE
2860  end select
2861  end if
2862 
2863  if( doinc ) then
2864  ostr = "inc " + dst
2865  outp ostr
2866  elseif( dodec ) then
2867  ostr = "dec " + dst
2868  outp ostr
2869  else
2870  ostr = "add " + dst + COMMA + src
2871  outp ostr
2872  end if
2873 
2874 end sub
2875 
2876 
2877 
2878 '':::::
2879 sub _emitADDF _
2880  ( _
2881  byval dvreg as IRVREG ptr, _
2882  byval svreg as IRVREG ptr _
2883  ) static
2884 
2885  dim src as string
2886  dim ostr as string
2887 
2888  hPrepOperand( svreg, src )
2889 
2890  if( svreg->typ = IR_VREGTYPE_REG ) then
2891  ostr = "faddp"
2892  outp ostr
2893  else
2894  if( typeGetClass( svreg->dtype ) = FB_DATACLASS_FPOINT ) then
2895  ostr = "fadd " + src
2896  outp ostr
2897  else
2898  '' Relying on hDoOptRemConv()
2899  assert( (typeGetSize( svreg->dtype ) = 2) or (typeGetSize( svreg->dtype ) = 4) )
2900  ostr = "fiadd " + src
2901  outp ostr
2902  end if
2903  end if
2904 
2905 end sub
2906 
2907 '':::::
2908 sub _emitSUBL _
2909  ( _
2910  byval dvreg as IRVREG ptr, _
2911  byval svreg as IRVREG ptr _
2912  ) static
2913 
2914  dim dst1 as string, dst2 as string, src1 as string, src2 as string
2915  dim ostr as string
2916 
2917  hPrepOperand64( dvreg, dst1, dst2 )
2918  hPrepOperand64( svreg, src1, src2 )
2919 
2920  ostr = "sub " + dst1 + COMMA + src1
2921  outp ostr
2922 
2923  ostr = "sbb " + dst2 + COMMA + src2
2924  outp ostr
2925 
2926 end sub
2927 
2928 '':::::
2929 sub _emitSUBI _
2930  ( _
2931  byval dvreg as IRVREG ptr, _
2932  byval svreg as IRVREG ptr _
2933  ) static
2934 
2935  dim dst as string, src as string
2936  dim doinc as integer, dodec as integer
2937  dim ostr as string
2938 
2939  hPrepOperand( dvreg, dst )
2940  hPrepOperand( svreg, src )
2941 
2942  doinc = FALSE
2943  dodec = FALSE
2944  if( svreg->typ = IR_VREGTYPE_IMM ) then
2945  select case svreg->value.i
2946  case 1
2947  dodec = TRUE
2948  case -1
2949  doinc = TRUE
2950  end select
2951  end if
2952 
2953  if( dodec ) then
2954  ostr = "dec " + dst
2955  outp ostr
2956  elseif( doinc ) then
2957  ostr = "inc " + dst
2958  outp ostr
2959  else
2960  ostr = "sub " + dst + COMMA + src
2961  outp ostr
2962  end if
2963 
2964 end sub
2965 
2966 
2967 
2968 '':::::
2969 sub _emitSUBF _
2970  ( _
2971  byval dvreg as IRVREG ptr, _
2972  byval svreg as IRVREG ptr _
2973  ) static
2974 
2975  dim src as string
2976  dim doinc as integer, dodec as integer
2977  dim ostr as string
2978 
2979  hPrepOperand( svreg, src )
2980 
2981  if( svreg->typ = IR_VREGTYPE_REG ) then
2982  outp "fsubrp"
2983  else
2984  if( typeGetClass( svreg->dtype ) = FB_DATACLASS_FPOINT ) then
2985  ostr = "fsub " + src
2986  outp ostr
2987  else
2988  '' Relying on hDoOptRemConv()
2989  assert( (typeGetSize( svreg->dtype ) = 2) or (typeGetSize( svreg->dtype ) = 4) )
2990  ostr = "fisub " + src
2991  outp ostr
2992  end if
2993  end if
2994 
2995 end sub
2996 
2997 '':::::
2998 sub _emitMULL _
2999  ( _
3000  byval dvreg as IRVREG ptr, _
3001  byval svreg as IRVREG ptr _
3002  ) static
3003 
3004  dim dst1 as string, dst2 as string, src1 as string, src2 as string
3005  dim iseaxfree as integer, isedxfree as integer
3006  dim eaxindest as integer, edxindest as integer
3007  dim ofs as integer
3008 
3009  hPrepOperand64( dvreg, dst1, dst2 )
3010  hPrepOperand64( svreg, src1, src2 )
3011 
3012  iseaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
3013  isedxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDX )
3014 
3015  eaxindest = hIsRegInVreg( dvreg, EMIT_REG_EAX )
3016  edxindest = hIsRegInVreg( dvreg, EMIT_REG_EDX )
3017 
3018  hPUSH( src2 )
3019  hPUSH( src1 )
3020  hPUSH( dst2 )
3021  hPUSH( dst1 )
3022 
3023  ofs = 0
3024 
3025  if( edxindest ) then
3026  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3027  ofs += 4
3028  hPUSH( "edx" )
3029  end if
3030  else
3031  if( isedxfree = FALSE ) then
3032  ofs += 4
3033  hPUSH( "edx" )
3034  end if
3035  end if
3036 
3037  if( eaxindest ) then
3038  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3039  ofs += 4
3040  hPUSH "eax"
3041  end if
3042  else
3043  if( iseaxfree = FALSE ) then
3044  ofs += 4
3045  hPUSH "eax"
3046  end if
3047  end if
3048 
3049  '' res = low(dst) * low(src)
3050  outp "mov eax, [esp+" + str( 0+ofs ) + "]"
3051  outp "mul dword ptr [esp+" + str( 8+ofs ) + "]"
3052 
3053  '' hres= low(dst) * high(src) + high(res)
3054  outp "xchg eax, [esp+" + str ( 0+ofs ) + "]"
3055 
3056  outp "imul eax, [esp+" + str ( 12+ofs ) + "]"
3057  outp "add eax, edx"
3058 
3059  '' hres += high(dst) * low(src)
3060  outp "mov edx, [esp+" + str( 4+ofs ) + "]"
3061  outp "imul edx, [esp+" + str( 8+ofs ) + "]"
3062  outp "add edx, eax"
3063  outp "mov [esp+" + str( 4+ofs ) + "], edx"
3064 
3065  if( eaxindest ) then
3066  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3067  hPOP "eax"
3068  end if
3069  else
3070  if( iseaxfree = FALSE ) then
3071  hPOP "eax"
3072  end if
3073  end if
3074 
3075  if( edxindest ) then
3076  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3077  hPOP "edx"
3078  end if
3079  else
3080  if( isedxfree = FALSE ) then
3081  hPOP "edx"
3082  end if
3083  end if
3084 
3085  '' low(dst) = low(res)
3086  hPOP dst1
3087  '' high(dst) = hres
3088  hPOP dst2
3089 
3090  outp "add esp, 8"
3091 
3092  '' code:
3093  '' mov eax, low(dst)
3094  '' mul low(src)
3095  '' mov ebx, low(dst)
3096  '' imul ebx, high(src)
3097  '' add ebx, edx
3098  '' mov edx, high(dst)
3099  '' imul edx, low(src)
3100  '' add edx, ebx
3101  '' mov low(dst), eax
3102  '' mov high(dst), edx
3103 
3104 end sub
3105 
3106 '':::::
3107 sub _emitMULI _
3108  ( _
3109  byval dvreg as IRVREG ptr, _
3110  byval svreg as IRVREG ptr _
3111  ) static
3112 
3113  dim reg as integer, isfree as integer, rname as string
3114  dim ostr as string
3115  dim dst as string, src as string
3116 
3117  hPrepOperand( dvreg, dst )
3118  hPrepOperand( svreg, src )
3119 
3120  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3121 
3122  reg = hFindRegNotInVreg( svreg )
3123  rname = *hGetRegName( svreg->dtype, reg )
3124 
3125  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
3126 
3127  if( isfree = FALSE ) then
3128  hPUSH rname
3129  end if
3130 
3131  hMOV rname, dst
3132  ostr = "imul " + rname + COMMA + src
3133  outp ostr
3134  hMOV dst, rname
3135 
3136  if( isfree = FALSE ) then
3137  hPOP rname
3138  end if
3139 
3140  else
3141  ostr = "imul " + dst + COMMA + src
3142  outp ostr
3143  end if
3144 
3145 end sub
3146 
3147 
3148 
3149 '':::::
3150 sub _emitMULF _
3151  ( _
3152  byval dvreg as IRVREG ptr, _
3153  byval svreg as IRVREG ptr _
3154  ) static
3155 
3156  dim src as string
3157  dim ostr as string
3158 
3159  hPrepOperand( svreg, src )
3160 
3161  if( svreg->typ = IR_VREGTYPE_REG ) then
3162  outp "fmulp"
3163  else
3164  if( typeGetClass( svreg->dtype ) = FB_DATACLASS_FPOINT ) then
3165  ostr = "fmul " + src
3166  outp ostr
3167  else
3168  '' Relying on hDoOptRemConv()
3169  assert( (typeGetSize( svreg->dtype ) = 2) or (typeGetSize( svreg->dtype ) = 4) )
3170  ostr = "fimul " + src
3171  outp ostr
3172  end if
3173  end if
3174 
3175 end sub
3176 
3177 
3178 
3179 '':::::
3180 sub _emitDIVF _
3181  ( _
3182  byval dvreg as IRVREG ptr, _
3183  byval svreg as IRVREG ptr _
3184  ) static
3185 
3186  dim src as string
3187  dim ostr as string
3188 
3189  hPrepOperand( svreg, src )
3190 
3191  if( svreg->typ = IR_VREGTYPE_REG ) then
3192  outp "fdivrp"
3193  else
3194  if( typeGetClass( svreg->dtype ) = FB_DATACLASS_FPOINT ) then
3195  ostr = "fdiv " + src
3196  outp ostr
3197  else
3198  '' Relying on hDoOptRemConv()
3199  assert( (typeGetSize( svreg->dtype ) = 2) or (typeGetSize( svreg->dtype ) = 4) )
3200  ostr = "fidiv " + src
3201  outp ostr
3202  end if
3203  end if
3204 
3205 end sub
3206 
3207 '':::::
3208 sub _emitDIVI _
3209  ( _
3210  byval dvreg as IRVREG ptr, _
3211  byval svreg as IRVREG ptr _
3212  ) static
3213 
3214  dim as string dst, src
3215  dim as integer ecxtrashed
3216  dim as integer eaxfree, ecxfree, edxfree
3217  dim as integer eaxindest, ecxindest, edxindest
3218  dim as integer eaxinsource, edxinsource
3219  dim as string eax, ecx, edx
3220  dim as string ostr
3221 
3222  hPrepOperand( dvreg, dst )
3223  hPrepOperand( svreg, src )
3224 
3225  if( typeGetSize( dvreg->dtype ) = 4 ) then
3226  eax = "eax"
3227  ecx = "ecx"
3228  edx = "edx"
3229  else
3230  eax = "ax"
3231  ecx = "cx"
3232  edx = "dx"
3233  end if
3234 
3235  ecxtrashed = FALSE
3236 
3237  eaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
3238  ecxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ECX )
3239  edxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDX )
3240 
3241  eaxinsource = hIsRegInVreg( svreg, EMIT_REG_EAX )
3242  edxinsource = hIsRegInVreg( svreg, EMIT_REG_EDX )
3243  eaxindest = hIsRegInVreg( dvreg, EMIT_REG_EAX )
3244  edxindest = hIsRegInVreg( dvreg, EMIT_REG_EDX )
3245  ecxindest = hIsRegInVreg( dvreg, EMIT_REG_ECX )
3246 
3247  if( (eaxinsource) or (edxinsource) or (svreg->typ = IR_VREGTYPE_IMM) ) then
3248  ecxtrashed = TRUE
3249  if( ecxindest ) then
3250  hPUSH( "ecx" )
3251  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3252  hPrepOperand( dvreg, ostr, FB_DATATYPE_INTEGER )
3253  hPUSH( ostr )
3254  end if
3255  elseif( ecxfree = FALSE ) then
3256  hPUSH( "ecx" )
3257  end if
3258  hMOV( ecx, src )
3259  src = ecx
3260  end if
3261 
3262  if( eaxindest = FALSE ) then
3263  if( (ecxindest) and (ecxtrashed) ) then
3264  if( eaxfree = FALSE ) then
3265  outp "xchg eax, [esp]"
3266  else
3267  hPOP "eax"
3268  end if
3269  else
3270  if( eaxfree = FALSE ) then
3271  hPUSH "eax"
3272  end if
3273  hMOV eax, dst
3274  end if
3275 
3276  else
3277  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3278  hPUSH "eax"
3279  hMOV eax, dst
3280  end if
3281  end if
3282 
3283  if( edxindest ) then
3284  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3285  hPUSH "edx"
3286  end if
3287  elseif( edxfree = FALSE ) then
3288  hPUSH "edx"
3289  end if
3290 
3291  if( typeIsSigned( dvreg->dtype ) ) then
3292  if( typeGetSize( dvreg->dtype ) = 4 ) then
3293  outp "cdq"
3294  else
3295  outp "cwd"
3296  end if
3297 
3298  ostr = "idiv " + src
3299  outp ostr
3300 
3301  else
3302  ostr = "xor " + edx + ", " + edx
3303  outp ostr
3304 
3305  ostr = "div " + src
3306  outp ostr
3307  end if
3308 
3309  if( edxindest ) then
3310  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3311  hPOP "edx"
3312  end if
3313  elseif( edxfree = FALSE ) then
3314  hPOP "edx"
3315  end if
3316 
3317  if( eaxindest = FALSE ) then
3318  if( ecxindest and ecxtrashed ) then
3319  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3320  if( eaxfree = FALSE ) then
3321  hPOP "ecx" '' ecx= tos (eax)
3322  outp "xchg ecx, [esp]" '' tos= ecx; ecx= dst
3323  else
3324  hPOP "ecx" '' ecx= tos (ecx)
3325  end if
3326  end if
3327  end if
3328 
3329  hMOV dst, eax
3330 
3331  if( eaxfree = FALSE ) then
3332  hPOP "eax"
3333  end if
3334 
3335  else
3336  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3337  if( (ecxfree = FALSE) and (ecxtrashed = FALSE) ) then
3338  outp "xchg ecx, [esp]" '' tos= ecx; ecx= dst
3339  outp "xchg ecx, eax" '' ecx= res; eax= dst
3340  else
3341  hMOV "ecx", "eax" '' ecx= eax
3342  hPOP "eax" '' restore eax
3343  end if
3344 
3345  hMOV dst, ecx '' [eax+...] = ecx
3346 
3347  if( (ecxfree = FALSE) and (ecxtrashed = FALSE) ) then
3348  hPOP "ecx"
3349  end if
3350  end if
3351  end if
3352 
3353  if( ecxtrashed ) then
3354  if( (ecxfree = FALSE) and (ecxindest = FALSE) ) then
3355  hPOP "ecx"
3356  end if
3357  end if
3358 
3359 end sub
3360 
3361 '':::::
3362 sub _emitMODI _
3363  ( _
3364  byval dvreg as IRVREG ptr, _
3365  byval svreg as IRVREG ptr _
3366  ) static
3367 
3368  dim as string dst, src
3369  dim as integer ecxtrashed
3370  dim as integer eaxfree, ecxfree, edxfree
3371  dim as integer eaxindest, ecxindest, edxindest
3372  dim as integer eaxinsource, edxinsource
3373  dim as string eax, ecx, edx
3374  dim as string ostr
3375 
3376  hPrepOperand( dvreg, dst )
3377  hPrepOperand( svreg, src )
3378 
3379  if( typeGetSize( dvreg->dtype ) = 4 ) then
3380  eax = "eax"
3381  ecx = "ecx"
3382  edx = "edx"
3383  else
3384  eax = "ax"
3385  ecx = "cx"
3386  edx = "dx"
3387  end if
3388 
3389  ecxtrashed = FALSE
3390 
3391  eaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
3392  ecxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ECX )
3393  edxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDX )
3394 
3395  eaxinsource = hIsRegInVreg( svreg, EMIT_REG_EAX )
3396  edxinsource = hIsRegInVreg( svreg, EMIT_REG_EDX )
3397  eaxindest = hIsRegInVreg( dvreg, EMIT_REG_EAX )
3398  edxindest = hIsRegInVreg( dvreg, EMIT_REG_EDX )
3399  ecxindest = hIsRegInVreg( dvreg, EMIT_REG_ECX )
3400 
3401  if( (eaxinsource) or (edxinsource) or (svreg->typ = IR_VREGTYPE_IMM) ) then
3402  ecxtrashed = TRUE
3403  if( ecxindest ) then
3404  hPUSH( "ecx" )
3405  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3406  hPrepOperand( dvreg, ostr, FB_DATATYPE_INTEGER )
3407  hPUSH( ostr )
3408  end if
3409  elseif( ecxfree = FALSE ) then
3410  hPUSH( "ecx" )
3411  end if
3412  hMOV( ecx, src )
3413  src = ecx
3414  end if
3415 
3416  if( eaxindest = FALSE ) then
3417  if( (ecxindest) and (ecxtrashed) ) then
3418  if( eaxfree = FALSE ) then
3419  outp "xchg eax, [esp]"
3420  else
3421  hPOP "eax"
3422  end if
3423  else
3424  if( eaxfree = FALSE ) then
3425  hPUSH "eax"
3426  end if
3427  hMOV eax, dst
3428  end if
3429 
3430  else
3431  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3432  hPUSH "eax"
3433  hMOV eax, dst
3434  end if
3435  end if
3436 
3437  if( edxindest ) then
3438  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3439  hPUSH "edx"
3440  end if
3441  elseif( edxfree = FALSE ) then
3442  hPUSH "edx"
3443  end if
3444 
3445  if( typeIsSigned( dvreg->dtype ) ) then
3446  if( typeGetSize( dvreg->dtype ) = 4 ) then
3447  outp "cdq"
3448  else
3449  outp "cwd"
3450  end if
3451 
3452  ostr = "idiv " + src
3453  outp ostr
3454 
3455  else
3456  ostr = "xor " + edx + ", " + edx
3457  outp ostr
3458 
3459  ostr = "div " + src
3460  outp ostr
3461  end if
3462 
3463  hMOV eax, edx
3464 
3465  if( edxindest ) then
3466  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3467  hPOP "edx"
3468  end if
3469  elseif( edxfree = FALSE ) then
3470  hPOP "edx"
3471  end if
3472 
3473  if( eaxindest = FALSE ) then
3474  if( ecxindest and ecxtrashed ) then
3475  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3476  if( eaxfree = FALSE ) then
3477  hPOP "ecx" '' ecx= tos (eax)
3478  outp "xchg ecx, [esp]" '' tos= ecx; ecx= dst
3479  else
3480  hPOP "ecx" '' ecx= tos (ecx)
3481  end if
3482  end if
3483  end if
3484 
3485  hMOV dst, eax
3486 
3487  if( eaxfree = FALSE ) then
3488  hPOP "eax"
3489  end if
3490 
3491  else
3492  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3493  if( (ecxfree = FALSE) and (ecxtrashed = FALSE) ) then
3494  outp "xchg ecx, [esp]" '' tos= ecx; ecx= dst
3495  outp "xchg ecx, eax" '' ecx= res; eax= dst
3496  else
3497  hMOV "ecx", "eax" '' ecx= eax
3498  hPOP "eax" '' restore eax
3499  end if
3500 
3501  hMOV dst, ecx '' [eax+...] = ecx
3502 
3503  if( (ecxfree = FALSE) and (ecxtrashed = FALSE) ) then
3504  hPOP "ecx"
3505  end if
3506  end if
3507  end if
3508 
3509  if( ecxtrashed ) then
3510  if( (ecxfree = FALSE) and (ecxindest = FALSE) ) then
3511  hPOP "ecx"
3512  end if
3513  end if
3514 
3515 end sub
3516 
3517 '':::::
3518 sub hSHIFTL _
3519  ( _
3520  byval op as integer, _
3521  byval dvreg as IRVREG ptr, _
3522  byval svreg as IRVREG ptr _
3523  ) static
3524 
3525  dim as string dst1, dst2, src, label, mnemonic32, mnemonic64
3526  dim as integer tmpreg, tmpisfree
3527  dim as string tmpregname
3528  dim as string a, b
3529  dim as IRVREG ptr av, bv
3530 
3531  ''
3532  if( op = AST_OP_SHL ) then
3533  '' x86 shl and sar are the same
3534  mnemonic32 = "shl "
3535  mnemonic64 = "shld "
3536  else
3537  if( typeIsSigned( dvreg->dtype ) ) then
3538  mnemonic32 = "sar "
3539  else
3540  mnemonic32 = "shr "
3541  end if
3542  mnemonic64 = "shrd "
3543  end if
3544 
3545  ''
3546  hPrepOperand64( dvreg, dst1, dst2 )
3547  hPrepOperand( svreg, src, FB_DATATYPE_INTEGER )
3548 
3549  if( op = AST_OP_SHL ) then
3550  a = dst2
3551  av = dvreg->vaux
3552  b = dst1
3553  bv = dvreg
3554  else '' SHR
3555  a = dst1
3556  av = dvreg
3557  b = dst2
3558  bv = dvreg->vaux
3559  end if
3560 
3561  if( svreg->typ = IR_VREGTYPE_IMM ) then
3562  if( svreg->value.i >= 64 ) then
3563  '' zero both result halves
3564  if( bv->typ = IR_VREGTYPE_REG ) then
3565  outp "xor " + b + ", " + b
3566  else
3567  outp "mov " + b + ", 0"
3568  end if
3569 
3570  if( av->typ = IR_VREGTYPE_REG ) then
3571  outp "xor " + a + ", " + a
3572  else
3573  outp "mov " + a + ", 0"
3574  end if
3575  elseif( svreg->value.i >= 32 ) then
3576  tmpisfree = TRUE
3577  if( (bv->typ = IR_VREGTYPE_REG) or (av->typ = IR_VREGTYPE_REG) ) then
3578  '' a or b is a reg
3579  outp "mov " + a + ", " + b
3580  else
3581  '' neither is a reg; get a temp
3582  tmpreg = hFindFreeReg( FB_DATACLASS_INTEGER )
3583  if( tmpreg = INVALID ) then
3584  '' Can only use a temp reg that isn't used in the dest vreg,
3585  '' because the code generated below doesn't handle that case.
3586  tmpreg = hFindRegNotInVreg( dvreg )
3587  tmpisfree = FALSE
3588  end if
3589  tmpregname = *hGetRegName( FB_DATATYPE_INTEGER, tmpreg )
3590  if( tmpisfree = FALSE ) then
3591  hPUSH( tmpregname )
3592  end if
3593  outp "mov " + tmpregname + ", " + b
3594  outp "mov " + a + ", " + tmpregname
3595  end if
3596 
3597  if( (op = AST_OP_SHR) and typeIsSigned( dvreg->dtype ) ) then
3598  outp "sar " + b +", 31"
3599  elseif( bv->typ = IR_VREGTYPE_REG ) then
3600  outp "xor " + b + ", " + b
3601  else
3602  outp "mov " + b + ", 0"
3603  end if
3604 
3605  if( svreg->value.i > 32 ) then
3606  src = str( svreg->value.i - 32 )
3607  outp mnemonic32 + a + ", " + src
3608  end if
3609 
3610  if( tmpisfree = FALSE ) then
3611  hPOP( tmpregname )
3612  end if
3613 
3614  else '' src < 32
3615  if( bv->typ = IR_VREGTYPE_REG ) then
3616  outp mnemonic64 + a + ", " + b + ", " + src
3617  outp mnemonic32 + b + ", " + src
3618  elseif( av->typ = IR_VREGTYPE_REG ) then
3619  outp "xchg " + a + ", " + b
3620  outp mnemonic64 + b + ", " + a + ", " + src
3621  outp mnemonic32 + a + ", " + src
3622  outp "xchg " + a + ", " + b
3623  else
3624  tmpreg = hFindFreeReg( FB_DATACLASS_INTEGER )
3625  if( tmpreg = INVALID ) then
3626  '' Can only use a temp reg that isn't used in the dest vreg,
3627  '' because the code generated below doesn't handle that case.
3628  tmpreg = hFindRegNotInVreg( dvreg )
3629  tmpisfree = FALSE
3630  else
3631  tmpisfree = TRUE
3632  end if
3633  tmpregname = *hGetRegName( FB_DATATYPE_INTEGER, tmpreg )
3634  if( tmpisfree = FALSE ) then
3635  hPUSH( tmpregname )
3636  end if
3637  outp "mov " + tmpregname + ", " + b
3638  outp mnemonic64 + a + ", " + tmpregname + ", " + src
3639  outp mnemonic32 + tmpregname + ", " + src
3640  outp "mov " + b + ", " + tmpregname
3641  if( tmpisfree = FALSE ) then
3642  hPOP( "eax" )
3643  end if
3644  end if
3645  end if
3646  else
3647  '' if src is not an imm, use cl and check for the x86 glitches
3648 
3649  dim as integer iseaxfree, isedxfree, isecxfree
3650  dim as integer eaxindest, edxindest, ecxindest
3651  dim as integer ofs
3652 
3653  label = *symbUniqueLabel( )
3654 
3655  hPUSH( dst2 )
3656  hPUSH( dst1 )
3657  ofs = 0
3658 
3659  iseaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
3660  isedxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDX )
3661  isecxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ECX )
3662 
3663  eaxindest = hIsRegInVreg( dvreg, EMIT_REG_EAX )
3664  edxindest = hIsRegInVreg( dvreg, EMIT_REG_EDX )
3665  ecxindest = hIsRegInVreg( dvreg, EMIT_REG_ECX )
3666 
3667  if( (svreg->typ <> IR_VREGTYPE_REG) or (svreg->reg <> EMIT_REG_ECX) ) then
3668  '' handle src < dword
3669  if( typeGetSize( svreg->dtype ) <> 4 ) then
3670  '' if it's not a reg, the right size was already set at the hPrepOperand() above
3671  if( svreg->typ = IR_VREGTYPE_REG ) then
3672  src = *hGetRegName( FB_DATATYPE_INTEGER, svreg->reg )
3673  end if
3674  end if
3675 
3676  if( isecxfree = FALSE ) then
3677  if( ecxindest and dvreg->typ = IR_VREGTYPE_REG ) then
3678  hMOV( "ecx", src )
3679  isecxfree = TRUE
3680  else
3681  hPUSH( src )
3682  outp "xchg ecx, [esp]"
3683  ofs += 4
3684  end if
3685  else
3686  hMOV( "ecx", src )
3687  end if
3688  else
3689  isecxfree = TRUE
3690  end if
3691 
3692  '' load dst1 to eax
3693  if( eaxindest ) then
3694  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3695  outp "xchg eax, [esp+" + str( ofs+0 ) + "]"
3696  else
3697  outp "mov eax, [esp+" + str( ofs+0 ) + "]"
3698  end if
3699  else
3700  if( iseaxfree = FALSE ) then
3701  outp "xchg eax, [esp+" + str( ofs+0 ) + "]"
3702  else
3703  outp "mov eax, [esp+" + str( ofs+0 ) + "]"
3704  end if
3705  end if
3706 
3707  '' load dst2 to edx
3708  if( edxindest ) then
3709  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3710  outp "xchg edx, [esp+" + str( ofs+4 ) + "]"
3711  else
3712  outp "mov edx, [esp+" + str( ofs+4 ) + "]"
3713  end if
3714  else
3715  if( isedxfree = FALSE ) then
3716  outp "xchg edx, [esp+" + str( ofs+4 ) + "]"
3717  else
3718  outp "mov edx, [esp+" + str( ofs+4 ) + "]"
3719  end if
3720  end if
3721 
3722  if( op = AST_OP_SHL ) then
3723  outp "shld edx, eax, cl"
3724  outp mnemonic32 + " eax, cl"
3725  else
3726  outp "shrd eax, edx, cl"
3727  outp mnemonic32 + " edx, cl"
3728  end if
3729 
3730  outp "test cl, 32"
3731  hBRANCH( "jz", label )
3732 
3733  if( op = AST_OP_SHL ) then
3734  outp "mov edx, eax"
3735  outp "xor eax, eax"
3736  else
3737  outp "mov eax, edx"
3738  if( typeIsSigned( dvreg->dtype ) ) then
3739  outp "sar edx, 31"
3740  else
3741  outp "xor edx, edx"
3742  end if
3743  end if
3744 
3745  hLABEL( label )
3746 
3747  if( isecxfree = FALSE ) then
3748  hPOP "ecx"
3749  end if
3750 
3751  '' save dst2
3752  if( edxindest ) then
3753  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3754  outp "xchg edx, [esp+4]"
3755  else
3756  outp "mov [esp+4], edx"
3757  end if
3758  else
3759  if( isedxfree = FALSE ) then
3760  outp "xchg edx, [esp+4]"
3761  else
3762  outp "mov [esp+4], edx"
3763  end if
3764  end if
3765 
3766  '' save dst1
3767  if( eaxindest ) then
3768  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3769  outp "xchg eax, [esp+0]"
3770  else
3771  outp "mov [esp+0], eax"
3772  end if
3773  else
3774  if( iseaxfree = FALSE ) then
3775  outp "xchg eax, [esp+0]"
3776  else
3777  outp "mov [esp+0], eax"
3778  end if
3779  end if
3780 
3781  hPOP( dst1 )
3782  hPOP( dst2 )
3783  end if
3784 
3785 end sub
3786 
3787 '':::::
3788 sub hSHIFTI _
3789  ( _
3790  byval op as integer, _
3791  byval dvreg as IRVREG ptr, _
3792  byval svreg as IRVREG ptr _
3793  ) static
3794 
3795  dim eaxpreserved as integer, ecxpreserved as integer
3796  dim eaxfree as integer, ecxfree as integer
3797  dim reg as integer
3798  dim ecxindest as integer
3799  dim as string ostr, dst, src, tmp, mnemonic
3800 
3801  ''
3802  if( typeIsSigned( dvreg->dtype ) ) then
3803  if( op = AST_OP_SHL ) then
3804  mnemonic = "sal"
3805  else
3806  mnemonic = "sar"
3807  end if
3808  else
3809  if( op = AST_OP_SHL ) then
3810  mnemonic = "shl"
3811  else
3812  mnemonic = "shr"
3813  end if
3814  end if
3815 
3816  ''
3817  hPrepOperand( dvreg, dst )
3818 
3819  ecxindest = FALSE
3820  eaxpreserved = FALSE
3821  ecxpreserved = FALSE
3822 
3823  if( svreg->typ = IR_VREGTYPE_IMM ) then
3824  hPrepOperand( svreg, src )
3825  tmp = dst
3826 
3827  else
3828  eaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
3829  ecxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ECX )
3830 
3831  if( svreg->typ = IR_VREGTYPE_REG ) then
3832  reg = svreg->reg
3833  else
3834  reg = INVALID
3835  end if
3836 
3837  ecxindest = hIsRegInVreg( dvreg, EMIT_REG_ECX )
3838 
3839  '' ecx in destine?
3840  if( ecxindest ) then
3841  '' preserve
3842  hPUSH "ecx"
3843  '' not a reg?
3844  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3845  hPrepOperand( dvreg, ostr, FB_DATATYPE_INTEGER )
3846  hPUSH ostr
3847  end if
3848 
3849  '' ecx not free?
3850  elseif( (reg <> EMIT_REG_ECX) and (ecxfree = FALSE) ) then
3851  ecxpreserved = TRUE
3852  hPUSH "ecx"
3853  end if
3854 
3855  '' source not a reg?
3856  if( svreg->typ <> IR_VREGTYPE_REG ) then
3857  hPrepOperand( svreg, ostr, FB_DATATYPE_BYTE )
3858  hMOV "cl", ostr
3859  else
3860  '' source not ecx?
3861  if( reg <> EMIT_REG_ECX ) then
3862  hMOV "ecx", rnameTB(dtypeTB(FB_DATATYPE_INTEGER).rnametb, reg)
3863  end if
3864  end if
3865 
3866  '' load ecx to a tmp?
3867  if( ecxindest ) then
3868  '' tmp not free?
3869  if( eaxfree = FALSE ) then
3870  eaxpreserved = TRUE
3871  outp "xchg eax, [esp]" '' eax= dst; push eax
3872  else
3873  hPOP "eax" '' eax= dst; pop tos
3874  end if
3875 
3876  tmp = rnameTB(dtypeTB(dvreg->dtype).rnametb, EMIT_REG_EAX )
3877 
3878  else
3879  tmp = dst
3880  end if
3881 
3882  src = "cl"
3883 
3884  end if
3885 
3886  ostr = mnemonic + " " + tmp + COMMA + src
3887  outp ostr
3888 
3889  if( ecxindest ) then
3890  if( dvreg->typ <> IR_VREGTYPE_REG ) then
3891  hPOP "ecx"
3892  if( eaxpreserved ) then
3893  outp "xchg ecx, [esp]" '' ecx= tos; tos= eax
3894  end if
3895  end if
3896  hMOV dst, rnameTB(dtypeTB(dvreg->dtype).rnametb, EMIT_REG_EAX)
3897  end if
3898 
3899  if( eaxpreserved ) then
3900  hPOP "eax"
3901  end if
3902 
3903  if( ecxpreserved ) then
3904  hPOP "ecx"
3905  end if
3906 
3907 end sub
3908 
3909 '':::::
3910 sub _emitSHLL _
3911  ( _
3912  byval dvreg as IRVREG ptr, _
3913  byval svreg as IRVREG ptr _
3914  ) static
3915 
3916  hSHIFTL( AST_OP_SHL, dvreg, svreg )
3917 
3918 end sub
3919 
3920 '':::::
3921 sub _emitSHLI _
3922  ( _
3923  byval dvreg as IRVREG ptr, _
3924  byval svreg as IRVREG ptr _
3925  ) static
3926 
3927  hSHIFTI( AST_OP_SHL, dvreg, svreg )
3928 
3929 end sub
3930 
3931 '':::::
3932 sub _emitSHRL _
3933  ( _
3934  byval dvreg as IRVREG ptr, _
3935  byval svreg as IRVREG ptr _
3936  ) static
3937 
3938  hSHIFTL( AST_OP_SHR, dvreg, svreg )
3939 
3940 end sub
3941 
3942 '':::::
3943 sub _emitSHRI _
3944  ( _
3945  byval dvreg as IRVREG ptr, _
3946  byval svreg as IRVREG ptr _
3947  ) static
3948 
3949  hSHIFTI( AST_OP_SHR, dvreg, svreg )
3950 
3951 end sub
3952 
3953 '':::::
3954 sub _emitANDL _
3955  ( _
3956  byval dvreg as IRVREG ptr, _
3957  byval svreg as IRVREG ptr _
3958  ) static
3959 
3960  dim dst1 as string, dst2 as string, src1 as string, src2 as string
3961  dim ostr as string
3962 
3963  hPrepOperand64( dvreg, dst1, dst2 )
3964  hPrepOperand64( svreg, src1, src2 )
3965 
3966  ostr = "and " + dst1 + COMMA + src1
3967  outp ostr
3968 
3969  ostr = "and " + dst2 + COMMA + src2
3970  outp ostr
3971 
3972 end sub
3973 
3974 '':::::
3975 sub _emitANDI _
3976  ( _
3977  byval dvreg as IRVREG ptr, _
3978  byval svreg as IRVREG ptr _
3979  ) static
3980 
3981  dim dst as string, src as string
3982  dim ostr as string
3983 
3984  hPrepOperand( dvreg, dst )
3985  hPrepOperand( svreg, src )
3986 
3987  ostr = "and " + dst + COMMA + src
3988  outp ostr
3989 
3990 end sub
3991 
3992 '':::::
3993 sub _emitORL _
3994  ( _
3995  byval dvreg as IRVREG ptr, _
3996  byval svreg as IRVREG ptr _
3997  ) static
3998 
3999  dim dst1 as string, dst2 as string, src1 as string, src2 as string
4000  dim ostr as string
4001 
4002  hPrepOperand64( dvreg, dst1, dst2 )
4003  hPrepOperand64( svreg, src1, src2 )
4004 
4005  ostr = "or " + dst1 + COMMA + src1
4006  outp ostr
4007 
4008  ostr = "or " + dst2 + COMMA + src2
4009  outp ostr
4010 
4011 end sub
4012 
4013 '':::::
4014 sub _emitORI _
4015  ( _
4016  byval dvreg as IRVREG ptr, _
4017  byval svreg as IRVREG ptr _
4018  ) static
4019 
4020  dim dst as string, src as string
4021  dim ostr as string
4022 
4023  hPrepOperand( dvreg, dst )
4024  hPrepOperand( svreg, src )
4025 
4026  ostr = "or " + dst + COMMA + src
4027  outp ostr
4028 
4029 end sub
4030 
4031 '':::::
4032 sub _emitXORL _
4033  ( _
4034  byval dvreg as IRVREG ptr, _
4035  byval svreg as IRVREG ptr _
4036  ) static
4037 
4038  dim dst1 as string, dst2 as string, src1 as string, src2 as string
4039  dim ostr as string
4040 
4041  hPrepOperand64( dvreg, dst1, dst2 )
4042  hPrepOperand64( svreg, src1, src2 )
4043 
4044  ostr = "xor " + dst1 + COMMA + src1
4045  outp ostr
4046 
4047  ostr = "xor " + dst2 + COMMA + src2
4048  outp ostr
4049 
4050 end sub
4051 
4052 '':::::
4053 sub _emitXORI _
4054  ( _
4055  byval dvreg as IRVREG ptr, _
4056  byval svreg as IRVREG ptr _
4057  ) static
4058 
4059  dim dst as string, src as string
4060  dim ostr as string
4061 
4062  hPrepOperand( dvreg, dst )
4063  hPrepOperand( svreg, src )
4064 
4065  ostr = "xor " + dst + COMMA + src
4066  outp ostr
4067 
4068 end sub
4069 
4070 '':::::
4071 sub _emitEQVL _
4072  ( _
4073  byval dvreg as IRVREG ptr, _
4074  byval svreg as IRVREG ptr _
4075  ) static
4076 
4077  dim dst1 as string, dst2 as string, src1 as string, src2 as string
4078  dim ostr as string
4079 
4080  hPrepOperand64( dvreg, dst1, dst2 )
4081  hPrepOperand64( svreg, src1, src2 )
4082 
4083  ostr = "xor " + dst1 + COMMA + src1
4084  outp ostr
4085 
4086  ostr = "xor " + dst2 + COMMA + src2
4087  outp ostr
4088 
4089  ostr = "not " + dst1
4090  outp ostr
4091 
4092  ostr = "not " + dst2
4093  outp ostr
4094 
4095 end sub
4096 
4097 '':::::
4098 sub _emitEQVI _
4099  ( _
4100  byval dvreg as IRVREG ptr, _
4101  byval svreg as IRVREG ptr _
4102  ) static
4103 
4104  dim dst as string, src as string
4105  dim ostr as string
4106 
4107  hPrepOperand( dvreg, dst )
4108  hPrepOperand( svreg, src )
4109 
4110  ostr = "xor " + dst + COMMA + src
4111  outp ostr
4112 
4113  ostr = "not " + dst
4114  outp ostr
4115 
4116 end sub
4117 
4118 '':::::
4119 sub _emitIMPL _
4120  ( _
4121  byval dvreg as IRVREG ptr, _
4122  byval svreg as IRVREG ptr _
4123  ) static
4124 
4125  dim dst1 as string, dst2 as string, src1 as string, src2 as string
4126  dim ostr as string
4127 
4128  hPrepOperand64( dvreg, dst1, dst2 )
4129  hPrepOperand64( svreg, src1, src2 )
4130 
4131  ostr = "not " + dst1
4132  outp ostr
4133 
4134  ostr = "not " + dst2
4135  outp ostr
4136 
4137  ostr = "or " + dst1 + COMMA + src1
4138  outp ostr
4139 
4140  ostr = "or " + dst2 + COMMA + src2
4141  outp ostr
4142 
4143 end sub
4144 
4145 '':::::
4146 sub _emitIMPI _
4147  ( _
4148  byval dvreg as IRVREG ptr, _
4149  byval svreg as IRVREG ptr _
4150  ) static
4151 
4152  dim dst as string, src as string
4153  dim ostr as string
4154 
4155  hPrepOperand( dvreg, dst )
4156  hPrepOperand( svreg, src )
4157 
4158  ostr = "not " + dst
4159  outp ostr
4160 
4161  ostr = "or " + dst + COMMA + src
4162  outp ostr
4163 
4164 end sub
4165 
4166 
4167 '':::::
4168 sub _emitATN2 _
4169  ( _
4170  byval dvreg as IRVREG ptr, _
4171  byval svreg as IRVREG ptr _
4172  ) static
4173 
4174  dim src as string
4175  dim ostr as string
4176 
4177  hPrepOperand( svreg, src )
4178 
4179  if( svreg->typ <> IR_VREGTYPE_REG ) then
4180  ostr = "fld " + src
4181  outp ostr
4182  else
4183  outp "fxch"
4184  end if
4185  outp "fpatan"
4186 
4187 end sub
4188 
4189 '':::::
4190 sub _emitPOW _
4191  ( _
4192  byval dvreg as IRVREG ptr, _
4193  byval svreg as IRVREG ptr _
4194  ) static
4195 
4196  dim src as string
4197  dim ostr as string
4198 
4199  hPrepOperand( svreg, src )
4200 
4201  if( svreg->typ <> IR_VREGTYPE_REG ) then
4202  ostr = "fld " + src
4203  outp ostr
4204  outp "fxch"
4205  end if
4206 
4207  outp "fabs"
4208  outp "fyl2x"
4209  outp "fld st(0)"
4210  outp "frndint"
4211  outp "fsub st(1), st(0)"
4212  outp "fxch"
4213  outp "f2xm1"
4214  outp "fld1"
4215  outp "faddp"
4216  outp "fscale"
4217  outp "fstp st(1)"
4218 
4219 end sub
4220 
4221 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
4222 '' relational
4223 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
4224 
4225 '':::::
4226 sub hCMPL _
4227  ( _
4228  byval rvreg as IRVREG ptr, _
4229  byval label as FBSYMBOL ptr, _
4230  byval mnemonic as zstring ptr, _
4231  byval rev_mnemonic as zstring ptr, _
4232  byval usg_mnemonic as zstring ptr, _
4233  byval dvreg as IRVREG ptr, _
4234  byval svreg as IRVREG ptr, _
4235  byval isinverse as integer = FALSE _
4236  ) static
4237 
4238  dim as string dst1, dst2, src1, src2, rname, ostr, lname, falselabel
4239 
4240  hPrepOperand64( dvreg, dst1, dst2 )
4241  hPrepOperand64( svreg, src1, src2 )
4242 
4243  if( label = NULL ) then
4244  lname = *symbUniqueLabel( )
4245  else
4246  lname = *symbGetMangledName( label )
4247  end if
4248 
4249  '' check high
4250  ostr = "cmp " + dst2 + COMMA + src2
4251  outp ostr
4252 
4253  falselabel = *symbUniqueLabel( )
4254 
4255  '' set the boolean result?
4256  if( rvreg <> NULL ) then
4257  hPrepOperand( rvreg, rname )
4258  hMOV( rname, "-1" )
4259  end if
4260 
4261  ostr = "j" + *mnemonic
4262  if( isinverse = FALSE ) then
4263  hBRANCH( ostr, lname )
4264  else
4265  hBRANCH( ostr, falselabel )
4266  end if
4267 
4268  if( len( *rev_mnemonic ) > 0 ) then
4269  ostr = "j" + *rev_mnemonic
4270  hBRANCH( ostr, falselabel )
4271  end if
4272 
4273  '' check low
4274  ostr = "cmp " + dst1 + COMMA + src1
4275  outp ostr
4276 
4277  ostr = "j" + *usg_mnemonic
4278  hBRANCH( ostr, lname )
4279 
4280  hLabel( falselabel )
4281 
4282  if( rvreg <> NULL ) then
4283  ostr = "xor " + rname + COMMA + rname
4284  outp ostr
4285 
4286  hLabel( lname )
4287  end if
4288 
4289 end sub
4290 
4291 '':::::
4292 sub hCMPI _
4293  ( _
4294  byval rvreg as IRVREG ptr, _
4295  byval label as FBSYMBOL ptr, _
4296  byval mnemonic as zstring ptr, _
4297  byval dvreg as IRVREG ptr, _
4298  byval svreg as IRVREG ptr _
4299  ) static
4300 
4301  dim as string rname, rname8, dst, src, ostr, lname
4302  dim as integer isedxfree, dotest
4303 
4304  hPrepOperand( dvreg, dst )
4305  hPrepOperand( svreg, src )
4306 
4307  if( label = NULL ) then
4308  lname = *symbUniqueLabel( )
4309  else
4310  lname = *symbGetMangledName( label )
4311  end if
4312 
4313  '' optimize "cmp" to "test"
4314  dotest = FALSE
4315  if( (svreg->typ = IR_VREGTYPE_IMM) and (dvreg->typ = IR_VREGTYPE_REG) ) then
4316  if( svreg->value.i = 0 ) then
4317  dotest = TRUE
4318  end if
4319  end if
4320 
4321  if( dotest ) then
4322  ostr = "test " + dst + COMMA + dst
4323  outp ostr
4324  else
4325  ostr = "cmp " + dst + COMMA + src
4326  outp ostr
4327  end if
4328 
4329  '' no result to be set? just branch
4330  if( rvreg = NULL ) then
4331  ostr = "j" + *mnemonic
4332  hBRANCH( ostr, lname )
4333  exit sub
4334  end if
4335 
4336  hPrepOperand( rvreg, rname )
4337 
4338  '' can it be optimized?
4339  if( (env.clopt.cputype >= FB_CPUTYPE_486) and (rvreg->typ = IR_VREGTYPE_REG) ) then
4340 
4341  rname8 = *hGetRegName( FB_DATATYPE_BYTE, rvreg->reg )
4342 
4343  '' handle EDI and ESI
4344  if( (rvreg->reg = EMIT_REG_ESI) or (rvreg->reg = EMIT_REG_EDI) ) then
4345 
4346  isedxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDX )
4347  if( isedxfree = FALSE ) then
4348  ostr = "xchg edx, " + rname
4349  outp ostr
4350  end if
4351 
4352  ostr = "set" + *mnemonic + " dl"
4353  outp ostr
4354 
4355  if( isedxfree = FALSE ) then
4356  ostr = "xchg edx, " + rname
4357  outp ostr
4358  else
4359  hMOV rname, "edx"
4360  end if
4361 
4362  else
4363  ostr = "set" + *mnemonic + " " + rname8
4364  outp ostr
4365  end if
4366 
4367  '' convert 1 to -1 (TRUE in QB/FB)
4368  ostr = "shr " + rname + ", 1"
4369  outp ostr
4370 
4371  ostr = "sbb " + rname + COMMA + rname
4372  outp ostr
4373 
4374  '' old (and slow) boolean set
4375  else
4376 
4377  ostr = "mov " + rname + ", -1"
4378  outp ostr
4379 
4380  ostr = "j" + *mnemonic
4381  hBRANCH( ostr, lname )
4382 
4383  ostr = "xor " + rname + COMMA + rname
4384  outp ostr
4385 
4386  hLabel( lname )
4387  end if
4388 
4389 end sub
4390 
4391 
4392 '':::::
4393 sub hCMPF _
4394  ( _
4395  byval rvreg as IRVREG ptr, _
4396  byval label as FBSYMBOL ptr, _
4397  byval mnemonic as zstring ptr, _
4398  byval mask as zstring ptr, _
4399  byval dvreg as IRVREG ptr, _
4400  byval svreg as IRVREG ptr _
4401  ) static
4402 
4403  dim as string rname, rname8, dst, src, ostr, lname
4404  dim as integer iseaxfree, isedxfree
4405 
4406  hPrepOperand( dvreg, dst )
4407  hPrepOperand( svreg, src )
4408 
4409  if( label = NULL ) then
4410  lname = *symbUniqueLabel( )
4411  else
4412  lname = *symbGetMangledName( label )
4413  end if
4414 
4415  '' do comp
4416  if( svreg->typ = IR_VREGTYPE_REG ) then
4417  outp "fcompp"
4418  else
4419  '' can it be optimized to ftst?
4420  if( typeGetClass( svreg->dtype ) = FB_DATACLASS_FPOINT ) then
4421  ostr = "fcomp " + src
4422  outp ostr
4423  else
4424  ostr = "ficomp " + src
4425  outp ostr
4426  end if
4427  end if
4428 
4429  iseaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
4430  if( rvreg <> NULL ) then
4431  iseaxfree = (rvreg->reg = EMIT_REG_EAX)
4432  end if
4433 
4434  if( iseaxfree = FALSE ) then
4435  hPUSH( "eax" )
4436  end if
4437 
4438  '' load fpu flags
4439  outp "fnstsw ax"
4440  if( len( *mask ) > 0 ) then
4441  ostr = "test ah, " + *mask
4442  outp ostr
4443  else
4444  outp "sahf"
4445  end if
4446 
4447  if( iseaxfree = FALSE ) then
4448  hPOP( "eax" )
4449  end if
4450 
4451  '' no result to be set? just branch
4452  if( rvreg = NULL ) then
4453  ostr = "j" + *mnemonic
4454  hBRANCH( ostr, lname )
4455  exit sub
4456  end if
4457 
4458  hPrepOperand( rvreg, rname )
4459 
4460  '' can it be optimized?
4461  if( env.clopt.cputype >= FB_CPUTYPE_486 ) then
4462  rname8 = *hGetRegName( FB_DATATYPE_BYTE, rvreg->reg )
4463 
4464  '' handle EDI and ESI
4465  if( (rvreg->reg = EMIT_REG_ESI) or (rvreg->reg = EMIT_REG_EDI) ) then
4466 
4467  isedxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDX )
4468  if( isedxfree = FALSE ) then
4469  ostr = "xchg edx, " + rname
4470  outp ostr
4471  end if
4472 
4473  ostr = "set" + *mnemonic + (TABCHAR + "dl")
4474  outp ostr
4475 
4476  if( isedxfree = FALSE ) then
4477  ostr = "xchg edx, " + rname
4478  outp ostr
4479  else
4480  hMOV rname, "edx"
4481  end if
4482  else
4483  ostr = "set" + *mnemonic + " " + rname8
4484  outp ostr
4485  end if
4486 
4487  '' convert 1 to -1 (TRUE in QB/FB)
4488  ostr = "shr " + rname + ", 1"
4489  outp ostr
4490 
4491  ostr = "sbb " + rname + COMMA + rname
4492  outp ostr
4493 
4494  '' old (and slow) boolean set
4495  else
4496  ostr = "mov " + rname + ", -1"
4497  outp ostr
4498 
4499  ostr = "j" + *mnemonic
4500  hBRANCH( ostr, lname )
4501 
4502  ostr = "xor " + rname + COMMA + rname
4503  outp ostr
4504 
4505  hLabel( lname )
4506  end if
4507 
4508 end sub
4509 
4510 '':::::
4511 sub _emitCGTL _
4512  ( _
4513  byval rvreg as IRVREG ptr, _
4514  byval label as FBSYMBOL ptr, _
4515  byval dvreg as IRVREG ptr, _
4516  byval svreg as IRVREG ptr _
4517  ) static
4518 
4519  dim jmp as string, rjmp as string
4520 
4521  if( typeIsSigned( dvreg->dtype ) ) then
4522  jmp = "g"
4523  rjmp = "l"
4524  else
4525  jmp = "a"
4526  rjmp = "b"
4527  end if
4528 
4529  hCMPL( rvreg, label, jmp, rjmp, "a", dvreg, svreg )
4530 
4531 end sub
4532 
4533 '':::::
4534 sub _emitCGTI _
4535  ( _
4536  byval rvreg as IRVREG ptr, _
4537  byval label as FBSYMBOL ptr, _
4538  byval dvreg as IRVREG ptr, _
4539  byval svreg as IRVREG ptr _
4540  ) static
4541 
4542  dim jmp as string
4543 
4544  if( typeIsSigned( dvreg->dtype ) ) then
4545  jmp = "g"
4546  else
4547  jmp = "a"
4548  end if
4549 
4550  hCMPI( rvreg, label, jmp, dvreg, svreg )
4551 
4552 end sub
4553 
4554 
4555 
4556 '':::::
4557 sub _emitCGTF _
4558  ( _
4559  byval rvreg as IRVREG ptr, _
4560  byval label as FBSYMBOL ptr, _
4561  byval dvreg as IRVREG ptr, _
4562  byval svreg as IRVREG ptr _
4563  ) static
4564 
4565  hCMPF( rvreg, label, "z", "0b01000001", dvreg, svreg )
4566 
4567 end sub
4568 
4569 '':::::
4570 sub _emitCLTL _
4571  ( _
4572  byval rvreg as IRVREG ptr, _
4573  byval label as FBSYMBOL ptr, _
4574  byval dvreg as IRVREG ptr, _
4575  byval svreg as IRVREG ptr _
4576  ) static
4577 
4578  dim jmp as string, rjmp as string
4579 
4580  if( typeIsSigned( dvreg->dtype ) ) then
4581  jmp = "l"
4582  rjmp = "g"
4583  else
4584  jmp = "b"
4585  rjmp = "a"
4586  end if
4587 
4588  hCMPL( rvreg, label, jmp, rjmp, "b", dvreg, svreg )
4589 
4590 end sub
4591 
4592 '':::::
4593 sub _emitCLTI _
4594  ( _
4595  byval rvreg as IRVREG ptr, _
4596  byval label as FBSYMBOL ptr, _
4597  byval dvreg as IRVREG ptr, _
4598  byval svreg as IRVREG ptr _
4599  ) static
4600 
4601  dim jmp as string
4602 
4603  if( typeIsSigned( dvreg->dtype ) ) then
4604  jmp = "l"
4605  else
4606  jmp = "b"
4607  end if
4608 
4609  hCMPI( rvreg, label, jmp, dvreg, svreg )
4610 
4611 end sub
4612 
4613 
4614 '':::::
4615 sub _emitCLTF _
4616  ( _
4617  byval rvreg as IRVREG ptr, _
4618  byval label as FBSYMBOL ptr, _
4619  byval dvreg as IRVREG ptr, _
4620  byval svreg as IRVREG ptr _
4621  ) static
4622 
4623  hCMPF( rvreg, label, "nz", "0b00000001", dvreg, svreg )
4624 
4625 end sub
4626 
4627 '':::::
4628 sub _emitCEQL _
4629  ( _
4630  byval rvreg as IRVREG ptr, _
4631  byval label as FBSYMBOL ptr, _
4632  byval dvreg as IRVREG ptr, _
4633  byval svreg as IRVREG ptr _
4634  ) static
4635 
4636  hCMPL( rvreg, label, "ne", "", "e", dvreg, svreg, TRUE )
4637 
4638 end sub
4639 
4640 '':::::
4641 sub _emitCEQI _
4642  ( _
4643  byval rvreg as IRVREG ptr, _
4644  byval label as FBSYMBOL ptr, _
4645  byval dvreg as IRVREG ptr, _
4646  byval svreg as IRVREG ptr _
4647  ) static
4648 
4649  hCMPI( rvreg, label, "e", dvreg, svreg )
4650 
4651 end sub
4652 
4653 
4654 '':::::
4655 sub _emitCEQF _
4656  ( _
4657  byval rvreg as IRVREG ptr, _
4658  byval label as FBSYMBOL ptr, _
4659  byval dvreg as IRVREG ptr, _
4660  byval svreg as IRVREG ptr _
4661  ) static
4662 
4663  hCMPF( rvreg, label, "nz", "0b01000000", dvreg, svreg )
4664 
4665 end sub
4666 
4667 '':::::
4668 sub _emitCNEL _
4669  ( _
4670  byval rvreg as IRVREG ptr, _
4671  byval label as FBSYMBOL ptr, _
4672  byval dvreg as IRVREG ptr, _
4673  byval svreg as IRVREG ptr _
4674  ) static
4675 
4676  hCMPL( rvreg, label, "ne", "", "ne", dvreg, svreg )
4677 
4678 end sub
4679 
4680 '':::::
4681 sub _emitCNEI _
4682  ( _
4683  byval rvreg as IRVREG ptr, _
4684  byval label as FBSYMBOL ptr, _
4685  byval dvreg as IRVREG ptr, _
4686  byval svreg as IRVREG ptr _
4687  ) static
4688 
4689  hCMPI( rvreg, label, "ne", dvreg, svreg )
4690 
4691 end sub
4692 
4693 
4694 '':::::
4695 sub _emitCNEF _
4696  ( _
4697  byval rvreg as IRVREG ptr, _
4698  byval label as FBSYMBOL ptr, _
4699  byval dvreg as IRVREG ptr, _
4700  byval svreg as IRVREG ptr _
4701  ) static
4702 
4703  hCMPF( rvreg, label, "z", "0b01000000", dvreg, svreg )
4704 
4705 end sub
4706 
4707 '':::::
4708 sub _emitCLEL _
4709  ( _
4710  byval rvreg as IRVREG ptr, _
4711  byval label as FBSYMBOL ptr, _
4712  byval dvreg as IRVREG ptr, _
4713  byval svreg as IRVREG ptr _
4714  ) static
4715 
4716  dim jmp as string, rjmp as string
4717 
4718  if( typeIsSigned( dvreg->dtype ) ) then
4719  jmp = "l"
4720  rjmp = "g"
4721  else
4722  jmp = "b"
4723  rjmp = "a"
4724  end if
4725 
4726  hCMPL( rvreg, label, jmp, rjmp, "be", dvreg, svreg )
4727 
4728 end sub
4729 
4730 '':::::
4731 sub _emitCLEI _
4732  ( _
4733  byval rvreg as IRVREG ptr, _
4734  byval label as FBSYMBOL ptr, _
4735  byval dvreg as IRVREG ptr, _
4736  byval svreg as IRVREG ptr _
4737  ) static
4738 
4739  dim jmp as string
4740 
4741  if( typeIsSigned( dvreg->dtype ) ) then
4742  jmp = "le"
4743  else
4744  jmp = "be"
4745  end if
4746 
4747  hCMPI( rvreg, label, jmp, dvreg, svreg )
4748 
4749 end sub
4750 
4751 
4752 '':::::
4753 sub _emitCLEF _
4754  ( _
4755  byval rvreg as IRVREG ptr, _
4756  byval label as FBSYMBOL ptr, _
4757  byval dvreg as IRVREG ptr, _
4758  byval svreg as IRVREG ptr _
4759  ) static
4760 
4761  hCMPF( rvreg, label, "nz", "0b01000001", dvreg, svreg )
4762 
4763 end sub
4764 
4765 
4766 '':::::
4767 sub _emitCGEL _
4768  ( _
4769  byval rvreg as IRVREG ptr, _
4770  byval label as FBSYMBOL ptr, _
4771  byval dvreg as IRVREG ptr, _
4772  byval svreg as IRVREG ptr _
4773  ) static
4774 
4775  dim jmp as string, rjmp as string
4776 
4777  if( typeIsSigned( dvreg->dtype ) ) then
4778  jmp = "g"
4779  rjmp = "l"
4780  else
4781  jmp = "a"
4782  rjmp = "b"
4783  end if
4784 
4785  hCMPL( rvreg, label, jmp, rjmp, "ae", dvreg, svreg )
4786 
4787 end sub
4788 
4789 '':::::
4790 sub _emitCGEI _
4791  ( _
4792  byval rvreg as IRVREG ptr, _
4793  byval label as FBSYMBOL ptr, _
4794  byval dvreg as IRVREG ptr, _
4795  byval svreg as IRVREG ptr _
4796  ) static
4797 
4798  dim jmp as string
4799 
4800  if( typeIsSigned( dvreg->dtype ) ) then
4801  jmp = "ge"
4802  else
4803  jmp = "ae"
4804  end if
4805 
4806  hCMPI( rvreg, label, jmp, dvreg, svreg )
4807 
4808 end sub
4809 
4810 
4811 '':::::
4812 sub _emitCGEF _
4813  ( _
4814  byval rvreg as IRVREG ptr, _
4815  byval label as FBSYMBOL ptr, _
4816  byval dvreg as IRVREG ptr, _
4817  byval svreg as IRVREG ptr _
4818  ) static
4819 
4820  hCMPF( rvreg, label, "ae", "", dvreg, svreg )
4821 
4822 end sub
4823 
4824 
4825 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
4826 '' unary ops
4827 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
4828 
4829 '':::::
4830 sub _emitNEGL _
4831  ( _
4832  byval dvreg as IRVREG ptr _
4833  ) static
4834 
4835  dim dst1 as string, dst2 as string
4836  dim ostr as string
4837 
4838  hPrepOperand64( dvreg, dst1, dst2 )
4839 
4840  ostr = "neg " + dst1
4841  outp ostr
4842 
4843  ostr = "adc " + dst2 + ", 0"
4844  outp ostr
4845 
4846  ostr = "neg " + dst2
4847  outp ostr
4848 
4849 end sub
4850 
4851 '':::::
4852 sub _emitNEGI _
4853  ( _
4854  byval dvreg as IRVREG ptr _
4855  ) static
4856 
4857  dim dst as string
4858  dim ostr as string
4859 
4860  hPrepOperand( dvreg, dst )
4861 
4862  ostr = "neg " + dst
4863  outp ostr
4864 
4865 end sub
4866 
4867 
4868 '':::::
4869 sub _emitNEGF _
4870  ( _
4871  byval dvreg as IRVREG ptr _
4872  ) static
4873 
4874  outp "fchs"
4875 
4876 end sub
4877 
4878 '':::::
4879 sub _emitNOTL _
4880  ( _
4881  byval dvreg as IRVREG ptr _
4882  ) static
4883 
4884  dim dst1 as string, dst2 as string
4885  dim ostr as string
4886 
4887  hPrepOperand64( dvreg, dst1, dst2 )
4888 
4889  ostr = "not " + dst1
4890  outp ostr
4891 
4892  ostr = "not " + dst2
4893  outp ostr
4894 
4895 end sub
4896 
4897 '':::::
4898 sub _emitNOTI _
4899  ( _
4900  byval dvreg as IRVREG ptr _
4901  ) static
4902 
4903  dim dst as string
4904  dim ostr as string
4905 
4906  hPrepOperand( dvreg, dst )
4907 
4908  ostr = "not " + dst
4909  outp ostr
4910 
4911 end sub
4912 
4913 '':::::
4914 sub _emitABSL _
4915  ( _
4916  byval dvreg as IRVREG ptr _
4917  ) static
4918 
4919  dim dst1 as string, dst2 as string
4920  dim reg as integer, isfree as integer, rname as string
4921  dim ostr as string
4922 
4923  hPrepOperand64( dvreg, dst1, dst2 )
4924 
4925  reg = hFindRegNotInVreg( dvreg )
4926  rname = *hGetRegName( FB_DATATYPE_INTEGER, reg )
4927 
4928  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
4929 
4930  if( isfree = FALSE ) then
4931  hPUSH( rname )
4932  end if
4933 
4934  hMOV( rname, dst2 )
4935 
4936  ostr = "sar " + rname + ", 31"
4937  outp ostr
4938 
4939  ostr = "xor " + dst1 + COMMA + rname
4940  outp ostr
4941 
4942  ostr = "xor " + dst2 + COMMA + rname
4943  outp ostr
4944 
4945  ostr = "sub " + dst1 + COMMA + rname
4946  outp ostr
4947 
4948  ostr = "sbb " + dst2 + COMMA + rname
4949  outp ostr
4950 
4951  if( isfree = FALSE ) then
4952  hPOP( rname )
4953  end if
4954 
4955 end sub
4956 
4957 '':::::
4958 sub _emitABSI _
4959  ( _
4960  byval dvreg as IRVREG ptr _
4961  ) static
4962 
4963  dim dst as string
4964  dim reg as integer, isfree as integer, rname as string, bits as integer
4965  dim ostr as string
4966 
4967  hPrepOperand( dvreg, dst )
4968 
4969  reg = hFindRegNotInVreg( dvreg )
4970  rname = *hGetRegName( dvreg->dtype, reg )
4971 
4972  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
4973 
4974  if( isfree = FALSE ) then
4975  hPUSH( rname )
4976  end if
4977 
4978  bits = typeGetBits( dvreg->dtype ) - 1
4979 
4980  hMOV( rname, dst )
4981 
4982  ostr = "sar " + rname + COMMA + str( bits )
4983  outp ostr
4984 
4985  ostr = "xor " + dst + COMMA + rname
4986  outp ostr
4987 
4988  ostr = "sub " + dst + COMMA + rname
4989  outp ostr
4990 
4991  if( isfree = FALSE ) then
4992  hPOP( rname )
4993  end if
4994 
4995 end sub
4996 
4997 
4998 '':::::
4999 sub _emitABSF _
5000  ( _
5001  byval dvreg as IRVREG ptr _
5002  ) static
5003 
5004  outp "fabs"
5005 
5006 end sub
5007 
5008 '':::::
5009 sub _emitSGNL _
5010  ( _
5011  byval dvreg as IRVREG ptr _
5012  ) static
5013 
5014  dim dst1 as string, dst2 as string
5015  dim ostr as string
5016  dim label1 as string, label2 as string
5017 
5018  hPrepOperand64( dvreg, dst1, dst2 )
5019 
5020  label1 = *symbUniqueLabel( )
5021  label2 = *symbUniqueLabel( )
5022 
5023  ostr = "cmp " + dst2 + ", 0"
5024  outp ostr
5025  hBRANCH( "jne", label1 )
5026 
5027  ostr = "cmp " + dst1 + ", 0"
5028  outp ostr
5029  hBRANCH( "je", label2 )
5030 
5031  hLABEL( label1 )
5032  hMOV( dst1, "1" )
5033  hMOV( dst2, "0" )
5034  hBRANCH( "jg", label2 )
5035  hMOV( dst1, "-1" )
5036  hMOV( dst2, "-1" )
5037 
5038  hLABEL( label2 )
5039 
5040 end sub
5041 
5042 '':::::
5043 sub _emitSGNI _
5044  ( _
5045  byval dvreg as IRVREG ptr _
5046  ) static
5047 
5048  dim as string dst, label, ostr
5049 
5050  hPrepOperand( dvreg, dst )
5051 
5052  label = *symbUniqueLabel( )
5053 
5054  ostr = "cmp " + dst + ", 0"
5055  outp ostr
5056 
5057  hBRANCH( "je", label )
5058  hMOV( dst, "1" )
5059  hBRANCH( "jg", label )
5060  hMOV( dst, "-1" )
5061 
5062  hLABEL( label )
5063 
5064 end sub
5065 
5066 
5067 '':::::
5068 sub _emitSGNF _
5069  ( _
5070  byval dvreg as IRVREG ptr _
5071  ) static
5072 
5073  dim as string dst, label, ostr
5074  dim as integer iseaxfree
5075 
5076  hPrepOperand( dvreg, dst )
5077 
5078  label = *symbUniqueLabel( )
5079 
5080  iseaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
5081 
5082  if( iseaxfree = FALSE ) then
5083  hPUSH( "eax" )
5084  end if
5085 
5086  outp "ftst"
5087  outp "fnstsw ax"
5088  outp "sahf"
5089 
5090  if( iseaxfree = FALSE ) then
5091  hPOP( "eax" )
5092  end if
5093 
5094  '' if dst = 0
5095  hBRANCH( "jz", label )
5096  '' elseif dst > 0
5097  outp "fstp st(0)"
5098  outp "fld1"
5099  hBRANCH( "ja", label )
5100  '' else
5101  outp "fchs"
5102 
5103  hLABEL( label )
5104 
5105 end sub
5106 
5107 '':::::
5108 sub _emitSIN _
5109  ( _
5110  byval dvreg as IRVREG ptr _
5111  ) static
5112 
5113  outp "fsin"
5114 
5115 end sub
5116 
5117 '':::::
5118 sub _emitASIN _
5119  ( _
5120  byval dvreg as IRVREG ptr _
5121  ) static
5122 
5123  '' asin( x ) = atn( sqr( (x*x) / (1-x*x) ) )
5124  outp "fld st(0)"
5125  outp "fmul st(0), st(0)"
5126  outp "fld1"
5127  outp "fsubrp"
5128  outp "fsqrt"
5129  outp "fpatan"
5130 
5131 end sub
5132 
5133 '':::::
5134 sub _emitCOS _
5135  ( _
5136  byval dvreg as IRVREG ptr _
5137  ) static
5138 
5139  outp "fcos"
5140 
5141 end sub
5142 
5143 '':::::
5144 sub _emitACOS _
5145  ( _
5146  byval dvreg as IRVREG ptr _
5147  ) static
5148 
5149  '' acos( x ) = atn( sqr( (1-x*x) / (x*x) ) )
5150  outp "fld st(0)"
5151  outp "fmul st(0), st(0)"
5152  outp "fld1"
5153  outp "fsubrp"
5154  outp "fsqrt"
5155  outp "fxch"
5156  outp "fpatan"
5157 
5158 end sub
5159 
5160 '':::::
5161 sub _emitTAN _
5162  ( _
5163  byval dvreg as IRVREG ptr _
5164  ) static
5165 
5166  outp "fptan"
5167  outp "fstp st(0)"
5168 
5169 end sub
5170 
5171 '':::::
5172 sub _emitATAN _
5173  ( _
5174  byval dvreg as IRVREG ptr _
5175  ) static
5176 
5177  outp "fld1"
5178  outp "fpatan"
5179 
5180 end sub
5181 
5182 '':::::
5183 sub _emitSQRT _
5184  ( _
5185  byval dvreg as IRVREG ptr _
5186  ) static
5187 
5188  outp "fsqrt"
5189 
5190 end sub
5191 
5192 '':::::
5193 sub _emitLOG _
5194  ( _
5195  byval dvreg as IRVREG ptr _
5196  ) static
5197 
5198  '' log( x ) = log2( x ) / log2( e ).
5199 
5200  outp "fldln2"
5201  outp "fxch"
5202  outp "fyl2x"
5203 
5204 end sub
5205 
5206 '':::::
5207 sub _emitEXP _
5208  ( _
5209  byval dvreg as IRVREG ptr _
5210  ) static
5211 
5212  outp "fldl2e"
5213  outp "fmulp st(1), st"
5214  outp "fld st"
5215  outp "frndint"
5216  outp "fsub st(1), st"
5217  outp "fxch"
5218  outp "f2xm1"
5219  '' can't use fld1 because max 2 fp regs can be used
5220  hPUSH( "0x3f800000" )
5221  outp "fadd dword ptr [esp]"
5222  outp "add esp, 4"
5223  outp "fscale"
5224  outp "fstp st(1)"
5225 end sub
5226 
5227 sub hFpuChangeRC( byref regname as string, byval mode as zstring ptr )
5228  outp( "sub esp, 4" )
5229  outp( "fnstcw [esp]" )
5230  hMOV( regname, "[esp]" )
5231  if( *mode <> "11" ) then
5232  outp( "and " + regname + ", 0b1111001111111111" )
5233  end if
5234  outp( "or " + regname + (", 0b0000" + *mode + "0000000000") )
5235  hPUSH( regname )
5236  outp( "fldcw [esp]" )
5237  outp( "add esp, 4" )
5238 end sub
5239 
5240 sub hEmitFloatFunc( byval func as integer )
5241  dim as integer reg = any, isregfree = any
5242  dim as string regname
5243 
5244  reg = hFindFreeReg( FB_DATACLASS_INTEGER )
5245  if( reg = INVALID ) then
5246  reg = EMIT_REG_EAX
5247  isregfree = FALSE
5248  else
5249  isregfree = TRUE
5250  end if
5251 
5252  regname = *hGetRegName( FB_DATATYPE_INTEGER, reg )
5253 
5254  if( isregfree = FALSE ) then
5255  hPUSH( regname )
5256  end if
5257 
5258  select case( func )
5259  case 1
5260  '' st(0) = floor( st(0) )
5261  '' round down toward -infinity
5262  hFpuChangeRC( regname, "01" )
5263  outp( "frndint" )
5264  case 2
5265  '' st(0) = fix( st(0) ) = floor( abs( st(0) ) ) * sng( st(0) )
5266  '' chop truncating toward 0
5267  hFpuChangeRC( regname, "11" )
5268  outp( "frndint" )
5269  case 3
5270  '' st(0) = st(0) - fix( st(0) )
5271  '' chop truncating toward 0
5272  hFpuChangeRC( regname, "11" )
5273  outp( "fld st(0)" )
5274  outp( "frndint" )
5275  outp( "fsubp" )
5276  end select
5277 
5278  '' restore FPU rounding
5279  outp( "fldcw [esp]" )
5280  outp( "add esp, 4" )
5281 
5282  if( isregfree = FALSE ) then
5283  hPOP( regname )
5284  end if
5285 end sub
5286 
5287 sub _emitFLOOR( byval dvreg as IRVREG ptr )
5288  hEmitFloatFunc( 1 )
5289 end sub
5290 
5291 sub _emitFIX( byval dvreg as IRVREG ptr )
5292  hEmitFloatFunc( 2 )
5293 end sub
5294 
5295 sub _emitFRAC( byval dvreg as IRVREG ptr )
5296  hEmitFloatFunc( 3 )
5297 end sub
5298 
5299 sub _emitCONVFD2FS( byval dvreg as IRVREG ptr )
5300  assert( dvreg->typ = IR_VREGTYPE_REG )
5301  assert( dvreg->regFamily = IR_REG_FPU_STACK )
5302 
5303  '' fld stores into st(0) but doesn't convert from
5304  '' qword to dword, a dword temp var must be used,
5305  '' in order to get the truncation
5306  outp( "sub esp, 4" )
5307  outp( "fstp dword ptr [esp]" )
5308  outp( "fld dword ptr [esp]" )
5309  outp( "add esp, 4" )
5310 end sub
5311 
5312 '':::::
5313 sub _emitXchgTOS _
5314  ( _
5315  byval svreg as IRVREG ptr _
5316  ) static
5317 
5318  dim as string src
5319  dim as string ostr
5320 
5321  hPrepOperand( svreg, src )
5322 
5323  ostr = "fxch " + src
5324  outp( ostr )
5325 
5326 end sub
5327 
5328 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
5329 '' stack
5330 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
5331 
5332 sub _emitSTACKALIGN( byval vreg as IRVREG ptr, byval unused as integer )
5333  if( vreg->value.i > 0 ) then
5334  outp( "sub esp, " + str( vreg->value.i ) )
5335  else
5336  outp( "add esp, " + str( -vreg->value.i ) )
5337  end if
5338 end sub
5339 
5340 '':::::
5341 sub _emitPUSHL _
5342  ( _
5343  byval svreg as IRVREG ptr, _
5344  byval unused as integer _
5345  ) static
5346 
5347  dim src1 as string, src2 as string
5348  dim ostr as string
5349 
5350  hPrepOperand64( svreg, src1, src2 )
5351 
5352  ostr = "push " + src2
5353  outp ostr
5354 
5355  ostr = "push " + src1
5356  outp ostr
5357 
5358 end sub
5359 
5360 sub _emitPUSHI( byval svreg as IRVREG ptr, byval unused as integer )
5361  dim as string src, tmp32
5362  dim as integer sdsize = any, tmpreg = any, istmpfree = any
5363 
5364  hPrepOperand( svreg, src )
5365 
5366  sdsize = typeGetSize( svreg->dtype )
5367 
5368  '' PUSH only supports 4-byte operands, if it's smaller we need to
5369  '' work-around/load into 4-byte location first.
5370 
5371  select case( svreg->typ )
5372  case IR_VREGTYPE_REG
5373  if( sdsize < 4 ) then
5374  '' Use eax instead of al etc., this can pull in "random"
5375  '' values from the unused part of the register,
5376  '' but should be ok.
5377  src = *hGetRegName( FB_DATATYPE_INTEGER, svreg->reg )
5378  end if
5379  outp( "push " + src )
5380 
5381  case IR_VREGTYPE_IMM
5382  outp( "push " + src )
5383 
5384  case else
5385  if( sdsize < 4 ) then
5386  '' Load into 4-byte reg first - it's not safe to assume
5387  '' we can just use DWORD PTR instead of BYTE PTR or
5388  '' WORD PTR (possible buffer overrun).
5389 
5390  tmpreg = hFindRegNotInVreg( svreg )
5391  istmpfree = hIsRegFree( FB_DATACLASS_INTEGER, tmpreg )
5392  tmp32 = *hGetRegName( FB_DATATYPE_INTEGER, tmpreg )
5393 
5394  if( istmpfree = FALSE ) then
5395  hPUSH( tmp32 )
5396  end if
5397 
5398  '' mov tmp, [src]
5399  '' (zero-extending, because e.g. &hFF should become
5400  '' &h000000FF, and not &hFFFFFFFF)
5401  outp( "movzx " + tmp32 + ", " + src )
5402 
5403  '' push tmp
5404  outp( "push " + tmp32 )
5405 
5406  if( istmpfree = FALSE ) then
5407  hPOP( tmp32 )
5408  end if
5409  else
5410  assert( sdsize = 4 )
5411  outp( "push " + src )
5412  end if
5413  end select
5414 
5415 end sub
5416 
5417 '':::::
5418 sub _emitPUSHF _
5419  ( _
5420  byval svreg as IRVREG ptr, _
5421  byval unused as integer _
5422  ) static
5423 
5424  dim src as string, sdsize as integer
5425  dim ostr as string
5426 
5427  hPrepOperand( svreg, src )
5428 
5429  sdsize = typeGetSize( svreg->dtype )
5430 
5431  if( svreg->typ <> IR_VREGTYPE_REG ) then
5432  if( svreg->dtype = FB_DATATYPE_SINGLE ) then
5433  ostr = "push " + src
5434  outp ostr
5435  else
5436  hPrepOperand( svreg, src, FB_DATATYPE_INTEGER, 4 )
5437  ostr = "push " + src
5438  outp ostr
5439 
5440  hPrepOperand( svreg, src, FB_DATATYPE_INTEGER, 0 )
5441  ostr = "push " + src
5442  outp ostr
5443  end if
5444  else
5445  ostr = "sub esp," + str( sdsize )
5446  outp ostr
5447 
5448  ostr = "fstp " + dtypeTB(svreg->dtype).mname + " [esp]"
5449  outp ostr
5450  end if
5451 
5452 end sub
5453 
5454 sub _emitPUSHUDT( byval svreg as IRVREG ptr, byval sdsize as integer )
5455  dim as string src, tmp32, tmp16
5456  dim as integer ofs = any, tmpreg = any, istmpfree = any, remainder = any
5457 
5458  '' The UDT should be pushed byte-by-byte, it must end up in the same
5459  '' order on stack as it is originally layed out in memory.
5460  ''
5461  '' For example, this sequence of bytes in memory (the UDT to push):
5462  '' &hAA &hBB &hCC &hDD &hEE &hFF
5463  ''
5464  '' It's 6 bytes, i.e. not a multiple of 8, i.e. there is a remainder:
5465  '' &hEE &hFF
5466  '' The two bytes are read with a WORD PTR, zero extended, then pushed:
5467  '' offset = sdsize - 2
5468  '' &h0000FFEE <- word ptr [svreg + offset]
5469  '' push &h0000FFEE
5470  '' producing on stack:
5471  '' &hEE &hFF &h00 &h00
5472  ''
5473  '' Then there are 4 bytes left to handle:
5474  '' &hAA &hBB &hCC &hDD
5475  '' They're read out using a DWORD PTR, then pushed:
5476  '' offset = 0
5477  '' push dword ptr [svreg + offset]
5478  '' producing on stack:
5479  '' &hAA &hBB &hCC &hDD &hEE &hFF &h00 &h00
5480  ''
5481  '' which is the desired "copy".
5482 
5483  '' Push remainder (last 1/2/3 bytes of the struct, located in memory
5484  '' at src + length - N)
5485  remainder = sdsize and (4-1)
5486  if( remainder > 0 ) then
5487  '' Load into 4-byte reg first - it's not safe to assume
5488  '' we can just use DWORD PTR instead of BYTE PTR or
5489  '' WORD PTR (possible buffer overrun).
5490 
5491  tmpreg = hFindRegNotInVreg( svreg )
5492  istmpfree = hIsRegFree( FB_DATACLASS_INTEGER, tmpreg )
5493  tmp32 = *hGetRegName( FB_DATATYPE_INTEGER, tmpreg )
5494 
5495  if( istmpfree = FALSE ) then
5496  hPUSH( tmp32 )
5497  end if
5498 
5499  select case( remainder )
5500  case 3
5501  '' 3-byte remainder:
5502  '' &h11 &h22 &h33
5503  '' It's probably best to access them as &h2211 WORD
5504  '' and &h33 BYTE. &h11 has a good chance of having
5505  '' 4-byte alignment, since the whole UDT will typically
5506  '' start at 4-byte boundary; at least for stack vars...
5507 
5508  '' 1. load 3rd byte:
5509  '' &h00000033 <- byte ptr [src + length - 1]
5510  hPrepOperand( svreg, src, FB_DATATYPE_BYTE, sdsize - 1 )
5511  outp( "movzx " + tmp32 + ", " + src )
5512 
5513  '' 2. shl
5514  '' &h00330000 <- &h00000033 shl 16
5515  outp( "shl " + tmp32 + ", 16" )
5516 
5517  '' 3. load first two bytes into the lower 16 bits
5518  '' of the register:
5519  '' &h00002211 <- word ptr [src + length - 3]
5520  '' &h00332211 <- &h00330000, &h00002211
5521  tmp16 = *hGetRegName( FB_DATATYPE_SHORT, tmpreg )
5522  hPrepOperand( svreg, src, FB_DATATYPE_SHORT, sdsize - 3 )
5523  outp( "mov " + tmp16 + ", " + src )
5524 
5525  '' 4. push
5526  '' push &h00332211
5527  '' producing on stack:
5528  '' &h11 &h22 &h33 &h00
5529 
5530  case 2
5531  '' mov tmp, word ptr [src + length - 2]
5532  '' (zero-extending, because e.g. &hFFFF should become
5533  '' &h0000FFFF, and not &hFFFFFFFF)
5534  ofs = sdsize - 2
5535  hPrepOperand( svreg, src, FB_DATATYPE_SHORT, ofs )
5536  outp( "movzx " + tmp32 + ", " + src )
5537 
5538  case 1
5539  '' mov tmp, byte ptr [src + length - 1]
5540  '' (zero-extending, ditto)
5541  ofs = sdsize - 1
5542  hPrepOperand( svreg, src, FB_DATATYPE_BYTE, ofs )
5543  outp( "movzx " + tmp32 + ", " + src )
5544 
5545  end select
5546 
5547  '' push tmp
5548  '' &h0000FFFF becomes &hFF &hFF &h00 &h00 on stack
5549  outp( "push " + tmp32 )
5550 
5551  if( istmpfree = FALSE ) then
5552  hPOP( tmp32 )
5553  end if
5554 
5555  sdsize -= remainder
5556  end if
5557 
5558  '' Push whole dwords, backwards (from high address to low address,
5559  '' since the stack grows downwards)
5560  ofs = sdsize - 4
5561  while( ofs >= 0 )
5562  hPrepOperand( svreg, src, FB_DATATYPE_INTEGER, ofs )
5563  outp( "push " + src )
5564  ofs -= 4
5565  wend
5566 
5567 end sub
5568 
5569 '':::::
5570 sub _emitPOPL _
5571  ( _
5572  byval dvreg as IRVREG ptr, _
5573  byval unused as integer _
5574  ) static
5575 
5576  dim dst1 as string, dst2 as string
5577  dim ostr as string
5578 
5579  hPrepOperand64( dvreg, dst1, dst2 )
5580 
5581  ostr = "pop " + dst1
5582  outp ostr
5583 
5584  ostr = "pop " + dst2
5585  outp ostr
5586 
5587 end sub
5588 
5589 '':::::
5590 sub _emitPOPI _
5591  ( _
5592  byval dvreg as IRVREG ptr, _
5593  byval unused as integer _
5594  ) static
5595 
5596  dim as string dst, ostr
5597  dim as integer dsize
5598 
5599  hPrepOperand( dvreg, dst )
5600 
5601  dsize = typeGetSize( dvreg->dtype )
5602 
5603  if( dvreg->typ = IR_VREGTYPE_IMM ) then
5604  '' gosub quirk: return-to-label needs to pop return address from the stack
5605  '' see ast-gosub.bas::astGosubAddReturn() - (jeffm)
5606 
5607  if( dvreg->value.i = 4 ) then
5608  if( hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX ) ) then
5609  hPOP "eax"
5610  else
5611  outp "add esp, 4"
5612  end if
5613  else
5614  ostr = "add esp, " + str( dvreg->value.i )
5615  outp ostr
5616  end if
5617 
5618  elseif( dsize = 4 ) then
5619  '' POP 4 bytes directly, no need for intermediate code
5620  ostr = "pop " + dst
5621  outp ostr
5622 
5623  else
5624  if( dvreg->typ = IR_VREGTYPE_REG ) then
5625  dst = *hGetRegName( FB_DATATYPE_INTEGER, dvreg->reg )
5626  ostr = "pop " + dst
5627  outp ostr
5628  else
5629  dim as integer reg, isfree
5630  dim as string aux8, aux16, aux32
5631 
5632  assert( (dsize = 1) or (dsize = 2) )
5633 
5634  reg = hFindRegNotInVreg( dvreg )
5635 
5636  aux8 = *hGetRegName( FB_DATATYPE_BYTE, reg )
5637  aux16 = *hGetRegName( FB_DATATYPE_SHORT, reg )
5638  aux32 = *hGetRegName( FB_DATATYPE_INTEGER, reg )
5639 
5640  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
5641 
5642  if( isfree ) then
5643  '' reg is free, overwrite with value from stack
5644  hMOV aux32, "dword ptr [esp]"
5645  else
5646  '' reg is used, swap it with value from stack,
5647  '' so the reg can be used with the new value,
5648  '' while its old value is preserved and
5649  '' restored later during the pop.
5650  hXCHG aux32, "dword ptr [esp]"
5651  end if
5652 
5653  '' Extract the wanted byte/short and store it
5654  if( dsize = 1 ) then
5655  hMOV dst, aux8
5656  else
5657  hMOV dst, aux16
5658  end if
5659 
5660  if( isfree ) then
5661  '' pop
5662  outp "add esp, 4"
5663  else
5664  '' pop and restore the preserved reg value
5665  hPOP aux32
5666  end if
5667  end if
5668 
5669  end if
5670 
5671 end sub
5672 
5673 
5674 '':::::
5675 sub _emitPOPF _
5676  ( _
5677  byval dvreg as IRVREG ptr, _
5678  byval unused as integer _
5679  ) static
5680 
5681  dim as string dst, ostr
5682  dim as integer dsize
5683 
5684  hPrepOperand( dvreg, dst )
5685 
5686  dsize = typeGetSize( dvreg->dtype )
5687 
5688  if( dvreg->typ <> IR_VREGTYPE_REG ) then
5689  if( dvreg->dtype = FB_DATATYPE_SINGLE ) then
5690  ostr = "pop " + dst
5691  outp ostr
5692  else
5693  hPrepOperand( dvreg, dst, FB_DATATYPE_INTEGER, 0 )
5694  ostr = "pop " + dst
5695  outp ostr
5696 
5697  hPrepOperand( dvreg, dst, FB_DATATYPE_INTEGER, 4 )
5698  ostr = "pop " + dst
5699  outp ostr
5700  end if
5701  else
5702  ostr = "fld " + dtypeTB(dvreg->dtype).mname + " [esp]"
5703  outp ostr
5704 
5705  ostr = "add esp," + str( dsize )
5706  outp ostr
5707  end if
5708 
5709 end sub
5710 
5711 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
5712 '' addressing
5713 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
5714 
5715 '':::::
5716 sub _emitADDROF _
5717  ( _
5718  byval dvreg as IRVREG ptr, _
5719  byval svreg as IRVREG ptr _
5720  ) static
5721 
5722  dim as string dst, src
5723  dim as string ostr
5724 
5725  hPrepOperand( dvreg, dst )
5726  hPrepOperand( svreg, src, , , , FALSE )
5727 
5728  ostr = "lea " + dst + ", " + src
5729  outp ostr
5730 
5731 end sub
5732 
5733 '':::::
5734 sub _emitDEREF _
5735  ( _
5736  byval dvreg as IRVREG ptr, _
5737  byval svreg as IRVREG ptr _
5738  ) static
5739 
5740  dim as string dst, src
5741  dim as string ostr
5742 
5743  hPrepOperand( dvreg, dst )
5744  hPrepOperand( svreg, src, FB_DATATYPE_UINT )
5745 
5746  ostr = "mov " + dst + COMMA + src
5747  outp ostr
5748 
5749 end sub
5750 
5751 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
5752 '' memory
5753 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
5754 
5755 '':::::
5756 sub hMemMoveRep _
5757  ( _
5758  byval dvreg as IRVREG ptr, _
5759  byval svreg as IRVREG ptr, _
5760  byval bytes as integer _
5761  ) static
5762 
5763  dim as string dst, src
5764  dim as string ostr
5765  dim as integer ecxfree, edifree, esifree
5766  dim as integer ediinsrc, ecxinsrc
5767 
5768  hPrepOperand( dvreg, dst )
5769  hPrepOperand( svreg, src )
5770 
5771  ecxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ECX )
5772  edifree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDI )
5773  esifree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ESI )
5774 
5775  ediinsrc = hIsRegInVreg( svreg, EMIT_REG_EDI )
5776  ecxinsrc = hIsRegInVreg( svreg, EMIT_REG_ECX )
5777 
5778  if( ecxfree = FALSE ) then
5779  hPUSH( "ecx" )
5780  end if
5781  if( edifree = FALSE ) then
5782  hPUSH( "edi" )
5783  end if
5784  if( esifree = FALSE ) then
5785  hPUSH( "esi" )
5786  end if
5787 
5788  if( ediinsrc = FALSE ) then
5789  if( dvreg->typ <> IR_VREGTYPE_REG ) then
5790  hMOV( "edi", dst )
5791  else
5792  '' not esi already?
5793  if( dvreg->reg <> EMIT_REG_EDI ) then
5794  hMOV( "edi", dst )
5795  end if
5796  end if
5797 
5798  else
5799  if( ecxinsrc ) then
5800  hPUSH( "ecx" )
5801  end if
5802 
5803  hMOV( "ecx", dst )
5804 
5805  if( ecxinsrc ) then
5806  outp "xchg ecx, [esp]"
5807  end if
5808  end if
5809 
5810  if( svreg->typ <> IR_VREGTYPE_REG ) then
5811  hMOV( "esi", src )
5812  else
5813  '' not esi already?
5814  if( svreg->reg <> EMIT_REG_ESI ) then
5815  hMOV( "esi", src )
5816  end if
5817  end if
5818 
5819  if( ediinsrc ) then
5820  if( ecxinsrc = FALSE ) then
5821  hMOV( "edi", "ecx" )
5822  else
5823  hPOP( "edi" )
5824  end if
5825  end if
5826 
5827  if( bytes > 4 ) then
5828  ostr = "mov ecx, " + str( cunsg(bytes) \ 4 )
5829  outp ostr
5830  outp "rep movsd"
5831 
5832  elseif( bytes = 4 ) then
5833  outp "mov ecx, [esi]"
5834  outp "mov [edi], ecx"
5835  if( (bytes and 3) > 0 ) then
5836  outp "add esi, 4"
5837  outp "add edi, 4"
5838  end if
5839  end if
5840 
5841  bytes and= 3
5842  if( bytes > 0 ) then
5843  if( bytes >= 2 ) then
5844  outp "mov cx, [esi]"
5845  outp "mov [edi], cx"
5846  if( bytes = 3 ) then
5847  outp "add esi, 2"
5848  outp "add edi, 2"
5849  end if
5850  end if
5851 
5852  if( (bytes and 1) <> 0 ) then
5853  outp "mov cl, [esi]"
5854  outp "mov [edi], cl"
5855  end if
5856  end if
5857 
5858  if( esifree = FALSE ) then
5859  hPOP( "esi" )
5860  end if
5861  if( edifree = FALSE ) then
5862  hPOP( "edi" )
5863  end if
5864  if( ecxfree = FALSE ) then
5865  hPOP( "ecx" )
5866  end if
5867 
5868 end sub
5869 
5870 '':::::
5871 sub hMemMoveBlk _
5872  ( _
5873  byval dvreg as IRVREG ptr, _
5874  byval svreg as IRVREG ptr, _
5875  byval bytes as integer _
5876  ) static
5877 
5878  dim as string dst, src, aux
5879  dim as integer i, ofs, reg, isfree
5880 
5881  reg = hFindRegNotInVreg( dvreg )
5882 
5883  '' no free regs left?
5884  if( hIsRegInVreg( svreg, reg ) ) then
5885  hMemMoveRep( dvreg, svreg, bytes )
5886  exit sub
5887  end if
5888 
5889  aux = *hGetRegName( FB_DATATYPE_INTEGER, reg )
5890 
5891  isfree = hIsRegFree( FB_DATACLASS_INTEGER, reg )
5892  if( isfree = FALSE ) then
5893  hPUSH( aux )
5894  end if
5895 
5896  ofs = 0
5897  '' move dwords
5898  for i = 1 to cunsg(bytes) \ 4
5899  hPrepOperand( svreg, src, FB_DATATYPE_INTEGER, ofs )
5900  hMOV( aux, src )
5901  hPrepOperand( dvreg, dst, FB_DATATYPE_INTEGER, ofs )
5902  hMOV( dst, aux )
5903  ofs += 4
5904  next
5905 
5906  '' a word left?
5907  if( (bytes and 2) <> 0 ) then
5908  aux = *hGetRegName( FB_DATATYPE_SHORT, reg )
5909  hPrepOperand( svreg, src, FB_DATATYPE_SHORT, ofs )
5910  hMOV( aux, src )
5911  hPrepOperand( dvreg, dst, FB_DATATYPE_SHORT, ofs )
5912  hMOV( dst, aux )
5913  ofs += 2
5914  end if
5915 
5916  '' a byte left?
5917  if( (bytes and 1) <> 0 ) then
5918  aux = *hGetRegName( FB_DATATYPE_BYTE, reg )
5919  hPrepOperand( svreg, src, FB_DATATYPE_BYTE, ofs )
5920  hMOV( aux, src )
5921  hPrepOperand( dvreg, dst, FB_DATATYPE_BYTE, ofs )
5922  hMOV( dst, aux )
5923  end if
5924 
5925  if( isfree = FALSE ) then
5926  hPOP( aux )
5927  end if
5928 
5929 end sub
5930 
5931 '':::::
5932 sub _emitMEMMOVE _
5933  ( _
5934  byval dvreg as IRVREG ptr, _
5935  byval svreg as IRVREG ptr, _
5936  byval bytes as integer, _
5937  byval extra as integer _
5938  ) static
5939 
5940  '' handle the assumption done at ast-node-mem::newMEM()
5941  if( culng( bytes ) > EMIT_MEMBLOCK_MAXLEN ) then
5942  hMemMoveRep( dvreg, svreg, bytes )
5943  else
5944  hMemMoveBlk( dvreg, svreg, bytes )
5945  end if
5946 
5947 end sub
5948 
5949 '':::::
5950 sub _emitMEMSWAP _
5951  ( _
5952  byval dvreg as IRVREG ptr, _
5953  byval svreg as IRVREG ptr, _
5954  byval bytes as integer, _
5955  byval extra as integer _
5956  ) static
5957 
5958  '' implemented as function
5959 
5960 end sub
5961 
5962 '':::::
5963 sub hMemClearRepIMM _
5964  ( _
5965  byval dvreg as IRVREG ptr, _
5966  byval bytes as ulong _
5967  ) static
5968 
5969  dim as string dst
5970  dim as string ostr
5971  dim as integer eaxfree, ecxfree, edifree
5972 
5973  hPrepOperand( dvreg, dst )
5974 
5975  eaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
5976  ecxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ECX )
5977  edifree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDI )
5978 
5979  if( eaxfree = FALSE ) then
5980  hPUSH( "eax" )
5981  end if
5982  if( ecxfree = FALSE ) then
5983  hPUSH( "ecx" )
5984  end if
5985  if( edifree = FALSE ) then
5986  hPUSH( "edi" )
5987  end if
5988 
5989  if( dvreg->typ <> IR_VREGTYPE_REG ) then
5990  hMOV( "edi", dst )
5991  else
5992  '' not edi already?
5993  if( dvreg->reg <> EMIT_REG_EDI ) then
5994  hMOV( "edi", dst )
5995  end if
5996  end if
5997 
5998  outp "xor eax, eax"
5999 
6000  if( bytes > 4 ) then
6001  ostr = "mov ecx, " + str( bytes \ 4 )
6002  outp ostr
6003  outp "rep stosd"
6004 
6005  elseif( bytes = 4 ) then
6006  outp "mov dword ptr [edi], eax"
6007  if( (bytes and 3) > 0 ) then
6008  outp "add edi, 4"
6009  end if
6010  end if
6011 
6012  bytes and= 3
6013  if( bytes > 0 ) then
6014  if( bytes >= 2 ) then
6015  outp "mov word ptr [edi], ax"
6016  if( bytes = 3 ) then
6017  outp "add edi, 2"
6018  end if
6019  end if
6020 
6021  if( (bytes and 1) <> 0 ) then
6022  outp "mov byte ptr [edi], al"
6023  end if
6024  end if
6025 
6026  if( edifree = FALSE ) then
6027  hPOP( "edi" )
6028  end if
6029  if( ecxfree = FALSE ) then
6030  hPOP( "ecx" )
6031  end if
6032  if( eaxfree = FALSE ) then
6033  hPOP( "eax" )
6034  end if
6035 
6036 end sub
6037 
6038 '':::::
6039 sub hMemClearBlkIMM _
6040  ( _
6041  byval dvreg as IRVREG ptr, _
6042  byval bytes as ulong _
6043  ) static
6044 
6045  dim as string dst
6046  dim as integer i, ofs
6047 
6048  ofs = 0
6049  '' move dwords
6050  for i = 1 to bytes \ 4
6051  hPrepOperand( dvreg, dst, FB_DATATYPE_INTEGER, ofs )
6052  hMOV( dst, "0" )
6053  ofs += 4
6054  next
6055 
6056  '' a word left?
6057  if( (bytes and 2) <> 0 ) then
6058  hPrepOperand( dvreg, dst, FB_DATATYPE_SHORT, ofs )
6059  hMOV( dst, "0" )
6060  ofs += 2
6061  end if
6062 
6063  '' a byte left?
6064  if( (bytes and 1) <> 0 ) then
6065  hPrepOperand( dvreg, dst, FB_DATATYPE_BYTE, ofs )
6066  hMOV( dst, "0" )
6067  end if
6068 
6069 end sub
6070 
6071 '':::::
6072 sub hMemClear _
6073  ( _
6074  byval dvreg as IRVREG ptr, _
6075  byval bytes_vreg as IRVREG ptr _
6076  ) static
6077 
6078  dim as string dst, bytes
6079  dim as string ostr
6080  dim as integer eaxfree, ecxfree, edifree
6081 
6082  hPrepOperand( dvreg, dst )
6083  hPrepOperand( bytes_vreg, bytes )
6084 
6085  eaxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EAX )
6086  ecxfree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_ECX )
6087  edifree = hIsRegFree( FB_DATACLASS_INTEGER, EMIT_REG_EDI )
6088 
6089  if( eaxfree = FALSE ) then
6090  hPUSH( "eax" )
6091  end if
6092  if( ecxfree = FALSE ) then
6093  hPUSH( "ecx" )
6094  end if
6095  if( edifree = FALSE ) then
6096  hPUSH( "edi" )
6097  end if
6098 
6099  if( hIsRegInVreg( bytes_vreg, EMIT_REG_EDI ) = FALSE ) then
6100  if( dvreg->typ <> IR_VREGTYPE_REG ) then
6101  hMOV( "edi", dst )
6102  else
6103  '' not edi already?
6104  if( dvreg->reg <> EMIT_REG_EDI ) then
6105  hMOV( "edi", dst )
6106  end if
6107  end if
6108 
6109  if( bytes_vreg->typ <> IR_VREGTYPE_REG ) then
6110  hMOV( "ecx", bytes )
6111  else
6112  '' not ecx already?
6113  if( bytes_vreg->reg <> EMIT_REG_ECX ) then
6114  hMOV( "ecx", bytes )
6115  end if
6116  end if
6117 
6118  else
6119  hPUSH( bytes )
6120 
6121  ostr = "lea edi, " + dst
6122  outp ostr
6123 
6124  hPOP( "ecx" )
6125  end if
6126 
6127  outp "xor eax, eax"
6128 
6129  outp "push ecx"
6130  outp "shr ecx, 2"
6131  outp "rep stosd"
6132  outp "pop ecx"
6133  outp "and ecx, 3"
6134  outp "rep stosb"
6135 
6136  if( edifree = FALSE ) then
6137  hPOP( "edi" )
6138  end if
6139  if( ecxfree = FALSE ) then
6140  hPOP( "ecx" )
6141  end if
6142  if( eaxfree = FALSE ) then
6143  hPOP( "eax" )
6144  end if
6145 
6146 end sub
6147 
6148 '':::::
6149 sub _emitMEMCLEAR _
6150  ( _
6151  byval dvreg as IRVREG ptr, _
6152  byval svreg as IRVREG ptr, _
6153  byval unused as integer, _
6154  byval extra as integer _
6155  )
6156 
6157  '' handle the assumption done at ast-node-mem::newMEM()
6158  if( irIsIMM( svreg ) ) then
6159  dim as ulong bytes = svreg->value.i
6160  if( bytes > EMIT_MEMBLOCK_MAXLEN ) then
6161  hMemClearRepIMM( dvreg, bytes )
6162  else
6163  hMemClearBlkIMM( dvreg, bytes )
6164  end if
6165 
6166  else
6167  hMemClear( dvreg, svreg )
6168  end if
6169 
6170 end sub
6171 
6172 '':::::
6173 sub _emitSTKCLEAR _
6174  ( _
6175  byval dvreg as IRVREG ptr, _
6176  byval svreg as IRVREG ptr, _
6177  byval bytes as integer, _
6178  byval baseofs as integer _
6179  ) static
6180 
6181  hClearLocals( bytes, baseofs )
6182 
6183 end sub
6184 
6185 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6186 '' debugging
6187 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6188 
6189 '':::::
6190 sub _emitLINEINI _
6191  ( _
6192  byval proc as FBSYMBOL ptr, _
6193  byval lnum as integer, _
6194  byval pos_ as integer _
6195  )
6196 
6197  edbgLineBegin( proc, lnum, pos_ )
6198 
6199 end sub
6200 
6201 '':::::
6202 sub _emitLINEEND _
6203  ( _
6204  byval proc as FBSYMBOL ptr, _
6205  byval lnum as integer, _
6206  byval pos_ as integer _
6207  )
6208 
6209  edbgLineEnd( proc, lnum, pos_ )
6210 
6211 end sub
6212 
6213 '':::::
6214 sub _emitSCOPEINI _
6215  ( _
6216  byval sym as FBSYMBOL ptr, _
6217  byval lnum as integer, _
6218  byval pos_ as integer _
6219  )
6220 
6221  edbgEmitScopeINI( sym )
6222 
6223 end sub
6224 
6225 '':::::
6226 sub _emitSCOPEEND _
6227  ( _
6228  byval sym as FBSYMBOL ptr, _
6229  byval lnum as integer, _
6230  byval pos_ as integer _
6231  )
6232 
6233  edbgEmitScopeEND( sym )
6234 
6235 end sub
6236 
6237 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6238 '' initializers
6239 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6240 
6241 sub emitVARINIBEGIN( byval sym as FBSYMBOL ptr )
6242  _setSection( IR_SECTION_DATA, 0 )
6243 
6244  '' add dbg info, if public or shared
6245  'if( (symbGetAttrib( sym ) and (FB_SYMBATTRIB_SHARED or FB_SYMBATTRIB_PUBLIC)) > 0 ) then
6246  edbgEmitGlobalVar( sym, IR_SECTION_DATA )
6247  'end if
6248 
6249  if( symbGetType( sym ) = FB_DATATYPE_DOUBLE ) then
6250  hALIGN( 8 )
6251  else
6252  hALIGN( 4 )
6253  end if
6254 
6255  '' public?
6256  if( symbIsPublic( sym ) ) then
6257  hPUBLIC( *symbGetMangledName( sym ), symbIsExport( sym ) )
6258  end if
6259 
6260  hLABEL( *symbGetMangledName( sym ) )
6261 end sub
6262 
6263 sub emitVARINIi( byval dtype as integer, byval value as integer )
6264  outEx( *_getTypeString( dtype ) + " " + str( value ) + NEWLINE )
6265 end sub
6266 
6267 sub emitVARINIf( byval dtype as integer, byval value as double )
6268  '' can't use STR() because GAS doesn't support the 1.#INF notation
6269  outEx( *_getTypeString( dtype ) + " " + hFloatToHex( value, dtype ) + NEWLINE )
6270 end sub
6271 
6272 sub emitVARINI64( byval dtype as integer, byval value as longint )
6273  outEx( *_getTypeString( dtype ) + " 0x" + hex( value ) + NEWLINE )
6274 end sub
6275 
6276 sub emitVARINIOFS( byval sname as zstring ptr, byval ofs as integer )
6277  static as string ostr
6278  ostr = ".int "
6279  ostr += *sname
6280  if( ofs <> 0 ) then
6281  ostr += " + "
6282  ostr += str( ofs )
6283  end if
6284  ostr += NEWLINE
6285  outEx( ostr )
6286 end sub
6287 
6288 sub emitVARINISTR( byval s as const zstring ptr )
6289  static as string ostr
6290  ostr = ".ascii " + QUOTE
6291  ostr += *s
6292  ostr += RSLASH + "0" + QUOTE + NEWLINE
6293  outEx( ostr )
6294 end sub
6295 
6296 sub emitVARINIWSTR( byval s as zstring ptr )
6297  static as string ostr
6298  ostr = ".ascii " + QUOTE
6299  ostr += *s
6300  for i as integer = 1 to typeGetSize( FB_DATATYPE_WCHAR )
6301  ostr += RSLASH + "0"
6302  next
6303  ostr += QUOTE + NEWLINE
6304  outEx( ostr )
6305 end sub
6306 
6307 sub emitVARINIPAD( byval bytes as integer )
6308  outEx( ".skip " + str( bytes ) + ",0" + NEWLINE )
6309 end sub
6310 
6312  _setSection( IR_SECTION_INFO, 0 )
6313 end sub
6314 
6315 sub emitFBCTINFSTRING( byval s as zstring ptr )
6316  static as string ln
6317  ln = *emit.vtbl.getTypeString( FB_DATATYPE_CHAR )
6318  ln += " """ + *s + $"\0"""
6319  emitWriteStr( ln )
6320 end sub
6321 
6323  emitWriteStr( "" )
6324 end sub
6325 
6326 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6327 '' functions table
6328 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6329 
6330 #define EMIT_CBENTRY(op) @_emit##op##
6331 
6332  '' same order as EMIT_NODEOP
6333  dim shared _opFnTB(0 to EMIT_MAXOPS-1) as any ptr => _
6334  { _
6335  EMIT_CBENTRY(NOP), _
6336  _
6337  EMIT_CBENTRY(LOADI2I), EMIT_CBENTRY(LOADF2I), EMIT_CBENTRY(LOADL2I), _
6338  EMIT_CBENTRY(LOADI2F), EMIT_CBENTRY(LOADF2F), EMIT_CBENTRY(LOADL2F), _
6339  EMIT_CBENTRY(LOADI2L), EMIT_CBENTRY(LOADF2L), EMIT_CBENTRY(LOADL2L), _
6340  _
6341  EMIT_CBENTRY(STORI2I), EMIT_CBENTRY(STORF2I), EMIT_CBENTRY(STORL2I), _
6342  EMIT_CBENTRY(STORI2F), EMIT_CBENTRY(STORF2F), EMIT_CBENTRY(STORL2F), _
6343  EMIT_CBENTRY(STORI2L), EMIT_CBENTRY(STORF2L), EMIT_CBENTRY(STORL2L), _
6344  _
6345  EMIT_CBENTRY(MOVI), EMIT_CBENTRY(MOVF), EMIT_CBENTRY(MOVL), _
6346  EMIT_CBENTRY(ADDI), EMIT_CBENTRY(ADDF), EMIT_CBENTRY(ADDL), _
6347  EMIT_CBENTRY(SUBI), EMIT_CBENTRY(SUBF), EMIT_CBENTRY(SUBL), _
6348  EMIT_CBENTRY(MULI), EMIT_CBENTRY(MULF), EMIT_CBENTRY(MULL), _
6349  EMIT_CBENTRY(DIVI), EMIT_CBENTRY(DIVF), NULL , _
6350  EMIT_CBENTRY(MODI), NULL , NULL , _
6351  EMIT_CBENTRY(SHLI), EMIT_CBENTRY(SHLL), _
6352  EMIT_CBENTRY(SHRI), EMIT_CBENTRY(SHRL), _
6353  EMIT_CBENTRY(ANDI), EMIT_CBENTRY(ANDL), _
6354  EMIT_CBENTRY(ORI) , EMIT_CBENTRY(ORL) , _
6355  EMIT_CBENTRY(XORI), EMIT_CBENTRY(XORL), _
6356  EMIT_CBENTRY(EQVI), EMIT_CBENTRY(EQVL), _
6357  EMIT_CBENTRY(IMPI), EMIT_CBENTRY(IMPL), _
6358  EMIT_CBENTRY(ATN2), _
6359  EMIT_CBENTRY(POW), _
6360  EMIT_CBENTRY(ADDROF), _
6361  EMIT_CBENTRY(DEREF), _
6362  _
6363  EMIT_CBENTRY(CGTI), EMIT_CBENTRY(CGTF), EMIT_CBENTRY(CGTL), _
6364  EMIT_CBENTRY(CLTI), EMIT_CBENTRY(CLTF), EMIT_CBENTRY(CLTL), _
6365  EMIT_CBENTRY(CEQI), EMIT_CBENTRY(CEQF), EMIT_CBENTRY(CEQL), _
6366  EMIT_CBENTRY(CNEI), EMIT_CBENTRY(CNEF), EMIT_CBENTRY(CNEL), _
6367  EMIT_CBENTRY(CGEI), EMIT_CBENTRY(CGEF), EMIT_CBENTRY(CGEL), _
6368  EMIT_CBENTRY(CLEI), EMIT_CBENTRY(CLEF), EMIT_CBENTRY(CLEL), _
6369  _
6370  EMIT_CBENTRY(NEGI), EMIT_CBENTRY(NEGF), EMIT_CBENTRY(NEGL), _
6371  EMIT_CBENTRY(NOTI), EMIT_CBENTRY(NOTL), _
6372  _
6373  NULL, _
6374  _
6375  EMIT_CBENTRY(ABSI), EMIT_CBENTRY(ABSF), EMIT_CBENTRY(ABSL), _
6376  EMIT_CBENTRY(SGNI), EMIT_CBENTRY(SGNF), EMIT_CBENTRY(SGNL), _
6377  _
6378  EMIT_CBENTRY(FIX), _
6379  EMIT_CBENTRY(FRAC), _
6380  EMIT_CBENTRY(CONVFD2FS), _
6381  _
6382  NULL, _
6383  _
6384  EMIT_CBENTRY(SIN), EMIT_CBENTRY(ASIN), _
6385  EMIT_CBENTRY(COS), EMIT_CBENTRY(ACOS), _
6386  EMIT_CBENTRY(TAN), EMIT_CBENTRY(ATAN), _
6387  EMIT_CBENTRY(SQRT), _
6388  _
6389  NULL, _
6390  NULL, _
6391  _
6392  EMIT_CBENTRY(LOG), _
6393  EMIT_CBENTRY(EXP), _
6394  EMIT_CBENTRY(FLOOR), _
6395  EMIT_CBENTRY(XCHGTOS), _
6396  _
6397  EMIT_CBENTRY(STACKALIGN), _
6398  EMIT_CBENTRY(PUSHI), EMIT_CBENTRY(PUSHF), EMIT_CBENTRY(PUSHL), _
6399  EMIT_CBENTRY(POPI), EMIT_CBENTRY(POPF), EMIT_CBENTRY(POPL), _
6400  EMIT_CBENTRY(PUSHUDT), _
6401  _
6402  EMIT_CBENTRY(CALL), _
6403  EMIT_CBENTRY(CALLPTR), _
6404  EMIT_CBENTRY(BRANCH), _
6405  EMIT_CBENTRY(JUMP), _
6406  EMIT_CBENTRY(JUMPPTR), _
6407  EMIT_CBENTRY(RET), _
6408  _
6409  EMIT_CBENTRY(LABEL), _
6410  EMIT_CBENTRY(PUBLIC), _
6411  EMIT_CBENTRY(LIT), _
6412  EMIT_CBENTRY(JMPTB), _
6413  _
6414  EMIT_CBENTRY(MEMMOVE), _
6415  EMIT_CBENTRY(MEMSWAP), _
6416  EMIT_CBENTRY(MEMCLEAR), _
6417  EMIT_CBENTRY(STKCLEAR), _
6418  _
6419  EMIT_CBENTRY(LINEINI), _
6420  EMIT_CBENTRY(LINEEND), _
6421  EMIT_CBENTRY(SCOPEINI), _
6422  EMIT_CBENTRY(SCOPEEND) _
6423  }
6424 
6425 
6426 
6427 '':::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6428 '' emit.vtbl implementation
6429 '':::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6430 
6431 '':::::
6432 function _init _
6433  ( _
6434  ) as integer
6435 
6436  ''
6437  hInitRegTB( )
6438 
6439  '' Remap wchar to target-specific type
6440  dtypeTB(FB_DATATYPE_WCHAR) = dtypeTB(env.target.wchar)
6441 
6442  ''
6443  emit.keyinited = FALSE
6444 
6445  ''
6446  emit.lastsection = INVALID
6447  emit.lastpriority = INVALID
6448 
6449  dim as uinteger iroptions = _
6450  IR_OPT_CPUSELFBOPS or IR_OPT_CPUBOPFLAGS or _
6451  IR_OPT_ADDRCISC
6452 
6453  if( env.clopt.fputype = FB_FPUTYPE_SSE ) then
6454  iroptions or= IR_OPT_FPUCONV
6455  end if
6456 
6457  irSetOption( iroptions )
6458 
6459  edbgInit( )
6460 
6461  function = TRUE
6462 
6463 end function
6464 
6465 '':::::
6466 sub _end
6467 
6468  ''
6469  emit.lastsection = INVALID
6470  emit.lastpriority = INVALID
6471 
6472  ''
6473  hEndRegTB( )
6474 
6475  hEndKeywordsTB( )
6476 
6477 end sub
6478 
6479 '':::::
6480 function _getOptionValue _
6481  ( _
6482  byval opt as IR_OPTIONVALUE _
6483  ) as integer
6484 
6485  select case opt
6486  case IR_OPTIONVALUE_MAXMEMBLOCKLEN
6487  return EMIT_MEMBLOCK_MAXLEN
6488 
6489  case else
6490  errReportEx( FB_ERRMSG_INTERNAL, __FUNCTION__ )
6491 
6492  end select
6493 
6494 end function
6495 
6496 
6497 '':::::
6498 function _open _
6499  ( _
6500  ) as integer
6501 
6502  if( hFileExists( env.outf.name ) ) then
6503  kill env.outf.name
6504  end if
6505 
6506  env.outf.num = freefile
6507  if( open( env.outf.name, for binary, access read write, as #env.outf.num ) <> 0 ) then
6508  return FALSE
6509  end if
6510 
6511  '' header
6512  hWriteHeader( )
6513 
6514  function = TRUE
6515 
6516 end function
6517 
6518 '':::::
6519 sub _close _
6520  ( _
6521  byval tottime as double _
6522  )
6523 
6524  hCOMMENT( env.inf.name + "' compilation took " + str( tottime ) + " secs" )
6525 
6526  '' Close any STABS #include block (and return to the toplevel .bas
6527  '' file name) before emitting the global vars
6528  edbgInclude( NULL )
6529 
6530  '' const
6531  hWriteConst( symbGetGlobalTbHead( ) )
6532 
6533  '' data
6534  hWriteData( symbGetGlobalTbHead( ) )
6535 
6536  '' bss
6537  hWriteBss( symbGetGlobalTbHead( ) )
6538 
6539  ''
6540  if( env.clopt.export and (env.target.options and FB_TARGETOPT_EXPORT) ) then
6541  hWriteExport( symbGetGlobalTbHead( ) )
6542  end if
6543 
6544  ''
6545  hWriteCtor( symbGetGlobCtorListHead( ), TRUE )
6546  hWriteCtor( symbGetGlobDtorListHead( ), FALSE )
6547 
6548  ''
6549  edbgEmitFooter( )
6550 
6551  ''
6552  if( close( #env.outf.num ) <> 0 ) then
6553  '' ...
6554  end if
6555 
6556  env.outf.num = 0
6557 
6558 end sub
6559 
6560 '':::::
6561 function _procGetFrameRegName _
6562  ( _
6563  ) as const zstring ptr
6564 
6565  static as zstring * 3+1 sname = "ebp"
6566 
6567  function = @sname
6568 
6569 end function
6570 
6571 '':::::
6572 function _isRegPreserved _
6573  ( _
6574  byval dclass as integer, _
6575  byval reg as integer _
6576  ) as integer static
6577 
6578  '' fp? fpu stack *must* be cleared before calling any function
6579  if( dclass = FB_DATACLASS_FPOINT ) then
6580  return FALSE
6581  end if
6582 
6583  select case as const reg
6584  case EMIT_REG_EAX, EMIT_REG_ECX, EMIT_REG_EDX
6585  return FALSE
6586  case else
6587  return TRUE
6588  end select
6589 
6590 end function
6591 
6592 '':::::
6593 sub _getResultReg _
6594  ( _
6595  byval dtype as integer, _
6596  byval dclass as integer, _
6597  byref r1 as integer, _
6598  byref r2 as integer _
6599  )
6600 
6601  if( dclass = FB_DATACLASS_INTEGER ) then
6602  r1 = EMIT_REG_EAX
6603  if( ISLONGINT( typeGet( dtype ) ) ) then
6604  r2 = EMIT_REG_EDX
6605  else
6606  r2 = INVALID
6607  end if
6608  else
6609  r1 = 0 '' st(0)
6610  r2 = INVALID
6611  end if
6612 
6613 end sub
6614 
6615 '':::::
6616 function _getFreePreservedReg _
6617  ( _
6618  byval dclass as integer, _
6619  byval dtype as integer _
6620  ) as integer static
6621 
6622  function = INVALID
6623 
6624  '' fp? no other regs can be used
6625  if( dclass = FB_DATACLASS_FPOINT ) then
6626  exit function
6627  end if
6628 
6629  '' try to reuse regs that are preserved between calls
6630  if( emit.regTB(dclass)->isFree( emit.regTB(dclass), EMIT_REG_EBX ) ) then
6631  function = EMIT_REG_EBX
6632 
6633  elseif( emit.regTB(dclass)->isFree( emit.regTB(dclass), EMIT_REG_ESI ) ) then
6634  if( typeGetSize( dtype ) <> 1 ) then
6635  function = EMIT_REG_ESI
6636  end if
6637 
6638  elseif( emit.regTB(dclass)->isFree( emit.regTB(dclass), EMIT_REG_EDI ) ) then
6639  if( typeGetSize( dtype ) <> 1 ) then
6640  function = EMIT_REG_EDI
6641  end if
6642  end if
6643 
6644 end function
6645 
6646 '':::::
6647 function _isKeyword _
6648  ( _
6649  byval text as zstring ptr _
6650  ) as integer static
6651 
6652  if( emit.keyinited = FALSE ) then
6653  hInitKeywordsTB( )
6654  end if
6655 
6656  function = (hashLookup( @emit.keyhash, text ) <> NULL)
6657 
6658 end function
6659 
6660 '':::::
6661 sub _procBegin _
6662  ( _
6663  byval proc as FBSYMBOL ptr _
6664  )
6665 
6666  proc->proc.ext->stk.localofs = EMIT_LOCSTART
6667  proc->proc.ext->stk.localmax = EMIT_LOCSTART
6668  proc->proc.ext->stk.argofs = EMIT_ARGSTART
6669 
6670  edbgProcBegin( proc )
6671 
6672 end sub
6673 
6674 '':::::
6675 sub _procEnd _
6676  ( _
6677  byval proc as FBSYMBOL ptr _
6678  )
6679 
6680  edbgProcEnd( proc )
6681 
6682 end sub
6683 
6684 sub _procAllocStaticVars( byval s as FBSYMBOL ptr )
6685  while( s )
6686  select case( symbGetClass( s ) )
6687  '' scope block? recursion..
6688  case FB_SYMBCLASS_SCOPE
6689  _procAllocStaticVars( symbGetScopeSymbTbHead( s ) )
6690 
6691  '' variable?
6692  case FB_SYMBCLASS_VAR
6693  '' static?
6694  if( symbIsStatic( s ) ) then
6695  hDeclVariable( s )
6696  end if
6697  end select
6698 
6699  s = symbGetNext( s )
6700  wend
6701 end sub
6702 
6703 sub _procAllocLocal _
6704  ( _
6705  byval proc as FBSYMBOL ptr, _
6706  byval sym as FBSYMBOL ptr _
6707  )
6708 
6709  dim as integer ofs = any, lgt = any
6710 
6711  lgt = symbGetLen( sym ) * symbGetArrayElements( sym )
6712 
6713  proc->proc.ext->stk.localofs += ((lgt + 3) and not 3)
6714 
6715  ofs = -proc->proc.ext->stk.localofs
6716 
6717  if( -ofs > proc->proc.ext->stk.localmax ) then
6718  proc->proc.ext->stk.localmax = -ofs
6719  end if
6720 
6721  sym->ofs = ofs
6722 
6723 end sub
6724 
6725 sub _procAllocArg _
6726  ( _
6727  byval proc as FBSYMBOL ptr, _
6728  byval sym as FBSYMBOL ptr _
6729  )
6730 
6731  dim as integer lgt = any
6732 
6733  assert( symbIsParam( sym ) )
6734 
6735  if( symbIsParamByVal( sym ) ) then
6736  lgt = symbGetLen( sym )
6737  else
6738  lgt = 4 '' it's just a pointer
6739  end if
6740 
6741  sym->ofs = proc->proc.ext->stk.argofs
6742  proc->proc.ext->stk.argofs += ((lgt + 3) and not 3)
6743 
6744 end sub
6745 
6746 '':::::
6747 sub _procHeader _
6748  ( _
6749  byval proc as FBSYMBOL ptr, _
6750  byval initlabel as FBSYMBOL ptr _
6751  )
6752 
6753  '' do nothing, proc will be only emitted at PROCFOOTER
6754 
6755  emitReset( )
6756 
6758 
6759 end sub
6760 
6761 '':::::
6762 sub _procFooter _
6763  ( _
6764  byval proc as FBSYMBOL ptr, _
6765  byval bytestopop as integer, _
6766  byval initlabel as FBSYMBOL ptr, _
6767  byval exitlabel as FBSYMBOL ptr _
6768  )
6769 
6770  dim as integer oldpos = any, ispublic = any
6771 
6772  ispublic = symbIsPublic( proc )
6773 
6774  _setSection( IR_SECTION_CODE, 0 )
6775 
6776  ''
6778 
6779  ''
6780  hALIGN( 16 )
6781 
6782  if( ispublic ) then
6783  hPUBLIC( symbGetMangledName( proc ), symbIsExport( proc ) )
6784  end if
6785 
6787 
6788  if( env.clopt.target = FB_COMPTARGET_LINUX ) then
6789  outEx( ".type " + *symbGetMangledName( proc ) + ", @function" + NEWLINE )
6790  end if
6791 
6792  '' frame
6793  hCreateFrame( proc )
6794 
6795  edbgEmitLineFlush( proc, proc->proc.ext->dbg.iniline, proc )
6796 
6797  ''
6798  emitFlush( )
6799 
6800  ''
6801  hDestroyFrame( proc, bytestopop )
6802 
6803  edbgEmitLineFlush( proc, proc->proc.ext->dbg.endline, exitlabel )
6804 
6805  edbgEmitProcFooter( proc, initlabel, exitlabel )
6806 
6807 end sub
6808 
6809 '':::::
6810 sub _scopeBegin _
6811  ( _
6812  byval s as FBSYMBOL ptr _
6813  )
6814 
6815  edbgScopeBegin( s )
6816 
6817 end sub
6818 
6819 '':::::
6820 sub _scopeEnd _
6821  ( _
6822  byval s as FBSYMBOL ptr _
6823  )
6824 
6825  edbgScopeEnd( s )
6826 
6827 end sub
6828 
6829 '':::::
6830 sub _setSection _
6831  ( _
6832  byval section as integer, _
6833  byval priority as integer _
6834  )
6835 
6836  dim as const zstring ptr sec = _getSectionString( section, priority )
6837  if( sec = NULL ) then
6838  exit sub
6839  end if
6840 
6841  static as string ostr
6842 
6843  ostr = *sec
6844  ostr += NEWLINE
6845 
6846  outEx( ostr )
6847 
6848 end sub
6849 
6850 function _getTypeString( byval dtype as integer ) as const zstring ptr
6851  select case as const typeGet( dtype )
6852  case FB_DATATYPE_UBYTE, FB_DATATYPE_BYTE
6853  function = @".byte"
6854  case FB_DATATYPE_USHORT, FB_DATATYPE_SHORT
6855  function = @".short"
6856  case FB_DATATYPE_INTEGER, FB_DATATYPE_UINT, FB_DATATYPE_ENUM
6857  function = @".int"
6858  case FB_DATATYPE_LONG, FB_DATATYPE_ULONG, FB_DATATYPE_SINGLE
6859  '' SINGLE: emitted as raw bytes in form of .long 0x...,
6860  '' instead of .float 1.234...,
6861  '' to allow the exact bytes to be emitted by hFloatToHex(),
6862  '' instead of a str() approximation.
6863  function = @".long"
6864  case FB_DATATYPE_LONGINT, FB_DATATYPE_ULONGINT, FB_DATATYPE_DOUBLE
6865  '' DOUBLE: ditto, instead of .double
6866  function = @".quad"
6867  case FB_DATATYPE_FIXSTR, FB_DATATYPE_CHAR, FB_DATATYPE_WCHAR
6868  '' wchar stills the same as it is emitted as escape sequences
6869  function = @".ascii"
6870  case FB_DATATYPE_STRING, FB_DATATYPE_STRUCT
6871  function = @".INVALID"
6872  case FB_DATATYPE_POINTER
6873  function = @".long"
6874  case else
6875  function = @".INVALID"
6876  end select
6877 end function
6878 
6879 '':::::
6880 function _getSectionString _
6881  ( _
6882  byval section as integer, _
6883  byval priority as integer _
6884  ) as const zstring ptr
6885 
6886  static as string ostr
6887 
6888  if( (section = emit.lastsection) and (priority = emit.lastpriority) ) then
6889  return NULL
6890  end if
6891 
6892  ostr = NEWLINE
6893 
6894  '' Omit the .section directive on Darwin
6895  if (fbGetOption( FB_COMPOPT_TARGET ) <> FB_COMPTARGET_DARWIN) then
6896  ostr += ".section "
6897  end if
6898 
6899  ostr += "."
6900 
6901  select case as const section
6902  case IR_SECTION_CONST
6903  select case as const fbGetOption( FB_COMPOPT_TARGET )
6904  case FB_COMPTARGET_CYGWIN, FB_COMPTARGET_DOS, _
6905  FB_COMPTARGET_WIN32, FB_COMPTARGET_XBOX
6906  ostr += "rdata"
6907 
6908  case FB_COMPTARGET_DARWIN
6909  ostr += "const"
6910 
6911  case else
6912  ostr += "rodata"
6913 
6914  end select
6915 
6916  case IR_SECTION_DATA
6917  ostr += "data"
6918 
6919  case IR_SECTION_BSS
6920  ostr += "bss"
6921 
6922  case IR_SECTION_CODE
6923  ostr += "text"
6924 
6925  case IR_SECTION_DIRECTIVE
6926  ostr += "drectve"
6927 
6928  case IR_SECTION_INFO
6929  ostr += FB_INFOSEC_NAME
6930 
6931  case IR_SECTION_CONSTRUCTOR
6932  ostr += "ctors"
6933  if( priority > 0 ) then
6934  ostr += "." + right( "00000" + str( 65535 - priority ), 5 )
6935  end if
6936  if( env.clopt.target = FB_COMPTARGET_LINUX ) then
6937  ostr += ", " + QUOTE + "aw" + QUOTE + ", @progbits"
6938  end if
6939 
6940  case IR_SECTION_DESTRUCTOR
6941  ostr += "dtors"
6942  if( priority > 0 ) then
6943  ostr += "." + right( "00000" + str( 65535 - priority ), 5 )
6944  end if
6945  if( env.clopt.target = FB_COMPTARGET_LINUX ) then
6946  ostr += ", " + QUOTE + "aw" + QUOTE + ", @progbits"
6947  end if
6948 
6949  end select
6950 
6951  function = strptr( ostr )
6952 
6953  emit.lastsection = section
6954  emit.lastpriority = priority
6955 
6956 end function
6957 
6958 
6959 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6960 '' initialization/finalization
6961 ''::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
6962 
6963 '':::::
6964 function emitGasX86_ctor _
6965  ( _
6966  ) as integer
6967 
6968  static as EMIT_VTBL _vtbl = _
6969  ( _
6970  @_init, _
6971  @_end, _
6972  @_getOptionValue, _
6973  @_open, _
6974  @_close, _
6975  @_isKeyword, _
6976  @_isRegPreserved, _
6978  @_getResultReg, _
6980  @_procBegin, _
6981  @_procEnd, _
6982  @_procHeader, _
6983  @_procFooter, _
6984  @_procAllocArg, _
6985  @_procAllocLocal, _
6987  @_scopeBegin, _
6988  @_scopeEnd, _
6989  @_setSection, _
6990  @_getTypeString, _
6992  )
6993 
6994  emit.vtbl = _vtbl
6995  emit.opFnTb = @_opFnTB(0)
6996 
6997  if( env.clopt.fputype >= FB_FPUTYPE_SSE ) then
6998  _init_opFnTB_SSE( emit.opFnTb )
6999  end if
7000 
7001  function = TRUE
7002 
7003 end function
7004 
7005 
7006