Initial commit: 0.4.3.0 from hackage
[harpy.git] / Harpy / X86Assembler.hs
1 {-# LANGUAGE MultiParamTypeClasses,FlexibleInstances,FunctionalDependencies #-}
2 --------------------------------------------------------------------------
3 -- |
4 -- Module      :  Harpy.X86Assembler
5 -- Copyright   :  (c) 2006-2007 Martin Grabmueller and Dirk Kleeblatt
6 -- License     :  GPL
7 -- 
8 -- Maintainer  :  {magr,klee}@cs.tu-berlin.de
9 -- Stability   :  provisional
10 -- Portability :  non-portable
11 --
12 -- A type class based layer on top of X86CodeGen
13 -- which determines the addressing modes from the types of the
14 -- operands.
15 --------------------------------------------------------------------------
16 module Harpy.X86Assembler (
17    module Harpy.X86Assembler,
18    XMMReg(..),
19    ) where
20
21 import Harpy.X86CodeGen
22 import Harpy.CodeGenMonad
23 import Data.Word
24 import Foreign.Ptr
25
26 import qualified Text.PrettyPrint.HughesPJ as PP
27
28
29 -- address modes used in this module:
30
31 -- Word8/16/32               immediate values
32 -- Reg8/16/32                register
33 -- Addr Word32               absolut
34 -- Ind Reg32                 register indirect
35 -- (Disp, Reg32)                     register indirect with displacement
36 -- (Reg32, Reg32, Scale)             (base, index, scale), effective address is (base + index * scale)
37 -- (Disp, Reg32, Scale)      (disp, index, scale), effective address is (disp + index * scale)
38 -- (Disp, Reg32, Reg32, Scale)  (base, index, scale) + displacement (only ebp is allowed as base register)
39 -- Label                        not-yet-specified label
40
41 onlyEbp = failCodeGen (PP.text "only epb is allowed as base register for disp/base/index/scale addressing")
42 onlyCl  = failCodeGen (PP.text "only cl is allowed as shift count")
43
44
45 -- x86 Registers
46
47 newtype Reg8 = Reg8 Word8
48 al, cl, dl, bl, ah, ch, dh, bh :: Reg8
49
50 al = Reg8 0
51 cl = Reg8 1
52 dl = Reg8 2
53 bl = Reg8 3
54 ah = Reg8 4
55 ch = Reg8 5
56 dh = Reg8 6
57 bh = Reg8 7
58
59 newtype Reg16 = Reg16 Word8
60 ax, cx, dx, bx, sp, bp, si, di :: Reg16
61
62 ax = Reg16 0
63 cx = Reg16 1
64 dx = Reg16 2
65 bx = Reg16 3
66 sp = Reg16 4
67 bp = Reg16 5
68 si = Reg16 6
69 di = Reg16 7
70
71 newtype Reg32 = Reg32 Word8 deriving (Eq, Ord)
72 eax, ecx, edx, ebx, esp, ebp, esi, edi :: Reg32
73
74 eax = Reg32 0
75 ecx = Reg32 1
76 edx = Reg32 2
77 ebx = Reg32 3
78 esp = Reg32 4
79 ebp = Reg32 5
80 esi = Reg32 6
81 edi = Reg32 7
82
83 {-
84 newtype XMMReg = XMMReg Word8
85     deriving (Eq, Ord)
86 -}
87
88 xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7 :: XMMReg
89 xmm0 = XMMReg 0
90 xmm1 = XMMReg 1
91 xmm2 = XMMReg 2
92 xmm3 = XMMReg 3
93 xmm4 = XMMReg 4
94 xmm5 = XMMReg 5
95 xmm6 = XMMReg 6
96 xmm7 = XMMReg 7
97
98 instance Show XMMReg where
99     show (XMMReg i) = "xmm" ++ show i
100
101 -- TODO: instances for other registers
102
103 instance Show Reg32 where
104  show (Reg32 0) = "eax"
105  show (Reg32 1) = "ecx"
106  show (Reg32 2) = "edx"
107  show (Reg32 3) = "ebx"
108  show (Reg32 4) = "esp"
109  show (Reg32 5) = "ebp"
110  show (Reg32 6) = "esi"
111  show (Reg32 7) = "edi"
112
113 -- memory addresses
114
115 newtype Addr  = Addr Word32
116 newtype Ind   = Ind Reg32
117 newtype Disp  = Disp Word32
118
119 data    Scale = S1 | S2 | S4 | S8
120
121 scaleToShift :: Scale -> Word8
122 scaleToShift S1 = 0
123 scaleToShift S2 = 1
124 scaleToShift S4 = 2
125 scaleToShift S8 = 3
126
127 newtype FPReg = FPReg Word8
128
129 data FPTopReg = FPTopReg
130
131 fpTop = FPTopReg
132
133 fp0 = FPReg 0
134 fp1 = FPReg 1
135 fp2 = FPReg 2
136 fp3 = FPReg 3
137 fp4 = FPReg 4
138 fp5 = FPReg 5
139 fp6 = FPReg 6
140 fp7 = FPReg 7
141
142 -- int 3
143
144 breakpoint = ensureBufferSize x86_max_instruction_bytes >> x86_breakpoint
145
146
147 -- clear direction flag
148
149 cld = ensureBufferSize x86_max_instruction_bytes >> x86_cld
150
151
152 -- store string
153
154 stosb = ensureBufferSize x86_max_instruction_bytes >> x86_stosb
155 stosl = ensureBufferSize x86_max_instruction_bytes >> x86_stosl
156 stosd = ensureBufferSize x86_max_instruction_bytes >> x86_stosd
157
158
159 -- move string
160
161 movsb = ensureBufferSize x86_max_instruction_bytes >> x86_movsb
162 movsl = ensureBufferSize x86_max_instruction_bytes >> x86_movsl
163 --movsd = ensureBufferSize x86_max_instruction_bytes >> x86_movsd
164
165
166 -- read time stamp counter
167
168 rdtsc = ensureBufferSize x86_max_instruction_bytes >> x86_rdtsc
169
170
171 -- compare and exchange
172
173 class Cmpxchg a b where
174   cmpxchg :: a -> b -> CodeGen e s ()
175
176 instance Cmpxchg Reg32 Reg32 where
177   cmpxchg (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmpxchg_reg_reg dest source
178
179 instance Cmpxchg Addr Reg32 where
180   cmpxchg (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmpxchg_mem_reg dest source
181
182 instance Cmpxchg (Disp, Reg32) Reg32 where
183   cmpxchg (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmpxchg_membase_reg dest disp source
184
185 instance Cmpxchg Ind Reg32 where
186   cmpxchg (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmpxchg_membase_reg dest 0 source
187
188
189
190 -- exchange memory/register with register
191
192 class Xchg a b where
193   xchg :: a -> b -> CodeGen e s ()
194
195 instance Xchg Reg8 Reg8 where
196   xchg (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_reg_reg dest source 1
197
198 instance Xchg Reg32 Reg32 where
199   xchg (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_reg_reg dest source 4
200
201 instance Xchg Addr Reg8 where
202   xchg (Addr dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_mem_reg dest source 1
203
204 instance Xchg Addr Reg32 where
205   xchg (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_mem_reg dest source 4
206
207 instance Xchg (Disp, Reg32) Reg8 where
208   xchg (Disp disp, Reg32 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_membase_reg dest disp source 1
209
210 instance Xchg Ind Reg8 where
211   xchg (Ind (Reg32 dest)) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_membase_reg dest 0 source 1
212
213 instance Xchg (Disp, Reg32) Reg32 where
214   xchg (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_membase_reg dest disp source 4
215
216 instance Xchg Ind Reg32 where
217   xchg (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xchg_membase_reg dest 0 source 4
218
219
220 -- exchange and add
221
222 class Xadd a b where
223   xadd :: a -> b -> CodeGen e s ()
224
225 instance Xadd Reg8 Reg8 where
226   xadd (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xadd_reg_reg dest source 1
227
228 instance Xadd Reg32 Reg32 where
229   xadd (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xadd_reg_reg dest source 4
230
231 instance Xadd Addr Reg8 where
232   xadd (Addr dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xadd_mem_reg dest source 1
233
234 instance Xadd Addr Reg32 where
235   xadd (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xadd_mem_reg dest source 4
236
237 instance Xadd (Disp, Reg32) Reg8 where
238   xadd (Disp disp, Reg32 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xadd_membase_reg dest disp source 1
239
240 instance Xadd Ind Reg8 where
241   xadd (Ind (Reg32 dest)) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_xadd_membase_reg dest 0 source 1
242
243 instance Xadd (Disp, Reg32) Reg32 where
244   xadd (Disp disp, Reg32 dest) (Reg32 source) =  ensureBufferSize x86_max_instruction_bytes >> x86_xadd_membase_reg dest disp source 4
245
246 instance Xadd Ind Reg32 where
247   xadd (Ind (Reg32 dest)) (Reg32 source) =  ensureBufferSize x86_max_instruction_bytes >> x86_xadd_membase_reg dest 0 source 4
248
249
250 -- Increment by 1
251
252 class Inc a where
253   inc :: a -> CodeGen e s ()
254
255 instance Inc Addr where
256   inc (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_inc_mem dest
257
258 instance Inc (Disp, Reg32) where
259   inc (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_inc_membase dest disp
260
261 instance Inc Ind where
262   inc (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_inc_membase dest 0
263
264 instance Inc Reg32 where
265   inc (Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_inc_reg dest
266
267
268 -- Decrement by 1
269
270 class Dec a where
271   dec :: a -> CodeGen e s ()
272
273 instance Dec Addr where
274   dec (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_dec_mem dest
275
276 instance Dec (Disp, Reg32) where
277   dec (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_dec_membase dest disp
278
279 instance Dec Ind where
280   dec (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_dec_membase dest 0
281
282 instance Dec Reg32 where
283   dec (Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_dec_reg dest
284
285
286 -- One's complement negation
287
288 class Not a where
289   not :: a -> CodeGen e s ()
290
291 instance Not Addr where
292   not (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_not_mem dest
293
294 instance Not (Disp, Reg32) where
295   not (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_not_membase dest disp
296
297 instance Not Ind where
298   not (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_not_membase dest 0
299
300 instance Not Reg32 where
301   not (Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_not_reg dest
302
303
304 -- Two's complement negation
305
306 class Neg a where
307   neg :: a -> CodeGen e s ()
308
309 instance Neg Addr where
310   neg (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_neg_mem dest
311
312 instance Neg (Disp, Reg32) where
313   neg (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_neg_membase dest disp
314
315 instance Neg Ind where
316   neg (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_neg_membase dest 0
317
318 instance Neg Reg32 where
319   neg (Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_neg_reg dest
320
321
322 -- No operation
323
324 nop = ensureBufferSize x86_max_instruction_bytes >> x86_nop
325
326
327 -- ALU operations
328
329 -- Calling "x86_alu_reg8_reg8 _ _ _ *False* *False*" is a little bit hackish: the last two
330 -- arguments are set to True for the "high byte registers" ah, bh, ch and dh.
331 -- x86_reg8_emit then sets the 3rd bit in the register number. This bit is set in our
332 -- encoding anyway to the right value, so we simply skip this part.
333
334 class Add a b where
335   add :: a -> b -> CodeGen e s ()
336
337 instance Add Reg32 Word32 where
338   add (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_add dest (fromIntegral imm)
339
340 instance Add Addr Word32 where
341   add (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_add dest (fromIntegral imm)
342
343 instance Add (Disp, Reg32) Word32 where
344   add (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_add dest disp (fromIntegral imm)
345
346 instance Add Ind Word32 where
347   add (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_add dest 0 (fromIntegral imm)
348
349 instance Add (Disp, Reg32) Word8 where
350   add (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_add dest disp (fromIntegral imm)
351
352 instance Add Ind Word8 where
353   add (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_add dest 0 (fromIntegral imm)
354
355 instance Add Addr Reg32 where
356   add (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_add dest source
357
358 instance Add (Disp, Reg32) Reg32 where
359   add (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_add dest disp source
360
361 instance Add Ind Reg32 where
362   add (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_add dest 0 source
363
364 instance Add Reg32 Reg32 where
365   add (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_add dest source
366
367 instance Add Reg8 Reg8 where
368   add (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_add dest source False False
369
370 instance Add Reg32 Addr where
371   add (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_add dest source
372
373 instance Add Reg32 (Disp, Reg32) where
374   add (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_add dest source disp
375
376 instance Add Reg32 Ind where
377   add (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_add dest source 0
378
379
380 class Or a b where
381   or :: a -> b -> CodeGen e s ()
382
383 instance Or Reg32 Word32 where
384   or (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_or dest (fromIntegral imm)
385
386 instance Or Addr Word32 where
387   or (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_or dest (fromIntegral imm)
388
389 instance Or (Disp, Reg32) Word32 where
390   or (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_or dest disp (fromIntegral imm)
391
392 instance Or Ind Word32 where
393   or (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_or dest 0 (fromIntegral imm)
394
395 instance Or (Disp, Reg32) Word8 where
396   or (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_or dest disp (fromIntegral imm)
397
398 instance Or Ind Word8 where
399   or (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_or dest 0 (fromIntegral imm)
400
401 instance Or Addr Reg32 where
402   or (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_or dest source
403
404 instance Or (Disp, Reg32) Reg32 where
405   or (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_or dest disp source
406
407 instance Or Ind Reg32 where
408   or (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_or dest 0 source
409
410 instance Or Reg32 Reg32 where
411   or (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_or dest source
412
413 instance Or Reg8 Reg8 where
414   or (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_or dest source False False
415
416 instance Or Reg32 Addr where
417   or (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_or dest source
418
419 instance Or Reg32 (Disp, Reg32) where
420   or (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_or dest source disp
421
422 instance Or Reg32 Ind where
423   or (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_or dest source 0
424
425
426 class Adc a b where
427   adc :: a -> b -> CodeGen e s ()
428
429 instance Adc Reg32 Word32 where
430   adc (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_adc dest (fromIntegral imm)
431
432 instance Adc Addr Word32 where
433   adc (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_adc dest (fromIntegral imm)
434
435 instance Adc (Disp, Reg32) Word32 where
436   adc (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_adc dest disp (fromIntegral imm)
437
438 instance Adc Ind Word32 where
439   adc (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_adc dest 0 (fromIntegral imm)
440
441 instance Adc (Disp, Reg32) Word8 where
442   adc (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_adc dest disp (fromIntegral imm)
443
444 instance Adc Ind Word8 where
445   adc (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_adc dest 0 (fromIntegral imm)
446
447 instance Adc Addr Reg32 where
448   adc (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_adc dest source
449
450 instance Adc (Disp, Reg32) Reg32 where
451   adc (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_adc dest disp source
452
453 instance Adc Ind Reg32 where
454   adc (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_adc dest 0 source
455
456 instance Adc Reg32 Reg32 where
457   adc (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_adc dest source
458
459 instance Adc Reg8 Reg8 where
460   adc (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_adc dest source False False
461
462 instance Adc Reg32 Addr where
463   adc (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_adc dest source
464
465 instance Adc Reg32 (Disp, Reg32) where
466   adc (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_adc dest source disp
467
468 instance Adc Reg32 Ind where
469   adc (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_adc dest source 0
470
471
472 class Sbb a b where
473   sbb :: a -> b -> CodeGen e s ()
474
475 instance Sbb Reg32 Word32 where
476   sbb (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_sbb dest (fromIntegral imm)
477
478 instance Sbb Addr Word32 where
479   sbb (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_sbb dest (fromIntegral imm)
480
481 instance Sbb (Disp, Reg32) Word32 where
482   sbb (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_sbb dest disp (fromIntegral imm)
483
484 instance Sbb Ind Word32 where
485   sbb (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_sbb dest 0 (fromIntegral imm)
486
487 instance Sbb (Disp, Reg32) Word8 where
488   sbb (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_sbb dest disp (fromIntegral imm)
489
490 instance Sbb Ind Word8 where
491   sbb (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_sbb dest 0 (fromIntegral imm)
492
493 instance Sbb Addr Reg32 where
494   sbb (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_sbb dest source
495
496 instance Sbb (Disp, Reg32) Reg32 where
497   sbb (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_sbb dest disp source
498
499 instance Sbb Ind Reg32 where
500   sbb (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_sbb dest 0 source
501
502 instance Sbb Reg32 Reg32 where
503   sbb (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_sbb dest source
504
505 instance Sbb Reg8 Reg8 where
506   sbb (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_sbb dest source False False
507
508 instance Sbb Reg32 Addr where
509   sbb (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_sbb dest source
510
511 instance Sbb Reg32 (Disp, Reg32) where
512   sbb (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_sbb dest source disp
513
514 instance Sbb Reg32 Ind where
515   sbb (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_sbb dest source 0
516
517
518 class And a b where
519   and :: a -> b -> CodeGen e s ()
520
521 instance And Reg32 Word32 where
522   and (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_and dest (fromIntegral imm)
523
524 instance And Addr Word32 where
525   and (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_and dest (fromIntegral imm)
526
527 instance And (Disp, Reg32) Word32 where
528   and (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_and dest disp (fromIntegral imm)
529
530 instance And Ind Word32 where
531   and (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_and dest 0 (fromIntegral imm)
532
533 instance And (Disp, Reg32) Word8 where
534   and (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_and dest disp (fromIntegral imm)
535
536 instance And Ind Word8 where
537   and (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_and dest 0 (fromIntegral imm)
538
539 instance And Addr Reg32 where
540   and (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_and dest source
541
542 instance And (Disp, Reg32) Reg32 where
543   and (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_and dest disp source
544
545 instance And Ind Reg32 where
546   and (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_and dest 0 source
547
548 instance And Reg32 Reg32 where
549   and (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_and dest source
550
551 instance And Reg8 Reg8 where
552   and (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_and dest source False False
553
554 instance And Reg32 Addr where
555   and (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_and dest source
556
557 instance And Reg32 (Disp, Reg32) where
558   and (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_and dest source disp
559
560 instance And Reg32 Ind where
561   and (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_and dest source 0
562
563
564 class Sub a b where
565   sub :: a -> b -> CodeGen e s ()
566
567 instance Sub Reg32 Word32 where
568   sub (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_sub dest (fromIntegral imm)
569
570 instance Sub Addr Word32 where
571   sub (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_sub dest (fromIntegral imm)
572
573 instance Sub (Disp, Reg32) Word32 where
574   sub (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_sub dest disp (fromIntegral imm)
575
576 instance Sub Ind Word32 where
577   sub (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_sub dest 0 (fromIntegral imm)
578
579 instance Sub (Disp, Reg32) Word8 where
580   sub (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_sub dest disp (fromIntegral imm)
581
582 instance Sub Ind Word8 where
583   sub (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_sub dest 0 (fromIntegral imm)
584
585 instance Sub Addr Reg32 where
586   sub (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_sub dest source
587
588 instance Sub (Disp, Reg32) Reg32 where
589   sub (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_sub dest disp source
590
591 instance Sub Ind Reg32 where
592   sub (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_sub dest 0 source
593
594 instance Sub Reg32 Reg32 where
595   sub (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_sub dest source
596
597 instance Sub Reg8 Reg8 where
598   sub (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_sub dest source False False
599
600 instance Sub Reg32 Addr where
601   sub (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_sub dest source
602
603 instance Sub Reg32 (Disp, Reg32) where
604   sub (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_sub dest source disp
605
606 instance Sub Reg32 Ind where
607   sub (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_sub dest source 0
608
609
610 class Xor a b where
611   xor :: a -> b -> CodeGen e s ()
612
613 instance Xor Reg32 Word32 where
614   xor (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_xor dest (fromIntegral imm)
615
616 instance Xor Addr Word32 where
617   xor (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_xor dest (fromIntegral imm)
618
619 instance Xor (Disp, Reg32) Word32 where
620   xor (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_xor dest disp (fromIntegral imm)
621
622 instance Xor Ind Word32 where
623   xor (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_xor dest 0 (fromIntegral imm)
624
625 instance Xor (Disp, Reg32) Word8 where
626   xor (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_xor dest disp (fromIntegral imm)
627
628 instance Xor Ind Word8 where
629   xor (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_xor dest 0 (fromIntegral imm)
630
631 instance Xor Addr Reg32 where
632   xor (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_xor dest source
633
634 instance Xor (Disp, Reg32) Reg32 where
635   xor (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_xor dest disp source
636
637 instance Xor Ind Reg32 where
638   xor (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_xor dest 0 source
639
640 instance Xor Reg32 Reg32 where
641   xor (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_xor dest source
642
643 instance Xor Reg8 Reg8 where
644   xor (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_xor dest source False False
645
646 instance Xor Reg32 Addr where
647   xor (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_xor dest source
648
649 instance Xor Reg32 (Disp, Reg32) where
650   xor (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_xor dest source disp
651
652 instance Xor Reg32 Ind where
653   xor (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_xor dest source 0
654
655
656 class Cmp a b where
657   cmp :: a -> b -> CodeGen e s ()
658
659 instance Cmp Reg32 Word32 where
660   cmp (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_cmp dest (fromIntegral imm)
661
662 instance Cmp Reg32 (Ptr a) where
663   cmp (Reg32 dest) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_imm x86_cmp dest (ptrToInt ptr)
664
665 instance Cmp Reg32 Label where
666   cmp (Reg32 dest) lab = do
667       ensureBufferSize x86_max_instruction_bytes
668       x86_alu_reg_imm x86_cmp dest 0xf0f0f0f0
669       emitFixup lab (-4) Fixup32Absolute
670
671 instance Cmp Addr Word32 where
672   cmp (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_cmp dest (fromIntegral imm)
673
674 instance Cmp Addr (Ptr a) where
675   cmp (Addr dest) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_cmp dest (ptrToWord32 ptr)
676
677 instance Cmp Addr Label where
678   cmp (Addr dest) lab = do
679       ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_imm x86_cmp dest 0xf0f0f0f0
680       emitFixup lab (-4) Fixup32Absolute
681
682 instance Cmp (Disp, Reg32) Word32 where
683   cmp (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_cmp dest disp (fromIntegral imm)
684
685 instance Cmp (Disp, Reg32) (Ptr a) where
686   cmp (Disp disp, Reg32 dest) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_cmp dest disp (ptrToWord32 ptr)
687
688 instance Cmp (Disp, Reg32) Label where
689   cmp (Disp disp, Reg32 dest) lab = do
690                                    ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_cmp dest disp 0xf0f0f0f0
691                                    emitFixup lab (-4) Fixup32Absolute
692
693 instance Cmp Ind Word32 where
694   cmp (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_cmp dest 0 (fromIntegral imm)
695
696 instance Cmp Ind (Ptr a) where
697   cmp (Ind (Reg32 dest)) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_cmp dest 0 (ptrToWord32 ptr)
698
699 instance Cmp Ind Label where
700   cmp (Ind (Reg32 dest)) lab = do
701                          ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_imm x86_cmp dest 0 0xf0f0f0f0
702                          emitFixup lab (-4) Fixup32Absolute
703
704 instance Cmp (Disp, Reg32) Word8 where
705   cmp (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_cmp dest disp imm
706
707 instance Cmp Ind Word8 where
708   cmp (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase8_imm x86_cmp dest 0 imm
709
710 instance Cmp Addr Reg32 where
711   cmp (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_mem_reg x86_cmp dest source
712
713 instance Cmp (Disp, Reg32) Reg32 where
714   cmp (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_cmp dest disp source
715
716 instance Cmp Ind Reg32 where
717   cmp (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_membase_reg x86_cmp dest 0 source
718
719 instance Cmp Reg32 Reg32 where
720   cmp (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_reg x86_cmp dest source
721
722 instance Cmp Reg8 Reg8 where
723   cmp (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg8_reg8 x86_cmp dest source False False
724
725 instance Cmp Reg32 Addr where
726   cmp (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_mem x86_cmp dest source
727
728 instance Cmp Reg32 (Disp, Reg32) where
729   cmp (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_cmp dest source disp
730
731 instance Cmp Reg32 Ind where
732   cmp (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_alu_reg_membase x86_cmp dest source 0
733
734
735 -- logical compare
736
737 class Test a b where
738   test :: a -> b -> CodeGen e s ()
739
740 instance Test Reg32 Word32 where
741   test (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_test_reg_imm dest imm 
742
743 instance Test Addr Word32 where
744   test (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_test_mem_imm dest imm 
745
746 instance Test (Disp, Reg32) Word32 where
747   test (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_test_membase_imm dest disp imm 
748
749 instance Test Ind Word32 where
750   test (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_test_membase_imm dest 0 imm 
751
752 instance Test Reg32 Reg32 where
753   test (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_test_reg_reg dest source 
754
755 instance Test Addr Reg32 where
756   test (Addr dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_test_mem_reg dest source 
757
758 instance Test (Disp, Reg32) Reg32 where
759   test (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_test_membase_reg dest disp source 
760
761 instance Test Ind Reg32 where
762   test (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_test_membase_reg dest 0 source 
763
764
765 -- shift and rotate
766
767 class Rol a b where
768   rol :: a -> b -> CodeGen e s ()
769
770 instance Rol Reg32 Word8 where
771   rol (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_rol dest imm 
772
773 instance Rol Addr Word8 where
774   rol (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_rol dest imm 
775
776 instance Rol (Disp, Reg32) Word8 where
777   rol (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_rol dest disp imm 
778
779 instance Rol Ind Word8 where
780   rol (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_rol dest 0 imm 
781
782 instance Rol Reg32 Reg8 where
783   rol (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_rol dest
784   rol _ _ = onlyCl
785
786 instance Rol Addr Reg8 where
787   rol (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_rol dest
788   rol _ _ = onlyCl
789
790 instance Rol (Disp, Reg32) Reg8 where
791   rol (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_rol dest disp
792
793 instance Rol Ind Reg8 where
794   rol (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_rol dest 0
795   rol _ _ = onlyCl
796
797 class Ror a b where
798   ror :: a -> b -> CodeGen e s ()
799
800 instance Ror Reg32 Word8 where
801   ror (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_ror dest imm 
802
803 instance Ror Addr Word8 where
804   ror (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_ror dest imm 
805
806 instance Ror (Disp, Reg32) Word8 where
807   ror (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_ror dest disp imm 
808
809 instance Ror Ind Word8 where
810   ror (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_ror dest 0 imm 
811
812 instance Ror Reg32 Reg8 where
813   ror (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_ror dest
814   ror _ _ = onlyCl
815
816 instance Ror Addr Reg8 where
817   ror (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_ror dest
818   ror _ _ = onlyCl
819
820 instance Ror (Disp, Reg32) Reg8 where
821   ror (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_ror dest disp
822
823 instance Ror Ind Reg8 where
824   ror (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_ror dest 0
825   ror _ _ = onlyCl
826
827 class Rcl a b where
828   rcl :: a -> b -> CodeGen e s ()
829
830 instance Rcl Reg32 Word8 where
831   rcl (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_rcl dest imm 
832
833 instance Rcl Addr Word8 where
834   rcl (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_rcl dest imm 
835
836 instance Rcl (Disp, Reg32) Word8 where
837   rcl (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_rcl dest disp imm 
838
839 instance Rcl Ind Word8 where
840   rcl (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_rcl dest 0 imm 
841
842 instance Rcl Reg32 Reg8 where
843   rcl (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_rcl dest
844   rcl _ _ = onlyCl
845
846 instance Rcl Addr Reg8 where
847   rcl (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_rcl dest
848   rcl _ _ = onlyCl
849
850 instance Rcl (Disp, Reg32) Reg8 where
851   rcl (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_rcl dest disp
852
853 instance Rcl Ind Reg8 where
854   rcl (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_rcl dest 0
855   rcl _ _ = onlyCl
856
857 class Rcr a b where
858   rcr :: a -> b -> CodeGen e s ()
859
860 instance Rcr Reg32 Word8 where
861   rcr (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_rcr dest imm 
862
863 instance Rcr Addr Word8 where
864   rcr (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_rcr dest imm 
865
866 instance Rcr (Disp, Reg32) Word8 where
867   rcr (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_rcr dest disp imm 
868
869 instance Rcr Ind Word8 where
870   rcr (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_rcr dest 0 imm 
871
872 instance Rcr Reg32 Reg8 where
873   rcr (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_rcr dest
874   rcr _ _ = onlyCl
875
876 instance Rcr Addr Reg8 where
877   rcr (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_rcr dest
878   rcr _ _ = onlyCl
879
880 instance Rcr (Disp, Reg32) Reg8 where
881   rcr (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_rcr dest disp
882
883 instance Rcr Ind Reg8 where
884   rcr (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_rcr dest 0
885   rcr _ _ = onlyCl
886
887 class Shl a b where
888   shl :: a -> b -> CodeGen e s ()
889
890 instance Shl Reg32 Word8 where
891   shl (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_shl dest imm 
892
893 instance Shl Addr Word8 where
894   shl (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_shl dest imm 
895
896 instance Shl (Disp, Reg32) Word8 where
897   shl (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_shl dest disp imm 
898
899 instance Shl Ind Word8 where
900   shl (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_shl dest 0 imm 
901
902 instance Shl Reg32 Reg8 where
903   shl (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_shl dest
904   shl _ _ = onlyCl
905
906 instance Shl Addr Reg8 where
907   shl (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_shl dest
908   shl _ _ = onlyCl
909
910 instance Shl (Disp, Reg32) Reg8 where
911   shl (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_shl dest disp
912
913 instance Shl Ind Reg8 where
914   shl (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_shl dest 0
915   shl _ _ = onlyCl
916
917 class Shr a b where
918   shr :: a -> b -> CodeGen e s ()
919
920 instance Shr Reg32 Word8 where
921   shr (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_shr dest imm 
922
923 instance Shr Addr Word8 where
924   shr (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_shr dest imm 
925
926 instance Shr (Disp, Reg32) Word8 where
927   shr (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_shr dest disp imm 
928
929 instance Shr Ind Word8 where
930   shr (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_shr dest 0 imm 
931
932 instance Shr Reg32 Reg8 where
933   shr (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_shr dest
934   shr _ _ = onlyCl
935
936 instance Shr Addr Reg8 where
937   shr (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_shr dest
938   shr _ _ = onlyCl
939
940 instance Shr (Disp, Reg32) Reg8 where
941   shr (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_shr dest disp
942
943 instance Shr Ind Reg8 where
944   shr (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_shr dest 0
945   shr _ _ = onlyCl
946
947 class Sar a b where
948   sar :: a -> b -> CodeGen e s ()
949
950 instance Sar Reg32 Word8 where
951   sar (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_sar dest imm 
952
953 instance Sar Addr Word8 where
954   sar (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_sar dest imm 
955
956 instance Sar (Disp, Reg32) Word8 where
957   sar (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_sar dest disp imm 
958
959 instance Sar Ind Word8 where
960   sar (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_sar dest 0 imm 
961
962 instance Sar Reg32 Reg8 where
963   sar (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_sar dest
964   sar _ _ = onlyCl
965
966 instance Sar Addr Reg8 where
967   sar (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_sar dest
968   sar _ _ = onlyCl
969
970 instance Sar (Disp, Reg32) Reg8 where
971   sar (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_sar dest disp
972
973 instance Sar Ind Reg8 where
974   sar (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_sar dest 0
975   sar _ _ = onlyCl
976
977 class Sal a b where
978   sal :: a -> b -> CodeGen e s ()
979
980 instance Sal Reg32 Word8 where
981   sal (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg_imm x86_shl dest imm 
982
983 instance Sal Addr Word8 where
984   sal (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem_imm x86_shl dest imm 
985
986 instance Sal (Disp, Reg32) Word8 where
987   sal (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_shl dest disp imm 
988
989 instance Sal Ind Word8 where
990   sal (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase_imm x86_shl dest 0 imm 
991
992 instance Sal Reg32 Reg8 where
993   sal (Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_reg x86_shl dest
994   sal _ _ = onlyCl
995
996 instance Sal Addr Reg8 where
997   sal (Addr dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_mem x86_shl dest
998   sal _ _ = onlyCl
999
1000 instance Sal (Disp, Reg32) Reg8 where
1001   sal (Disp disp, Reg32 dest) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_shl dest disp
1002
1003 instance Sal Ind Reg8 where
1004   sal (Ind (Reg32 dest)) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shift_membase x86_shl dest 0
1005   sal _ _ = onlyCl
1006
1007
1008 -- double precision shift right
1009
1010 class Shrd a b c where
1011   shrd :: a -> b -> c -> CodeGen e s ()
1012
1013 instance Shrd Reg32 Reg32 Reg8 where
1014   shrd (Reg32 dest) (Reg32 source) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shrd_reg dest source
1015   shrd _ _ _ = onlyCl
1016
1017 instance Shrd Reg32 Reg32 Word8 where
1018   shrd (Reg32 dest) (Reg32 source) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shrd_reg_imm dest source imm 
1019
1020
1021 -- double precision shift left
1022
1023 class Shld a b c where
1024   shld :: a -> b -> c -> CodeGen e s ()
1025
1026 instance Shld Reg32 Reg32 Reg8 where
1027   shld (Reg32 dest) (Reg32 source) (Reg8 1) = ensureBufferSize x86_max_instruction_bytes >> x86_shld_reg dest source
1028   shld _ _ _ = onlyCl
1029
1030 instance Shld Reg32 Reg32 Word8 where
1031   shld (Reg32 dest) (Reg32 source) imm = ensureBufferSize x86_max_instruction_bytes >> x86_shld_reg_imm dest source imm 
1032
1033
1034 -- unsigned multiply
1035
1036 class Mul a where
1037   mul :: a -> CodeGen e s ()
1038
1039 instance Mul Reg32 where
1040   mul (Reg32 arg) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_reg arg False
1041
1042 instance Mul Addr where
1043   mul (Addr arg) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_mem arg False
1044
1045 instance Mul (Disp, Reg32) where
1046   mul (Disp disp, Reg32 arg) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_membase arg disp False
1047
1048 instance Mul Ind where
1049   mul (Ind (Reg32 arg)) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_membase arg 0 False
1050
1051
1052 -- signed multiply
1053
1054 data InPlace = InPlace
1055
1056 -- if a == InPlace then
1057 --   b = b * c
1058 -- else
1059 --   a = b * c
1060
1061 class Imul a b c where
1062   imul :: a -> b -> c -> CodeGen e s ()
1063
1064 instance Imul InPlace Reg32 Reg32 where
1065   imul _ (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_reg dest source
1066
1067 instance Imul InPlace Reg32 Addr where
1068   imul _ (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_mem dest source
1069
1070 instance Imul InPlace Reg32 (Disp, Reg32) where
1071   imul _ (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_membase dest source disp
1072
1073 instance Imul InPlace Reg32 Ind where
1074   imul _ (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_membase dest source 0
1075
1076 instance Imul Reg32 Reg32 Word32 where
1077   imul (Reg32 dest) (Reg32 source) imm = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_reg_imm dest source imm 
1078
1079 instance Imul Reg32 Addr Word32 where
1080   imul (Reg32 dest) (Addr source) imm = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_mem_imm dest source imm 
1081
1082 instance Imul Reg32 (Disp, Reg32) Word32 where
1083   imul (Reg32 dest) (Disp disp, Reg32 source) imm = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_membase_imm dest source disp imm 
1084
1085 instance Imul Reg32 Ind Word32 where
1086   imul (Reg32 dest) (Ind (Reg32 source)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_imul_reg_membase_imm dest source 0 imm 
1087
1088
1089 -- divide EDX:EAX by rm;
1090 -- eax = quotient, edx = remainder
1091
1092 -- unsigned divide
1093
1094 class Div a where
1095   div :: a -> CodeGen e s ()
1096
1097 instance Div Reg32 where
1098   div (Reg32 arg) = ensureBufferSize x86_max_instruction_bytes >> x86_div_reg arg False
1099
1100 instance Div Addr where
1101   div (Addr arg) = ensureBufferSize x86_max_instruction_bytes >> x86_div_mem arg False
1102
1103 instance Div (Disp, Reg32) where
1104   div (Disp disp, Reg32 arg) = ensureBufferSize x86_max_instruction_bytes >> x86_div_membase arg disp False
1105
1106 instance Div Ind where
1107   div (Ind (Reg32 arg)) = ensureBufferSize x86_max_instruction_bytes >> x86_div_membase arg 0 False
1108
1109
1110 -- signed divide
1111
1112 class Idiv a where
1113   idiv :: a -> CodeGen e s ()
1114
1115 instance Idiv Reg32 where
1116   idiv (Reg32 arg) = ensureBufferSize x86_max_instruction_bytes >> x86_div_reg arg True
1117
1118 instance Idiv Addr where
1119   idiv (Addr arg) = ensureBufferSize x86_max_instruction_bytes >> x86_div_mem arg True
1120
1121 instance Idiv (Disp, Reg32) where
1122   idiv (Disp disp, Reg32 arg) = ensureBufferSize x86_max_instruction_bytes >> x86_div_membase arg disp True
1123
1124 instance Idiv Ind where
1125   idiv (Ind (Reg32 arg)) = ensureBufferSize x86_max_instruction_bytes >> x86_div_membase arg 0 True
1126
1127
1128 -- "mov" instruction for different sources and destinations
1129
1130 class Mov a b where
1131   mov :: a -> b -> CodeGen e s ()
1132
1133
1134 instance Mov Reg8 Reg8 where
1135   mov (Reg8 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_reg dest source 1
1136
1137 instance Mov Reg16 Reg16 where
1138   mov (Reg16 dest) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_reg dest source 2
1139
1140 instance Mov Reg32 Reg32 where
1141   mov (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_reg dest source 4
1142
1143
1144 instance Mov Reg32 Word32 where
1145   mov (Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_imm dest (fromIntegral imm)
1146
1147 instance Mov Reg32 (Ptr a) where
1148   mov (Reg32 dest) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_imm dest (ptrToWord32 ptr)
1149
1150 instance Mov Reg32 Label where
1151   mov (Reg32 dest) lab = do ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_imm dest 0
1152                             emitFixup lab (-4) Fixup32Absolute
1153
1154 instance Mov Addr Word8 where
1155   mov (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_imm dest (fromIntegral imm) 1
1156
1157 instance Mov Addr Word16 where
1158   mov (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_imm dest (fromIntegral imm) 2
1159
1160 instance Mov Addr Word32 where
1161   mov (Addr dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_imm dest imm 4
1162
1163 instance Mov Addr (Ptr a) where
1164   mov (Addr dest) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_imm dest (ptrToWord32 ptr) 4
1165
1166 instance Mov Addr Label where
1167   mov (Addr dest) lab = do ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_imm dest 0 4
1168                            emitFixup lab (-4) Fixup32Absolute
1169
1170 instance Mov (Disp, Reg32) Word8 where
1171   mov (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest disp (fromIntegral imm) 1
1172
1173 instance Mov Ind Word8 where
1174   mov (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest 0 (fromIntegral imm) 1
1175
1176 instance Mov (Disp, Reg32) Word16 where
1177   mov (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest disp (fromIntegral imm) 2
1178
1179 instance Mov Ind Word16 where
1180   mov (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest 0 (fromIntegral imm) 2
1181
1182 instance Mov (Disp, Reg32) Word32 where
1183   mov (Disp disp, Reg32 dest) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest disp imm 4
1184
1185 instance Mov (Disp, Reg32) (Ptr a) where
1186   mov (Disp disp, Reg32 dest) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest disp (ptrToWord32 ptr) 4
1187
1188 instance Mov (Disp, Reg32) Label where
1189   mov (Disp disp, Reg32 dest) lab = do ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest disp 0 4
1190                                        emitFixup lab (-4) Fixup32Absolute
1191
1192 instance Mov Ind Word32 where
1193   mov (Ind (Reg32 dest)) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest 0 imm 4
1194
1195 instance Mov Ind (Ptr a) where
1196   mov (Ind (Reg32 dest)) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest 0 (ptrToWord32 ptr) 4
1197
1198 instance Mov Ind Label where
1199   mov (Ind (Reg32 dest)) lab = do ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_imm dest 0 0 4
1200                                   emitFixup lab (-4) Fixup32Absolute
1201
1202 instance Mov (Reg32, Reg32, Scale) Word8 where
1203   mov (Reg32 base, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm base 0 index (scaleToShift scale) (fromIntegral imm) 1
1204
1205 instance Mov (Reg32, Reg32, Scale) Word16 where
1206   mov (Reg32 base, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm base 0 index (scaleToShift scale) (fromIntegral imm) 2
1207
1208 instance Mov (Reg32, Reg32, Scale) Word32 where
1209   mov (Reg32 base, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm base 0 index (scaleToShift scale) imm 4
1210
1211 instance Mov (Reg32, Reg32, Scale) (Ptr a) where
1212   mov (Reg32 base, Reg32 index, scale) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm base 0 index (scaleToShift scale) (ptrToWord32 ptr) 4
1213
1214 instance Mov (Reg32, Reg32, Scale) Label where
1215   mov (Reg32 base, Reg32 index, scale) lab = do ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm base 0 index (scaleToShift scale) 0 4
1216                                                 emitFixup lab (-4) Fixup32Absolute
1217
1218 instance Mov (Disp, Reg32, Scale) Word8 where
1219   mov (Disp disp, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm x86_nobasereg disp index (scaleToShift scale) (fromIntegral imm) 1
1220
1221 instance Mov (Disp, Reg32, Scale) Word16 where
1222   mov (Disp disp, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm x86_nobasereg disp index (scaleToShift scale) (fromIntegral imm) 2
1223
1224 instance Mov (Disp, Reg32, Scale) Word32 where
1225   mov (Disp disp, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm x86_nobasereg disp index (scaleToShift scale) imm 4
1226
1227 instance Mov (Disp, Reg32, Scale) (Ptr a) where
1228   mov (Disp disp, Reg32 index, scale) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm x86_nobasereg disp index (scaleToShift scale) (ptrToWord32 ptr) 4
1229
1230 instance Mov (Disp, Reg32, Scale) Label where
1231   mov (Disp disp, Reg32 index, scale) lab = do ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm x86_nobasereg disp index (scaleToShift scale) 0 4
1232                                                emitFixup lab (-4) Fixup32Absolute
1233
1234 instance Mov (Disp, Reg32, Reg32, Scale) Word8 where
1235   mov (Disp disp, Reg32 5, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm 5 disp index (scaleToShift scale) (fromIntegral imm) 1
1236   mov _ _ = onlyEbp
1237
1238 instance Mov (Disp, Reg32, Reg32, Scale) Word16 where
1239   mov (Disp disp, Reg32 5, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm 5 disp index (scaleToShift scale) (fromIntegral imm) 2
1240   mov _ _ = onlyEbp
1241
1242 instance Mov (Disp, Reg32, Reg32, Scale) Word32 where
1243   mov (Disp disp, Reg32 5, Reg32 index, scale) imm = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm 5 disp index (scaleToShift scale) imm 4
1244   mov _ _ = onlyEbp
1245
1246 instance Mov (Disp, Reg32, Reg32, Scale) (Ptr a) where
1247   mov (Disp disp, Reg32 5, Reg32 index, scale) ptr = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm 5 disp index (scaleToShift scale) (ptrToWord32 ptr) 4
1248   mov _ _ = onlyEbp
1249
1250 instance Mov (Disp, Reg32, Reg32, Scale) Label where
1251   mov (Disp disp, Reg32 5, Reg32 index, scale) lab = do ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_imm 5 disp index (scaleToShift scale) 0 4
1252                                                         emitFixup lab (-4) Fixup32Absolute
1253   mov _ _ = onlyEbp
1254
1255 instance Mov Addr Reg8 where
1256   mov (Addr a) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_reg a source 1
1257
1258 instance Mov Addr Reg16 where
1259   mov (Addr a) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_reg a source 2
1260
1261 instance Mov Addr Reg32 where
1262   mov (Addr a) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_mem_reg a source 4
1263
1264 instance Mov Reg8 Addr where
1265   mov (Reg8 dest) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_mem dest a 1
1266
1267 instance Mov Reg16 Addr where
1268   mov (Reg16 dest) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_mem dest a 2
1269
1270 instance Mov Reg32 Addr where
1271   mov (Reg32 dest) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_mem dest a 4
1272
1273
1274 instance Mov Ind Reg8 where
1275   mov (Ind (Reg32 dest)) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_regp_reg dest source 1
1276
1277 instance Mov Ind Reg16 where
1278   mov (Ind (Reg32 dest)) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_regp_reg dest source 2
1279
1280 instance Mov Ind Reg32 where
1281   mov (Ind (Reg32 dest)) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_regp_reg dest source 4
1282
1283 instance Mov Reg8 Ind where
1284   mov (Reg8 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_regp dest source 1
1285
1286 instance Mov Reg16 Ind where
1287   mov (Reg16 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_regp dest source 2
1288
1289 instance Mov Reg32 Ind where
1290   mov (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_regp dest source 4
1291
1292
1293 instance Mov (Disp, Reg32) Reg8 where
1294   mov (Disp disp, Reg32 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_reg dest disp source 1
1295
1296 instance Mov (Disp, Reg32) Reg16 where
1297   mov (Disp disp, Reg32 dest) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_reg dest disp source 2
1298
1299 instance Mov (Disp, Reg32) Reg32 where
1300   mov (Disp disp, Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_membase_reg dest disp source 4
1301
1302 instance Mov Reg8 (Disp, Reg32) where
1303   mov (Reg8 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_membase dest source disp 1
1304
1305 instance Mov Reg16 (Disp, Reg32) where
1306   mov (Reg16 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_membase dest source disp 2
1307
1308 instance Mov Reg32 (Disp, Reg32) where
1309   mov (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_membase dest source disp 4
1310
1311
1312 instance Mov (Reg32, Reg32, Scale) Reg8 where
1313   mov (Reg32 base, Reg32 index, s) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg base 0 index (scaleToShift s) source 1
1314
1315 instance Mov (Reg32, Reg32, Scale) Reg16 where
1316   mov (Reg32 base, Reg32 index, s) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg base 0 index (scaleToShift s) source 2
1317
1318 instance Mov (Reg32, Reg32, Scale) Reg32 where
1319   mov (Reg32 base, Reg32 index, s) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg base 0 index (scaleToShift s) source 4
1320
1321 instance Mov Reg8 (Reg32, Reg32, Scale) where
1322   mov (Reg8 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest base 0 index (scaleToShift s) 1
1323
1324 instance Mov Reg16 (Reg32, Reg32, Scale) where
1325   mov (Reg16 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest base 0 index (scaleToShift s) 2
1326
1327 instance Mov Reg32 (Reg32, Reg32, Scale) where
1328   mov (Reg32 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest base 0 index (scaleToShift s) 4
1329
1330
1331 instance Mov (Disp, Reg32, Scale) Reg8 where
1332   mov (Disp disp, Reg32 index, s) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg x86_nobasereg disp index (scaleToShift s) source 1
1333
1334 instance Mov (Disp, Reg32, Scale) Reg16 where
1335   mov (Disp disp, Reg32 index, s) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg x86_nobasereg disp index (scaleToShift s) source 2
1336
1337 instance Mov (Disp, Reg32, Scale) Reg32 where
1338   mov (Disp disp, Reg32 index, s) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg x86_nobasereg disp index (scaleToShift s) source 4
1339
1340 instance Mov Reg8 (Disp, Reg32, Scale) where
1341   mov (Reg8 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest x86_nobasereg disp index (scaleToShift s) 1
1342
1343 instance Mov Reg16 (Disp, Reg32, Scale) where
1344   mov (Reg16 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest x86_nobasereg disp index (scaleToShift s) 2
1345
1346 instance Mov Reg32 (Disp, Reg32, Scale) where
1347   mov (Reg32 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest x86_nobasereg disp index (scaleToShift s) 4
1348
1349
1350 instance Mov (Disp, Reg32, Reg32, Scale) Reg8 where
1351   mov (Disp disp, Reg32 5, Reg32 index, s) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg 5 disp index (scaleToShift s) source 1
1352   mov _ _ = onlyEbp
1353
1354 instance Mov (Disp, Reg32, Reg32, Scale) Reg16 where
1355   mov (Disp disp, Reg32 5, Reg32 index, s) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg 5 disp index (scaleToShift s) source 2
1356   mov _ _ = onlyEbp
1357
1358 instance Mov (Disp, Reg32, Reg32, Scale) Reg32 where
1359   mov (Disp disp, Reg32 5, Reg32 index, s) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> ensureBufferSize x86_max_instruction_bytes >> x86_mov_memindex_reg 5 disp index (scaleToShift s) source 4
1360   mov _ _ = onlyEbp
1361
1362 instance Mov Reg8 (Disp, Reg32, Reg32, Scale) where
1363   mov (Reg8 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest 5 disp index (scaleToShift s) 1
1364   mov _ _ = onlyEbp
1365
1366 instance Mov Reg16 (Disp, Reg32, Reg32, Scale) where
1367   mov (Reg16 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest 5 disp index (scaleToShift s) 2
1368   mov _ _ = onlyEbp
1369
1370 instance Mov Reg32 (Disp, Reg32, Reg32, Scale) where
1371   mov (Reg32 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_reg_memindex dest 5 disp index (scaleToShift s) 4
1372   mov _ _ = onlyEbp
1373
1374
1375 -- move with sign-extension
1376
1377 class Movsxb a b where
1378   movsxb :: a -> b -> CodeGen e s ()
1379
1380 instance Movsxb Reg32 Reg8 where
1381   movsxb (Reg32 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_reg dest source True False
1382
1383 instance Movsxb Reg32 Addr where
1384   movsxb (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_mem dest source True False
1385
1386 instance Movsxb Reg32 (Disp, Reg32) where
1387   movsxb (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source disp True False
1388
1389 instance Movsxb Reg32 Ind where
1390   movsxb (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source 0 True False
1391
1392 instance Movsxb Reg32 (Disp, Reg32, Reg32, Scale) where
1393   movsxb (Reg32 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest 5 disp index (scaleToShift s) True False
1394   movsxb _ _ = onlyEbp
1395
1396 instance Movsxb Reg32 (Disp, Reg32, Scale) where
1397   movsxb (Reg32 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest x86_nobasereg disp index (scaleToShift s) True False
1398
1399 instance Movsxb Reg32 (Reg32, Reg32, Scale) where
1400   movsxb (Reg32 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest base 0 index (scaleToShift s) True False
1401
1402 class Movsxw a b where
1403   movsxw :: a -> b -> CodeGen e s ()
1404
1405 instance Movsxw Reg32 Reg16 where
1406   movsxw (Reg32 dest) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_reg dest source True True
1407
1408 instance Movsxw Reg32 Addr where
1409   movsxw (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_mem dest source True True
1410
1411 instance Movsxw Reg32 (Disp, Reg32) where
1412   movsxw (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source disp True True
1413
1414 instance Movsxw Reg32 Ind where
1415   movsxw (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source 0 True True
1416
1417 instance Movsxw Reg32 (Disp, Reg32, Reg32, Scale) where
1418   movsxw (Reg32 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest 5 disp index (scaleToShift s) True True
1419   movsxw _ _ = onlyEbp
1420
1421 instance Movsxw Reg32 (Disp, Reg32, Scale) where
1422   movsxw (Reg32 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest x86_nobasereg disp index (scaleToShift s) True True
1423
1424 instance Movsxw Reg32 (Reg32, Reg32, Scale) where
1425   movsxw (Reg32 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest base 0 index (scaleToShift s) True True
1426
1427
1428 -- move with zero-extension
1429
1430 class Movzxb a b where
1431   movzxb :: a -> b -> CodeGen e s ()
1432
1433 instance Movzxb Reg32 Reg8 where
1434   movzxb (Reg32 dest) (Reg8 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_reg dest source False False
1435
1436 instance Movzxb Reg32 Addr where
1437   movzxb (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_mem dest source False False
1438
1439 instance Movzxb Reg32 (Disp, Reg32) where
1440   movzxb (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source disp False False
1441
1442 instance Movzxb Reg32 Ind where
1443   movzxb (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source 0 False False
1444
1445 instance Movzxb Reg32 (Disp, Reg32, Reg32, Scale) where
1446   movzxb (Reg32 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest 5 disp index (scaleToShift s) False False
1447   movzxb _ _ = onlyEbp
1448
1449 instance Movzxb Reg32 (Disp, Reg32, Scale) where
1450   movzxb (Reg32 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest x86_nobasereg disp index (scaleToShift s) False False
1451
1452 instance Movzxb Reg32 (Reg32, Reg32, Scale) where
1453   movzxb (Reg32 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest base 0 index (scaleToShift s) False False
1454
1455 class Movzxw a b where
1456   movzxw :: a -> b -> CodeGen e s ()
1457
1458 instance Movzxw Reg32 Reg16 where
1459   movzxw (Reg32 dest) (Reg16 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_reg dest source False True
1460
1461 instance Movzxw Reg32 Addr where
1462   movzxw (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_mem dest source False True
1463
1464 instance Movzxw Reg32 (Disp, Reg32) where
1465   movzxw (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source disp False True
1466
1467 instance Movzxw Reg32 Ind where
1468   movzxw (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_membase dest source 0 False True
1469
1470 instance Movzxw Reg32 (Disp, Reg32, Reg32, Scale) where
1471   movzxw (Reg32 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest 5 disp index (scaleToShift s) False True
1472   movzxw _ _ = onlyEbp
1473
1474 instance Movzxw Reg32 (Disp, Reg32, Scale) where
1475   movzxw (Reg32 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest x86_nobasereg disp index (scaleToShift s) False True
1476
1477 instance Movzxw Reg32 (Reg32, Reg32, Scale) where
1478   movzxw (Reg32 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_widen_memindex dest base 0 index (scaleToShift s) False True
1479
1480
1481 -- load effective address
1482
1483 class Lea a b where
1484   lea :: a -> b -> CodeGen e s ()
1485
1486 instance Lea Reg32 Addr where
1487   lea (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_lea_mem dest source 
1488
1489 instance Lea Reg32 (Disp, Reg32) where
1490   lea (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_lea_membase dest source disp 
1491
1492 instance Lea Reg32 Ind where
1493   lea (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_lea_membase dest source 0 
1494
1495 instance Lea Reg32 (Disp, Reg32, Reg32, Scale) where
1496   lea (Reg32 dest) (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_lea_memindex dest 5 disp index (scaleToShift s)
1497   lea _ _ = onlyEbp
1498
1499 instance Lea Reg32 (Disp, Reg32, Scale) where
1500   lea (Reg32 dest) (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_lea_memindex dest x86_nobasereg disp index (scaleToShift s)
1501
1502 instance Lea Reg32 (Reg32, Reg32, Scale) where
1503   lea (Reg32 dest) (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_lea_memindex dest base 0 index (scaleToShift s)
1504
1505
1506 -- convert word to doubleword
1507
1508 cdq = ensureBufferSize x86_max_instruction_bytes >> x86_cdq
1509
1510
1511 -- wait for FPU
1512
1513 wait = ensureBufferSize x86_max_instruction_bytes >> x86_wait
1514
1515
1516 -- push to stack
1517
1518 class Push a where
1519   push :: a -> CodeGen e s ()
1520
1521 instance Push Reg32 where
1522   push (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_push_reg source 
1523
1524 instance Push Ind where
1525   push (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_push_regp source
1526
1527 instance Push Addr where
1528   push (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_push_mem source 
1529
1530 instance Push (Disp, Reg32) where
1531   push (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_push_membase source disp 
1532
1533 instance Push Word32 where
1534   push imm = ensureBufferSize x86_max_instruction_bytes >> x86_push_imm imm 
1535
1536 instance Push Label where
1537   push l = do ensureBufferSize x86_max_instruction_bytes >> x86_push_imm_template
1538               emitFixup l (-4) Fixup32Absolute
1539
1540 instance Push (Disp, Reg32, Reg32, Scale) where
1541   push (Disp disp, Reg32 5, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_push_memindex 5 disp index (scaleToShift s)
1542   push _ = onlyEbp
1543
1544 instance Push (Disp, Reg32, Scale) where
1545   push (Disp disp, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_push_memindex x86_nobasereg disp index (scaleToShift s)
1546
1547 instance Push (Reg32, Reg32, Scale) where
1548   push (Reg32 base, Reg32 index, s) = ensureBufferSize x86_max_instruction_bytes >> x86_push_memindex base 0 index (scaleToShift s)
1549
1550
1551 -- pop from stack
1552
1553 class Pop a where
1554   pop :: a -> CodeGen e s ()
1555
1556 instance Pop Reg32 where
1557   pop (Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_pop_reg dest 
1558
1559 instance Pop Addr where
1560   pop (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_pop_mem dest 
1561
1562 instance Pop (Disp, Reg32) where
1563   pop (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_pop_membase dest disp 
1564
1565 instance Pop Ind where
1566   pop (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_pop_membase dest 0 
1567
1568
1569 -- push/pop general purpose registers
1570
1571 pushad = ensureBufferSize x86_max_instruction_bytes >> x86_pushad
1572 popad  = ensureBufferSize x86_max_instruction_bytes >> x86_popad
1573
1574
1575 -- push/pop EFLAGS
1576
1577 pushfd = ensureBufferSize x86_max_instruction_bytes >> x86_pushfd
1578 popfd  = ensureBufferSize x86_max_instruction_bytes >> x86_popfd
1579
1580
1581 -- loop according to ECX counter
1582
1583 class Loop a where
1584   loop   :: a -> CodeGen e s ()
1585   loope  :: a -> CodeGen e s ()
1586   loopne :: a -> CodeGen e s ()
1587
1588 instance Loop Word8 where
1589     loop w   = ensureBufferSize x86_max_instruction_bytes >> x86_loop w
1590     loope w  = ensureBufferSize x86_max_instruction_bytes >> x86_loope w
1591     loopne w = ensureBufferSize x86_max_instruction_bytes >> x86_loopne w
1592
1593 instance Loop Label where
1594     loop l   = do ensureBufferSize x86_max_instruction_bytes >> x86_loop 0
1595                   emitFixup l (-1) Fixup8
1596     loope l  = do ensureBufferSize x86_max_instruction_bytes >> x86_loope 0
1597                   emitFixup l (-1) Fixup8
1598     loopne l = do ensureBufferSize x86_max_instruction_bytes >> x86_loopne 0
1599                   emitFixup l (-1) Fixup8
1600
1601 -- jump
1602
1603 class Jmp a where
1604   jmp :: a -> CodeGen e s ()
1605
1606 instance Jmp Word8 where
1607   jmp imm = ensureBufferSize x86_max_instruction_bytes >> x86_jump8 imm 
1608
1609 instance Jmp Word32 where
1610   jmp imm = ensureBufferSize x86_max_instruction_bytes >> x86_jump32 imm 
1611
1612 instance Jmp Reg32 where
1613   jmp (Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_jump_reg dest 
1614
1615 instance Jmp Addr where
1616   jmp (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_jump_mem dest 
1617
1618 instance Jmp (Disp, Reg32) where
1619   jmp (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_jump_membase dest disp 
1620
1621 instance Jmp Ind where
1622   jmp (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_jump_membase dest 0 
1623
1624 instance Jmp Label where
1625   jmp l = do ensureBufferSize x86_max_instruction_bytes >> x86_jump32 0
1626              emitFixup l (-4) Fixup32
1627             
1628 instance Jmp (Ptr a) where
1629   jmp ptr = ensureBufferSize x86_max_instruction_bytes >> x86_jump_pointer ptr 
1630
1631 -- jump on condition code (branch)
1632
1633 class Ja a where
1634   ja :: a -> CodeGen e s ()
1635
1636 instance Ja Word8 where
1637   ja imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_a imm False
1638
1639 instance Ja Word32 where
1640   ja imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_a imm False
1641
1642 instance Ja (Ptr a) where
1643   ja ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_a ptr False
1644
1645 instance Ja Label where
1646   ja l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_a 0 False
1647             emitFixup l (-4) Fixup32
1648
1649 class Jae a where
1650   jae :: a -> CodeGen e s ()
1651
1652 instance Jae Word8 where
1653   jae imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_ae imm False
1654
1655 instance Jae Word32 where
1656   jae imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ae imm False
1657
1658 instance Jae (Ptr a) where
1659   jae ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_ae ptr False
1660
1661 instance Jae Label where
1662   jae l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ae 0 False
1663              emitFixup l (-4) Fixup32
1664
1665 class Jb a where
1666   jb :: a -> CodeGen e s ()
1667
1668 instance Jb Word8 where
1669   jb imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_b imm False
1670
1671 instance Jb Word32 where
1672   jb imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_b imm False
1673
1674 instance Jb (Ptr a) where
1675   jb ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_b ptr False
1676
1677 instance Jb Label where
1678   jb l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_b 0 False
1679             emitFixup l (-4) Fixup32
1680
1681 class Jbe a where
1682   jbe :: a -> CodeGen e s ()
1683
1684 instance Jbe Word8 where
1685   jbe imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_be imm False
1686
1687 instance Jbe Word32 where
1688   jbe imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_be imm False
1689
1690 instance Jbe (Ptr a) where
1691   jbe ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_be ptr False
1692
1693 instance Jbe Label where
1694   jbe l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_be 0 False
1695              emitFixup l (-4) Fixup32
1696
1697 class Jc a where
1698   jc :: a -> CodeGen e s ()
1699
1700 instance Jc Word8 where
1701   jc imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_c imm False
1702
1703 instance Jc Word32 where
1704   jc imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_c imm False
1705
1706 instance Jc (Ptr a) where
1707   jc ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_c ptr False
1708
1709 instance Jc Label where
1710   jc l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_c 0 False
1711             emitFixup l (-4) Fixup32
1712
1713 class Je a where
1714   je :: a -> CodeGen e s ()
1715
1716 instance Je Word8 where
1717   je imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_e imm False
1718
1719 instance Je Word32 where
1720   je imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_e imm False
1721
1722 instance Je (Ptr a) where
1723   je ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_e ptr False
1724
1725 instance Je Label where
1726   je l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_e 0 False
1727             emitFixup l (-4) Fixup32
1728
1729 class Jna a where
1730   jna :: a -> CodeGen e s ()
1731
1732 instance Jna Word8 where
1733   jna imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_na imm False
1734
1735 instance Jna Word32 where
1736   jna imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_na imm False
1737
1738 instance Jna (Ptr a) where
1739   jna ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_na ptr False
1740
1741 instance Jna Label where
1742   jna l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_na 0 False
1743              emitFixup l (-4) Fixup32
1744
1745 class Jnae a where
1746   jnae :: a -> CodeGen e s ()
1747
1748 instance Jnae Word8 where
1749   jnae imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_nae imm False
1750
1751 instance Jnae Word32 where
1752   jnae imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nae imm False
1753
1754 instance Jnae (Ptr a) where
1755   jnae ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_nae ptr False
1756
1757 instance Jnae Label where
1758   jnae l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nae 0 False
1759               emitFixup l (-4) Fixup32
1760
1761 class Jnb a where
1762   jnb :: a -> CodeGen e s ()
1763
1764 instance Jnb Word8 where
1765   jnb imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_nb imm False
1766
1767 instance Jnb Word32 where
1768   jnb imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nb imm False
1769
1770 instance Jnb (Ptr a) where
1771   jnb ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_nb ptr False
1772
1773 instance Jnb Label where
1774   jnb l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nb 0 False
1775              emitFixup l (-4) Fixup32
1776
1777 class Jnbe a where
1778   jnbe :: a -> CodeGen e s ()
1779
1780 instance Jnbe Word8 where
1781   jnbe imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_nbe imm False
1782
1783 instance Jnbe Word32 where
1784   jnbe imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nbe imm False
1785
1786 instance Jnbe (Ptr a) where
1787   jnbe ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_nbe ptr False
1788
1789 instance Jnbe Label where
1790   jnbe l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nbe 0 False
1791               emitFixup l (-4) Fixup32
1792
1793 class Jnc a where
1794   jnc :: a -> CodeGen e s ()
1795
1796 instance Jnc Word8 where
1797   jnc imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_nc imm False
1798
1799 instance Jnc Word32 where
1800   jnc imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nc imm False
1801
1802 instance Jnc (Ptr a) where
1803   jnc ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_nc ptr False
1804
1805 instance Jnc Label where
1806   jnc l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nc 0 False
1807              emitFixup l (-4) Fixup32
1808
1809 class Jne a where
1810   jne :: a -> CodeGen e s ()
1811
1812 instance Jne Word8 where
1813   jne imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_ne imm False
1814
1815 instance Jne Word32 where
1816   jne imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ne imm False
1817
1818 instance Jne (Ptr a) where
1819   jne ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_ne ptr False
1820
1821 instance Jne Label where
1822   jne l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ne 0 False
1823              emitFixup l (-4) Fixup32
1824
1825 class Jnp a where
1826   jnp :: a -> CodeGen e s ()
1827
1828 instance Jnp Word8 where
1829   jnp imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_np imm False
1830
1831 instance Jnp Word32 where
1832   jnp imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_np imm False
1833
1834 instance Jnp (Ptr a) where
1835   jnp ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_np ptr False
1836
1837 instance Jnp Label where
1838   jnp l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_np 0 False
1839              emitFixup l (-4) Fixup32
1840
1841 class Jnz a where
1842   jnz :: a -> CodeGen e s ()
1843
1844 instance Jnz Word8 where
1845   jnz imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_nz imm False
1846
1847 instance Jnz Word32 where
1848   jnz imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nz imm False
1849
1850 instance Jnz (Ptr a) where
1851   jnz ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_nz ptr False
1852
1853 instance Jnz Label where
1854   jnz l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_nz 0 False
1855              emitFixup l (-4) Fixup32
1856
1857 class Jp a where
1858   jp :: a -> CodeGen e s ()
1859
1860 instance Jp Word8 where
1861   jp imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_p imm False
1862
1863 instance Jp Word32 where
1864   jp imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_p imm False
1865
1866 instance Jp (Ptr a) where
1867   jp ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_p ptr False
1868
1869 instance Jp Label where
1870   jp l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_p 0 False
1871             emitFixup l (-4) Fixup32
1872
1873 class Jpe a where
1874   jpe :: a -> CodeGen e s ()
1875
1876 instance Jpe Word8 where
1877   jpe imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_pe imm False
1878
1879 instance Jpe Word32 where
1880   jpe imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_pe imm False
1881
1882 instance Jpe (Ptr a) where
1883   jpe ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_pe ptr False
1884
1885 instance Jpe Label where
1886   jpe l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_pe 0 False
1887              emitFixup l (-4) Fixup32
1888
1889 class Jpo a where
1890   jpo :: a -> CodeGen e s ()
1891
1892 instance Jpo Word8 where
1893   jpo imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_po imm False
1894
1895 instance Jpo Word32 where
1896   jpo imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_po imm False
1897
1898 instance Jpo (Ptr a) where
1899   jpo ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_po ptr False
1900
1901 instance Jpo Label where
1902   jpo l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_po 0 False
1903              emitFixup l (-4) Fixup32
1904
1905 class Jz a where
1906   jz :: a -> CodeGen e s ()
1907
1908 instance Jz Word8 where
1909   jz imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_z imm False
1910
1911 instance Jz Word32 where
1912   jz imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_z imm False
1913
1914 instance Jz (Ptr a) where
1915   jz ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_z ptr False
1916
1917 instance Jz Label where
1918   jz l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_z 0 False
1919             emitFixup l (-4) Fixup32
1920
1921 class Jg a where
1922   jg :: a -> CodeGen e s ()
1923
1924 instance Jg Word8 where
1925   jg imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_gt imm True
1926
1927 instance Jg Word32 where
1928   jg imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_gt imm True
1929
1930 instance Jg (Ptr a) where
1931   jg ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_gt ptr True
1932
1933 instance Jg Label where
1934   jg l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_gt 0 True
1935             emitFixup l (-4) Fixup32
1936
1937 class Jge a where
1938   jge :: a -> CodeGen e s ()
1939
1940 instance Jge Word8 where
1941   jge imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_ge imm True
1942
1943 instance Jge Word32 where
1944   jge imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ge imm True
1945
1946 instance Jge (Ptr a) where
1947   jge ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_ge ptr True
1948
1949 instance Jge Label where
1950   jge l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ge 0 True
1951              emitFixup l (-4) Fixup32
1952
1953 class Jl a where
1954   jl :: a -> CodeGen e s ()
1955
1956 instance Jl Word8 where
1957   jl imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_lt imm True
1958
1959 instance Jl Word32 where
1960   jl imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_lt imm True
1961
1962 instance Jl (Ptr a) where
1963   jl ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_lt ptr True
1964
1965 instance Jl Label where
1966   jl l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_lt 0 True
1967             emitFixup l (-4) Fixup32
1968
1969 class Jle a where
1970   jle :: a -> CodeGen e s ()
1971
1972 instance Jle Word8 where
1973   jle imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_le imm True
1974
1975 instance Jle Word32 where
1976   jle imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_le imm True
1977
1978 instance Jle (Ptr a) where
1979   jle ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_le ptr True
1980
1981 instance Jle Label where
1982   jle l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_le 0 True
1983              emitFixup l (-4) Fixup32
1984
1985 class Jng a where
1986   jng :: a -> CodeGen e s ()
1987
1988 instance Jng Word8 where
1989   jng imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_le imm True
1990
1991 instance Jng Word32 where
1992   jng imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_le imm True
1993
1994 instance Jng (Ptr a) where
1995   jng ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_le ptr True
1996
1997 instance Jng Label where
1998   jng l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_le 0 True
1999              emitFixup l (-4) Fixup32
2000
2001 class Jnge a where
2002   jnge :: a -> CodeGen e s ()
2003
2004 instance Jnge Word8 where
2005   jnge imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_lt imm True
2006
2007 instance Jnge Word32 where
2008   jnge imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_lt imm True
2009
2010 instance Jnge (Ptr a) where
2011   jnge ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_lt ptr True
2012
2013 instance Jnge Label where
2014   jnge l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_lt 0 True
2015               emitFixup l (-4) Fixup32
2016
2017 class Jnl a where
2018   jnl :: a -> CodeGen e s ()
2019
2020 instance Jnl Word8 where
2021   jnl imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_ge imm True
2022
2023 instance Jnl Word32 where
2024   jnl imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ge imm True
2025
2026 instance Jnl (Ptr a) where
2027   jnl ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_ge ptr True
2028
2029 instance Jnl Label where
2030   jnl l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ge 0 True
2031              emitFixup l (-4) Fixup32
2032
2033 class Jnle a where
2034   jnle :: a -> CodeGen e s ()
2035
2036 instance Jnle Word8 where
2037   jnle imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_gt imm True
2038
2039 instance Jnle Word32 where
2040   jnle imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_gt imm True
2041
2042 instance Jnle (Ptr a) where
2043   jnle ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_gt ptr True
2044
2045 instance Jnle Label where
2046   jnle l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_gt 0 True
2047               emitFixup l (-4) Fixup32
2048
2049 class Jno a where
2050   jno :: a -> CodeGen e s ()
2051
2052 instance Jno Word8 where
2053   jno imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_no imm True
2054
2055 instance Jno Word32 where
2056   jno imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_no imm True
2057
2058 instance Jno (Ptr a) where
2059   jno ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_no ptr True
2060
2061 instance Jno Label where
2062   jno l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_no 0 True
2063              emitFixup l (-4) Fixup32
2064
2065 class Jns a where
2066   jns :: a -> CodeGen e s ()
2067
2068 instance Jns Word8 where
2069   jns imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_ns imm True
2070
2071 instance Jns Word32 where
2072   jns imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ns imm True
2073
2074 instance Jns (Ptr a) where
2075   jns ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_ns ptr True
2076
2077 instance Jns Label where
2078   jns l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_ns 0 True
2079              emitFixup l (-4) Fixup32
2080
2081 class Jo a where
2082   jo :: a -> CodeGen e s ()
2083
2084 instance Jo Word8 where
2085   jo imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_o imm True
2086
2087 instance Jo Word32 where
2088   jo imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_o imm True
2089
2090 instance Jo (Ptr a) where
2091   jo ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_o ptr True
2092
2093 instance Jo Label where
2094   jo l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_o 0 True
2095             emitFixup l (-4) Fixup32
2096
2097 class Js a where
2098   js :: a -> CodeGen e s ()
2099
2100 instance Js Word8 where
2101   js imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch8 x86_cc_s imm True
2102
2103 instance Js Word32 where
2104   js imm = ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_s imm True
2105
2106 instance Js (Ptr a) where
2107   js ptr = ensureBufferSize x86_max_instruction_bytes >> x86_branch_pointer x86_cc_s ptr True
2108
2109 instance Js Label where
2110   js l = do ensureBufferSize x86_max_instruction_bytes >> x86_branch32 x86_cc_s 0 True
2111             emitFixup l (-4) Fixup32
2112
2113 -- jump if ecx register is 0
2114
2115 jecxz :: Word8 -> CodeGen e s ()
2116 jecxz w = ensureBufferSize x86_max_instruction_bytes >> x86_jecxz w
2117
2118
2119 -- set byte on condition code
2120
2121 class Seta a where
2122   seta :: a -> CodeGen e s ()
2123
2124 instance Seta Reg8 where
2125   seta (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_a dest False
2126
2127 instance Seta Addr where
2128   seta (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_a dest False
2129
2130 instance Seta (Disp, Reg32) where
2131   seta (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_a dest disp False
2132
2133 instance Seta Ind where
2134   seta (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_a dest 0 False
2135
2136 class Setae a where
2137   setae :: a -> CodeGen e s ()
2138
2139 instance Setae Reg8 where
2140   setae (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_ae dest False
2141
2142 instance Setae Addr where
2143   setae (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_ae dest False
2144
2145 instance Setae (Disp, Reg32) where
2146   setae (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ae dest disp False
2147
2148 instance Setae Ind where
2149   setae (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ae dest 0 False
2150
2151 class Setb a where
2152   setb :: a -> CodeGen e s ()
2153
2154 instance Setb Reg8 where
2155   setb (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_b dest False
2156
2157 instance Setb Addr where
2158   setb (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_b dest False
2159
2160 instance Setb (Disp, Reg32) where
2161   setb (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_b dest disp False
2162
2163 instance Setb Ind where
2164   setb (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_b dest 0 False
2165
2166 class Setbe a where
2167   setbe :: a -> CodeGen e s ()
2168
2169 instance Setbe Reg8 where
2170   setbe (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_be dest False
2171
2172 instance Setbe Addr where
2173   setbe (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_be dest False
2174
2175 instance Setbe (Disp, Reg32) where
2176   setbe (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_be dest disp False
2177
2178 instance Setbe Ind where
2179   setbe (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_be dest 0 False
2180
2181 class Setc a where
2182   setc :: a -> CodeGen e s ()
2183
2184 instance Setc Reg8 where
2185   setc (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_c dest False
2186
2187 instance Setc Addr where
2188   setc (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_c dest False
2189
2190 instance Setc (Disp, Reg32) where
2191   setc (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_c dest disp False
2192
2193 instance Setc Ind where
2194   setc (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_c dest 0 False
2195
2196 class Sete a where
2197   sete :: a -> CodeGen e s ()
2198
2199 instance Sete Reg8 where
2200   sete (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_e dest False
2201
2202 instance Sete Addr where
2203   sete (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_e dest False
2204
2205 instance Sete (Disp, Reg32) where
2206   sete (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_e dest disp False
2207
2208 instance Sete Ind where
2209   sete (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_e dest 0 False
2210
2211 class Setna a where
2212   setna :: a -> CodeGen e s ()
2213
2214 instance Setna Reg8 where
2215   setna (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_na dest False
2216
2217 instance Setna Addr where
2218   setna (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_na dest False
2219
2220 instance Setna (Disp, Reg32) where
2221   setna (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_na dest disp False
2222
2223 instance Setna Ind where
2224   setna (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_na dest 0 False
2225
2226 class Setnae a where
2227   setnae :: a -> CodeGen e s ()
2228
2229 instance Setnae Reg8 where
2230   setnae (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_nae dest False
2231
2232 instance Setnae Addr where
2233   setnae (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_nae dest False
2234
2235 instance Setnae (Disp, Reg32) where
2236   setnae (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nae dest disp False
2237
2238 instance Setnae Ind where
2239   setnae (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nae dest 0 False
2240
2241 class Setnb a where
2242   setnb :: a -> CodeGen e s ()
2243
2244 instance Setnb Reg8 where
2245   setnb (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_nb dest False
2246
2247 instance Setnb Addr where
2248   setnb (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_nb dest False
2249
2250 instance Setnb (Disp, Reg32) where
2251   setnb (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nb dest disp False
2252
2253 instance Setnb Ind where
2254   setnb (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nb dest 0 False
2255
2256 class Setnbe a where
2257   setnbe :: a -> CodeGen e s ()
2258
2259 instance Setnbe Reg8 where
2260   setnbe (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_nbe dest False
2261
2262 instance Setnbe Addr where
2263   setnbe (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_nbe dest False
2264
2265 instance Setnbe (Disp, Reg32) where
2266   setnbe (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nbe dest disp False
2267
2268 instance Setnbe Ind where
2269   setnbe (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nbe dest 0 False
2270
2271 class Setnc a where
2272   setnc :: a -> CodeGen e s ()
2273
2274 instance Setnc Reg8 where
2275   setnc (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_nc dest False
2276
2277 instance Setnc Addr where
2278   setnc (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_nc dest False
2279
2280 instance Setnc (Disp, Reg32) where
2281   setnc (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nc dest disp False
2282
2283 instance Setnc Ind where
2284   setnc (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nc dest 0 False
2285
2286 class Setne a where
2287   setne :: a -> CodeGen e s ()
2288
2289 instance Setne Reg8 where
2290   setne (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_ne dest False
2291
2292 instance Setne Addr where
2293   setne (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_ne dest False
2294
2295 instance Setne (Disp, Reg32) where
2296   setne (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ne dest disp False
2297
2298 instance Setne Ind where
2299   setne (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ne dest 0 False
2300
2301 class Setnp a where
2302   setnp :: a -> CodeGen e s ()
2303
2304 instance Setnp Reg8 where
2305   setnp (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_np dest False
2306
2307 instance Setnp Addr where
2308   setnp (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_np dest False
2309
2310 instance Setnp (Disp, Reg32) where
2311   setnp (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_np dest disp False
2312
2313 instance Setnp Ind where
2314   setnp (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_np dest 0 False
2315
2316 class Setnz a where
2317   setnz :: a -> CodeGen e s ()
2318
2319 instance Setnz Reg8 where
2320   setnz (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_nz dest False
2321
2322 instance Setnz Addr where
2323   setnz (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_nz dest False
2324
2325 instance Setnz (Disp, Reg32) where
2326   setnz (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nz dest disp False
2327
2328 instance Setnz Ind where
2329   setnz (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_nz dest 0 False
2330
2331 class Setp a where
2332   setp :: a -> CodeGen e s ()
2333
2334 instance Setp Reg8 where
2335   setp (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_p dest False
2336
2337 instance Setp Addr where
2338   setp (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_p dest False
2339
2340 instance Setp (Disp, Reg32) where
2341   setp (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_p dest disp False
2342
2343 instance Setp Ind where
2344   setp (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_p dest 0 False
2345
2346 class Setpe a where
2347   setpe :: a -> CodeGen e s ()
2348
2349 instance Setpe Reg8 where
2350   setpe (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_pe dest False
2351
2352 instance Setpe Addr where
2353   setpe (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_pe dest False
2354
2355 instance Setpe (Disp, Reg32) where
2356   setpe (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_pe dest disp False
2357
2358 instance Setpe Ind where
2359   setpe (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_pe dest 0 False
2360
2361 class Setpo a where
2362   setpo :: a -> CodeGen e s ()
2363
2364 instance Setpo Reg8 where
2365   setpo (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_po dest False
2366
2367 instance Setpo Addr where
2368   setpo (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_po dest False
2369
2370 instance Setpo (Disp, Reg32) where
2371   setpo (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_po dest disp False
2372
2373 instance Setpo Ind where
2374   setpo (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_po dest 0 False
2375
2376 class Setg a where
2377   setg :: a -> CodeGen e s ()
2378
2379 instance Setg Reg8 where
2380   setg (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_gt dest True
2381
2382 instance Setg Addr where
2383   setg (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_gt dest True
2384
2385 instance Setg (Disp, Reg32) where
2386   setg (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_gt dest disp True
2387
2388 instance Setg Ind where
2389   setg (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_gt dest 0 True
2390
2391 class Setge a where
2392   setge :: a -> CodeGen e s ()
2393
2394 instance Setge Reg8 where
2395   setge (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_ge dest True
2396
2397 instance Setge Addr where
2398   setge (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_ge dest True
2399
2400 instance Setge (Disp, Reg32) where
2401   setge (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ge dest disp True
2402
2403 instance Setge Ind where
2404   setge (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ge dest 0 True
2405
2406 class Setl a where
2407   setl :: a -> CodeGen e s ()
2408
2409 instance Setl Reg8 where
2410   setl (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_lt dest True
2411
2412 instance Setl Addr where
2413   setl (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_lt dest True
2414
2415 instance Setl (Disp, Reg32) where
2416   setl (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_lt dest disp True
2417
2418 instance Setl Ind where
2419   setl (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_lt dest 0 True
2420
2421 class Setle a where
2422   setle :: a -> CodeGen e s ()
2423
2424 instance Setle Reg8 where
2425   setle (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_le dest True
2426
2427 instance Setle Addr where
2428   setle (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_le dest True
2429
2430 instance Setle (Disp, Reg32) where
2431   setle (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_le dest disp True
2432
2433 instance Setle Ind where
2434   setle (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_le dest 0 True
2435
2436 class Setng a where
2437   setng :: a -> CodeGen e s ()
2438
2439 instance Setng Reg8 where
2440   setng (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_le dest True
2441
2442 instance Setng Addr where
2443   setng (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_le dest True
2444
2445 instance Setng (Disp, Reg32) where
2446   setng (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_le dest disp True
2447
2448 instance Setng Ind where
2449   setng (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_le dest 0 True
2450
2451 class Setnge a where
2452   setnge :: a -> CodeGen e s ()
2453
2454 instance Setnge Reg8 where
2455   setnge (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_lt dest True
2456
2457 instance Setnge Addr where
2458   setnge (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_lt dest True
2459
2460 instance Setnge (Disp, Reg32) where
2461   setnge (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_lt dest disp True
2462
2463 instance Setnge Ind where
2464   setnge (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_lt dest 0 True
2465
2466 class Setnl a where
2467   setnl :: a -> CodeGen e s ()
2468
2469 instance Setnl Reg8 where
2470   setnl (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_ge dest True
2471
2472 instance Setnl Addr where
2473   setnl (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_ge dest True
2474
2475 instance Setnl (Disp, Reg32) where
2476   setnl (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ge dest disp True
2477
2478 instance Setnl Ind where
2479   setnl (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ge dest 0 True
2480
2481 class Setnle a where
2482   setnle :: a -> CodeGen e s ()
2483
2484 instance Setnle Reg8 where
2485   setnle (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_gt dest True
2486
2487 instance Setnle Addr where
2488   setnle (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_gt dest True
2489
2490 instance Setnle (Disp, Reg32) where
2491   setnle (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_gt dest disp True
2492
2493 instance Setnle Ind where
2494   setnle (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_gt dest 0 True
2495
2496 class Setno a where
2497   setno :: a -> CodeGen e s ()
2498
2499 instance Setno Reg8 where
2500   setno (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_no dest True
2501
2502 instance Setno Addr where
2503   setno (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_no dest True
2504
2505 instance Setno (Disp, Reg32) where
2506   setno (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_no dest disp True
2507
2508 instance Setno Ind where
2509   setno (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_no dest 0 True
2510
2511 class Setns a where
2512   setns :: a -> CodeGen e s ()
2513
2514 instance Setns Reg8 where
2515   setns (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_ns dest True
2516
2517 instance Setns Addr where
2518   setns (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_ns dest True
2519
2520 instance Setns (Disp, Reg32) where
2521   setns (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ns dest disp True
2522
2523 instance Setns Ind where
2524   setns (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_ns dest 0 True
2525
2526 class Seto a where
2527   seto :: a -> CodeGen e s ()
2528
2529 instance Seto Reg8 where
2530   seto (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_o dest True
2531
2532 instance Seto Addr where
2533   seto (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_o dest True
2534
2535 instance Seto (Disp, Reg32) where
2536   seto (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_o dest disp True
2537
2538 instance Seto Ind where
2539   seto (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_o dest 0 True
2540
2541 class Sets a where
2542   sets :: a -> CodeGen e s ()
2543
2544 instance Sets Reg8 where
2545   sets (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_s dest True
2546
2547 instance Sets Addr where
2548   sets (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_s dest True
2549
2550 instance Sets (Disp, Reg32) where
2551   sets (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_s dest disp True
2552
2553 instance Sets Ind where
2554   sets (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_s dest 0 True
2555
2556 class Setz a where
2557   setz :: a -> CodeGen e s ()
2558
2559 instance Setz Reg8 where
2560   setz (Reg8 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_reg x86_cc_z dest False
2561
2562 instance Setz Addr where
2563   setz (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_mem x86_cc_z dest False
2564
2565 instance Setz (Disp, Reg32) where
2566   setz (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_z dest disp False
2567
2568 instance Setz Ind where
2569   setz (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_set_membase x86_cc_z dest 0 False
2570
2571
2572 -- call procedure
2573
2574 class Call a where
2575   call :: a -> CodeGen e s ()
2576
2577 instance Call Word32 where
2578   call imm = ensureBufferSize x86_max_instruction_bytes >> x86_call_imm imm 
2579
2580 instance Call Label where
2581   call l = do ensureBufferSize x86_max_instruction_bytes >> x86_call_imm 0
2582               emitFixup l (-4) Fixup32
2583
2584 instance Call Reg32 where
2585   call (Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_call_reg dest 
2586
2587 instance Call Addr where
2588   call (Addr dest) = ensureBufferSize x86_max_instruction_bytes >> x86_call_mem dest 
2589
2590 instance Call (Disp, Reg32) where
2591   call (Disp disp, Reg32 dest) = ensureBufferSize x86_max_instruction_bytes >> x86_call_membase dest disp 
2592
2593 instance Call Ind where
2594   call (Ind (Reg32 dest)) = ensureBufferSize x86_max_instruction_bytes >> x86_call_membase dest 0 
2595
2596 instance Call (FunPtr a) where
2597   call f = ensureBufferSize x86_max_instruction_bytes >> x86_call_hs f
2598
2599
2600 -- return from procedure
2601
2602 ret :: CodeGen e s ()
2603 ret = ensureBufferSize x86_max_instruction_bytes >> x86_ret
2604
2605 retN :: Word16 -> CodeGen e s ()
2606 retN n = ensureBufferSize x86_max_instruction_bytes >> x86_ret_imm n
2607
2608
2609 -- make stack frame
2610
2611 enter :: Word16 -> CodeGen e s ()
2612 enter w = ensureBufferSize x86_max_instruction_bytes >> x86_enter w
2613
2614
2615 -- conditional move
2616
2617 class Cmova a b where
2618   cmova :: a -> b -> CodeGen e s ()
2619
2620 instance Cmova Reg32 Reg32 where
2621   cmova (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_a False dest source
2622
2623 instance Cmova Reg32 Addr where
2624   cmova (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_a False dest source
2625
2626 instance Cmova Reg32 (Disp, Reg32) where
2627   cmova (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_a False dest source disp
2628
2629 instance Cmova Reg32 Ind where
2630   cmova (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_a False dest source 0
2631
2632 class Cmovae a b where
2633   cmovae :: a -> b -> CodeGen e s ()
2634
2635 instance Cmovae Reg32 Reg32 where
2636   cmovae (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_ae False dest source
2637
2638 instance Cmovae Reg32 Addr where
2639   cmovae (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_ae False dest source
2640
2641 instance Cmovae Reg32 (Disp, Reg32) where
2642   cmovae (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ae False dest source disp
2643
2644 instance Cmovae Reg32 Ind where
2645   cmovae (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ae False dest source 0
2646
2647 class Cmovb a b where
2648   cmovb :: a -> b -> CodeGen e s ()
2649
2650 instance Cmovb Reg32 Reg32 where
2651   cmovb (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_b False dest source
2652
2653 instance Cmovb Reg32 Addr where
2654   cmovb (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_b False dest source
2655
2656 instance Cmovb Reg32 (Disp, Reg32) where
2657   cmovb (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_b False dest source disp
2658
2659 instance Cmovb Reg32 Ind where
2660   cmovb (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_b False dest source 0
2661
2662 class Cmovbe a b where
2663   cmovbe :: a -> b -> CodeGen e s ()
2664
2665 instance Cmovbe Reg32 Reg32 where
2666   cmovbe (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_be False dest source
2667
2668 instance Cmovbe Reg32 Addr where
2669   cmovbe (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_be False dest source
2670
2671 instance Cmovbe Reg32 (Disp, Reg32) where
2672   cmovbe (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_be False dest source disp
2673
2674 instance Cmovbe Reg32 Ind where
2675   cmovbe (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_be False dest source 0
2676
2677 class Cmovc a b where
2678   cmovc :: a -> b -> CodeGen e s ()
2679
2680 instance Cmovc Reg32 Reg32 where
2681   cmovc (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_c False dest source
2682
2683 instance Cmovc Reg32 Addr where
2684   cmovc (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_c False dest source
2685
2686 instance Cmovc Reg32 (Disp, Reg32) where
2687   cmovc (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_c False dest source disp
2688
2689 instance Cmovc Reg32 Ind where
2690   cmovc (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_c False dest source 0
2691
2692 class Cmove a b where
2693   cmove :: a -> b -> CodeGen e s ()
2694
2695 instance Cmove Reg32 Reg32 where
2696   cmove (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_e False dest source
2697
2698 instance Cmove Reg32 Addr where
2699   cmove (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_e False dest source
2700
2701 instance Cmove Reg32 (Disp, Reg32) where
2702   cmove (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_e False dest source disp
2703
2704 instance Cmove Reg32 Ind where
2705   cmove (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_e False dest source 0
2706
2707 class Cmovna a b where
2708   cmovna :: a -> b -> CodeGen e s ()
2709
2710 instance Cmovna Reg32 Reg32 where
2711   cmovna (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_na False dest source
2712
2713 instance Cmovna Reg32 Addr where
2714   cmovna (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_na False dest source
2715
2716 instance Cmovna Reg32 (Disp, Reg32) where
2717   cmovna (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_na False dest source disp
2718
2719 instance Cmovna Reg32 Ind where
2720   cmovna (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_na False dest source 0
2721
2722 class Cmovnae a b where
2723   cmovnae :: a -> b -> CodeGen e s ()
2724
2725 instance Cmovnae Reg32 Reg32 where
2726   cmovnae (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_nae False dest source
2727
2728 instance Cmovnae Reg32 Addr where
2729   cmovnae (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_nae False dest source
2730
2731 instance Cmovnae Reg32 (Disp, Reg32) where
2732   cmovnae (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nae False dest source disp
2733
2734 instance Cmovnae Reg32 Ind where
2735   cmovnae (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nae False dest source 0
2736
2737 class Cmovnb a b where
2738   cmovnb :: a -> b -> CodeGen e s ()
2739
2740 instance Cmovnb Reg32 Reg32 where
2741   cmovnb (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_nb False dest source
2742
2743 instance Cmovnb Reg32 Addr where
2744   cmovnb (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_nb False dest source
2745
2746 instance Cmovnb Reg32 (Disp, Reg32) where
2747   cmovnb (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nb False dest source disp
2748
2749 instance Cmovnb Reg32 Ind where
2750   cmovnb (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nb False dest source 0
2751
2752 class Cmovnbe a b where
2753   cmovnbe :: a -> b -> CodeGen e s ()
2754
2755 instance Cmovnbe Reg32 Reg32 where
2756   cmovnbe (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_nbe False dest source
2757
2758 instance Cmovnbe Reg32 Addr where
2759   cmovnbe (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_nbe False dest source
2760
2761 instance Cmovnbe Reg32 (Disp, Reg32) where
2762   cmovnbe (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nbe False dest source disp
2763
2764 instance Cmovnbe Reg32 Ind where
2765   cmovnbe (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nbe False dest source 0
2766
2767 class Cmovnc a b where
2768   cmovnc :: a -> b -> CodeGen e s ()
2769
2770 instance Cmovnc Reg32 Reg32 where
2771   cmovnc (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_nc False dest source
2772
2773 instance Cmovnc Reg32 Addr where
2774   cmovnc (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_nc False dest source
2775
2776 instance Cmovnc Reg32 (Disp, Reg32) where
2777   cmovnc (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nc False dest source disp
2778
2779 instance Cmovnc Reg32 Ind where
2780   cmovnc (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nc False dest source 0
2781
2782 class Cmovne a b where
2783   cmovne :: a -> b -> CodeGen e s ()
2784
2785 instance Cmovne Reg32 Reg32 where
2786   cmovne (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_ne False dest source
2787
2788 instance Cmovne Reg32 Addr where
2789   cmovne (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_ne False dest source
2790
2791 instance Cmovne Reg32 (Disp, Reg32) where
2792   cmovne (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ne False dest source disp
2793
2794 instance Cmovne Reg32 Ind where
2795   cmovne (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ne False dest source 0
2796
2797 class Cmovnp a b where
2798   cmovnp :: a -> b -> CodeGen e s ()
2799
2800 instance Cmovnp Reg32 Reg32 where
2801   cmovnp (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_np False dest source
2802
2803 instance Cmovnp Reg32 Addr where
2804   cmovnp (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_np False dest source
2805
2806 instance Cmovnp Reg32 (Disp, Reg32) where
2807   cmovnp (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_np False dest source disp
2808
2809 instance Cmovnp Reg32 Ind where
2810   cmovnp (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_np False dest source 0
2811
2812 class Cmovnz a b where
2813   cmovnz :: a -> b -> CodeGen e s ()
2814
2815 instance Cmovnz Reg32 Reg32 where
2816   cmovnz (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_nz False dest source
2817
2818 instance Cmovnz Reg32 Addr where
2819   cmovnz (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_nz False dest source
2820
2821 instance Cmovnz Reg32 (Disp, Reg32) where
2822   cmovnz (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nz False dest source disp
2823
2824 instance Cmovnz Reg32 Ind where
2825   cmovnz (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_nz False dest source 0
2826
2827 class Cmovp a b where
2828   cmovp :: a -> b -> CodeGen e s ()
2829
2830 instance Cmovp Reg32 Reg32 where
2831   cmovp (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_p False dest source
2832
2833 instance Cmovp Reg32 Addr where
2834   cmovp (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_p False dest source
2835
2836 instance Cmovp Reg32 (Disp, Reg32) where
2837   cmovp (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_p False dest source disp
2838
2839 instance Cmovp Reg32 Ind where
2840   cmovp (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_p False dest source 0
2841
2842 class Cmovpe a b where
2843   cmovpe :: a -> b -> CodeGen e s ()
2844
2845 instance Cmovpe Reg32 Reg32 where
2846   cmovpe (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_pe False dest source
2847
2848 instance Cmovpe Reg32 Addr where
2849   cmovpe (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_pe False dest source
2850
2851 instance Cmovpe Reg32 (Disp, Reg32) where
2852   cmovpe (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_pe False dest source disp
2853
2854 instance Cmovpe Reg32 Ind where
2855   cmovpe (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_pe False dest source 0
2856
2857 class Cmovpo a b where
2858   cmovpo :: a -> b -> CodeGen e s ()
2859
2860 instance Cmovpo Reg32 Reg32 where
2861   cmovpo (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_po False dest source
2862
2863 instance Cmovpo Reg32 Addr where
2864   cmovpo (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_po False dest source
2865
2866 instance Cmovpo Reg32 (Disp, Reg32) where
2867   cmovpo (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_po False dest source disp
2868
2869 instance Cmovpo Reg32 Ind where
2870   cmovpo (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_po False dest source 0
2871
2872 class Cmovz a b where
2873   cmovz :: a -> b -> CodeGen e s ()
2874
2875 instance Cmovz Reg32 Reg32 where
2876   cmovz (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_z False dest source
2877
2878 instance Cmovz Reg32 Addr where
2879   cmovz (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_z False dest source
2880
2881 instance Cmovz Reg32 (Disp, Reg32) where
2882   cmovz (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_z False dest source disp
2883
2884 instance Cmovz Reg32 Ind where
2885   cmovz (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_z False dest source 0
2886
2887 class Cmovg a b where
2888   cmovg :: a -> b -> CodeGen e s ()
2889
2890 instance Cmovg Reg32 Reg32 where
2891   cmovg (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_gt True dest source
2892
2893 instance Cmovg Reg32 Addr where
2894   cmovg (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_gt True dest source
2895
2896 instance Cmovg Reg32 (Disp, Reg32) where
2897   cmovg (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_gt True dest source disp
2898
2899 instance Cmovg Reg32 Ind where
2900   cmovg (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_gt True dest source 0
2901
2902 class Cmovge a b where
2903   cmovge :: a -> b -> CodeGen e s ()
2904
2905 instance Cmovge Reg32 Reg32 where
2906   cmovge (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_ge True dest source
2907
2908 instance Cmovge Reg32 Addr where
2909   cmovge (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_ge True dest source
2910
2911 instance Cmovge Reg32 (Disp, Reg32) where
2912   cmovge (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ge True dest source disp
2913
2914 instance Cmovge Reg32 Ind where
2915   cmovge (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ge True dest source 0
2916
2917 class Cmovl a b where
2918   cmovl :: a -> b -> CodeGen e s ()
2919
2920 instance Cmovl Reg32 Reg32 where
2921   cmovl (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_lt True dest source
2922
2923 instance Cmovl Reg32 Addr where
2924   cmovl (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_lt True dest source
2925
2926 instance Cmovl Reg32 (Disp, Reg32) where
2927   cmovl (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_lt True dest source disp
2928
2929 instance Cmovl Reg32 Ind where
2930   cmovl (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_lt True dest source 0
2931
2932 class Cmovle a b where
2933   cmovle :: a -> b -> CodeGen e s ()
2934
2935 instance Cmovle Reg32 Reg32 where
2936   cmovle (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_le True dest source
2937
2938 instance Cmovle Reg32 Addr where
2939   cmovle (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_le True dest source
2940
2941 instance Cmovle Reg32 (Disp, Reg32) where
2942   cmovle (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_le True dest source disp
2943
2944 instance Cmovle Reg32 Ind where
2945   cmovle (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_le True dest source 0
2946
2947 class Cmovng a b where
2948   cmovng :: a -> b -> CodeGen e s ()
2949
2950 instance Cmovng Reg32 Reg32 where
2951   cmovng (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_le True dest source
2952
2953 instance Cmovng Reg32 Addr where
2954   cmovng (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_le True dest source
2955
2956 instance Cmovng Reg32 (Disp, Reg32) where
2957   cmovng (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_le True dest source disp
2958
2959 instance Cmovng Reg32 Ind where
2960   cmovng (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_le True dest source 0
2961
2962 class Cmovnge a b where
2963   cmovnge :: a -> b -> CodeGen e s ()
2964
2965 instance Cmovnge Reg32 Reg32 where
2966   cmovnge (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_lt True dest source
2967
2968 instance Cmovnge Reg32 Addr where
2969   cmovnge (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_lt True dest source
2970
2971 instance Cmovnge Reg32 (Disp, Reg32) where
2972   cmovnge (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_lt True dest source disp
2973
2974 instance Cmovnge Reg32 Ind where
2975   cmovnge (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_lt True dest source 0
2976
2977 class Cmovnl a b where
2978   cmovnl :: a -> b -> CodeGen e s ()
2979
2980 instance Cmovnl Reg32 Reg32 where
2981   cmovnl (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_ge True dest source
2982
2983 instance Cmovnl Reg32 Addr where
2984   cmovnl (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_ge True dest source
2985
2986 instance Cmovnl Reg32 (Disp, Reg32) where
2987   cmovnl (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ge True dest source disp
2988
2989 instance Cmovnl Reg32 Ind where
2990   cmovnl (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ge True dest source 0
2991
2992 class Cmovnle a b where
2993   cmovnle :: a -> b -> CodeGen e s ()
2994
2995 instance Cmovnle Reg32 Reg32 where
2996   cmovnle (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_gt True dest source
2997
2998 instance Cmovnle Reg32 Addr where
2999   cmovnle (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_gt True dest source
3000
3001 instance Cmovnle Reg32 (Disp, Reg32) where
3002   cmovnle (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_gt True dest source disp
3003
3004 instance Cmovnle Reg32 Ind where
3005   cmovnle (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_gt True dest source 0
3006
3007 class Cmovno a b where
3008   cmovno :: a -> b -> CodeGen e s ()
3009
3010 instance Cmovno Reg32 Reg32 where
3011   cmovno (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_no True dest source
3012
3013 instance Cmovno Reg32 Addr where
3014   cmovno (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_no True dest source
3015
3016 instance Cmovno Reg32 (Disp, Reg32) where
3017   cmovno (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_no True dest source disp
3018
3019 instance Cmovno Reg32 Ind where
3020   cmovno (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_no True dest source 0
3021
3022 class Cmovns a b where
3023   cmovns :: a -> b -> CodeGen e s ()
3024
3025 instance Cmovns Reg32 Reg32 where
3026   cmovns (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_ns True dest source
3027
3028 instance Cmovns Reg32 Addr where
3029   cmovns (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_ns True dest source
3030
3031 instance Cmovns Reg32 (Disp, Reg32) where
3032   cmovns (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ns True dest source disp
3033
3034 instance Cmovns Reg32 Ind where
3035   cmovns (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_ns True dest source 0
3036
3037 class Cmovo a b where
3038   cmovo :: a -> b -> CodeGen e s ()
3039
3040 instance Cmovo Reg32 Reg32 where
3041   cmovo (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_o True dest source
3042
3043 instance Cmovo Reg32 Addr where
3044   cmovo (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_o True dest source
3045
3046 instance Cmovo Reg32 (Disp, Reg32) where
3047   cmovo (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_o True dest source disp
3048
3049 instance Cmovo Reg32 Ind where
3050   cmovo (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_o True dest source 0
3051
3052 class Cmovs a b where
3053   cmovs :: a -> b -> CodeGen e s ()
3054
3055 instance Cmovs Reg32 Reg32 where
3056   cmovs (Reg32 dest) (Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_reg x86_cc_s True dest source
3057
3058 instance Cmovs Reg32 Addr where
3059   cmovs (Reg32 dest) (Addr source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_mem x86_cc_s True dest source
3060
3061 instance Cmovs Reg32 (Disp, Reg32) where
3062   cmovs (Reg32 dest) (Disp disp, Reg32 source) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_s True dest source disp
3063
3064 instance Cmovs Reg32 Ind where
3065   cmovs (Reg32 dest) (Ind (Reg32 source)) = ensureBufferSize x86_max_instruction_bytes >> x86_cmov_membase x86_cc_s True dest source 0
3066
3067
3068 -- release stack frame
3069
3070 leave :: CodeGen e s ()
3071 leave = ensureBufferSize x86_max_instruction_bytes >> x86_leave
3072
3073
3074 -- store ah into flags
3075
3076 sahf :: CodeGen e s ()
3077 sahf = ensureBufferSize x86_max_instruction_bytes >> x86_sahf
3078
3079 -- Floating point instructions
3080
3081 fldz = ensureBufferSize x86_max_instruction_bytes >> x86_fldz
3082 fld1 = ensureBufferSize x86_max_instruction_bytes >> x86_fld1
3083 fldpi = ensureBufferSize x86_max_instruction_bytes >> x86_fldpi
3084
3085 fstsw = ensureBufferSize x86_max_instruction_bytes >> x86_fstsw
3086 fnstsw = ensureBufferSize x86_max_instruction_bytes >> x86_fstsw
3087
3088 fcompp = ensureBufferSize x86_max_instruction_bytes >> x86_fcompp
3089 fucompp = ensureBufferSize x86_max_instruction_bytes >> x86_fucompp
3090
3091 fchs = ensureBufferSize x86_max_instruction_bytes >> x86_fchs
3092 frem = ensureBufferSize x86_max_instruction_bytes >> x86_frem
3093
3094 fxch (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fxch idx
3095
3096 fcomi (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fcomi idx
3097 fcomip (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fcomip idx
3098 fucomi (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fucomi idx
3099 fucomip (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fucomip idx
3100
3101 fsin = ensureBufferSize x86_max_instruction_bytes >> x86_fsin
3102 fcos = ensureBufferSize x86_max_instruction_bytes >> x86_fcos
3103 fptan = ensureBufferSize x86_max_instruction_bytes >> x86_fptan
3104 fpatan = ensureBufferSize x86_max_instruction_bytes >> x86_fpatan
3105 fabs = ensureBufferSize x86_max_instruction_bytes >> x86_fabs
3106 ftst = ensureBufferSize x86_max_instruction_bytes >> x86_ftst
3107 fxam = ensureBufferSize x86_max_instruction_bytes >> x86_fxam
3108 fprem = ensureBufferSize x86_max_instruction_bytes >> x86_fprem
3109 fprem1 = ensureBufferSize x86_max_instruction_bytes >> x86_fprem1
3110 frndint = ensureBufferSize x86_max_instruction_bytes >> x86_frndint
3111 fsqrt = ensureBufferSize x86_max_instruction_bytes >> x86_fsqrt
3112
3113 class Fadd a b where
3114     fadd :: a -> b -> CodeGen e s ()
3115
3116 instance Fadd FPTopReg FPReg where
3117     fadd FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fadd idx
3118
3119 instance Fadd FPTopReg Addr where
3120     fadd FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fadd a True
3121
3122 instance Fadd FPTopReg (Disp, Reg32) where
3123     fadd FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fadd r d True
3124
3125 instance Fadd FPTopReg Ind where
3126     fadd FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fadd r 0 True
3127
3128 instance Fadd FPReg FPTopReg where
3129     fadd (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fadd idx False
3130
3131
3132 class Faddp a b where
3133     faddp :: a -> b -> CodeGen e s ()
3134
3135 instance Faddp FPReg FPTopReg where
3136     faddp (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fadd idx True
3137
3138
3139 class Fiadd a b where
3140     fiadd32 :: a -> b -> CodeGen e s ()
3141     fiadd16 :: a -> b -> CodeGen e s ()
3142
3143 instance Fiadd FPTopReg (Disp, Reg32) where
3144     fiadd32 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fadd r d True
3145     fiadd16 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fadd r d False
3146
3147 instance Fiadd FPTopReg Ind where
3148     fiadd32 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fadd r 0 True
3149     fiadd16 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fadd r 0 False
3150
3151
3152 class Fsub a b where
3153     fsub :: a -> b -> CodeGen e s ()
3154
3155 instance Fsub FPTopReg FPReg where
3156     fsub FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fsub idx
3157
3158 instance Fsub FPTopReg Addr where
3159     fsub FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fsub a True
3160
3161 instance Fsub FPTopReg (Disp, Reg32) where
3162     fsub FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fsub r d True
3163
3164 instance Fsub FPTopReg Ind where
3165     fsub FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fsub r 0 True
3166
3167 instance Fsub FPReg FPTopReg where
3168     fsub (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fsub idx False
3169
3170
3171 class Fsubp a b where
3172     fsubp :: a -> b -> CodeGen e s ()
3173
3174 instance Fsubp FPReg FPTopReg where
3175     fsubp (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fsub idx True
3176
3177
3178 class Fisub a b where
3179     fisub32 :: a -> b -> CodeGen e s ()
3180     fisub16 :: a -> b -> CodeGen e s ()
3181
3182 instance Fisub FPTopReg (Disp, Reg32) where
3183     fisub32 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fsub r d True
3184     fisub16 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fsub r d False
3185
3186 instance Fisub FPTopReg Ind where
3187     fisub32 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fsub r 0 True
3188     fisub16 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fsub r 0 False
3189
3190
3191 class Fsubr a b where
3192     fsubr :: a -> b -> CodeGen e s ()
3193
3194 instance Fsubr FPTopReg FPReg where
3195     fsubr FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fsubr idx
3196
3197 instance Fsubr FPTopReg Addr where
3198     fsubr FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fsubr a True
3199
3200 instance Fsubr FPTopReg (Disp, Reg32) where
3201     fsubr FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fsubr r d True
3202
3203 instance Fsubr FPTopReg Ind where
3204     fsubr FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fsubr r 0 True
3205
3206
3207 class Fmul a b where
3208     fmul :: a -> b -> CodeGen e s ()
3209
3210 instance Fmul FPTopReg FPReg where
3211     fmul FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fmul idx
3212
3213 instance Fmul FPTopReg Addr where
3214     fmul FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fmul a True
3215
3216 instance Fmul FPTopReg (Disp, Reg32) where
3217     fmul FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fmul r d True
3218
3219 instance Fmul FPTopReg Ind where
3220     fmul FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fmul r 0 True
3221
3222 instance Fmul FPReg FPTopReg where
3223     fmul (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fmul idx False
3224
3225
3226 class Fmulp a b where
3227     fmulp :: a -> b -> CodeGen e s ()
3228
3229 instance Fmulp FPReg FPTopReg where
3230     fmulp (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fmul idx True
3231
3232
3233 class Fimul a b where
3234     fimul32 :: a -> b -> CodeGen e s ()
3235     fimul16 :: a -> b -> CodeGen e s ()
3236
3237 instance Fimul FPTopReg (Disp, Reg32) where
3238     fimul32 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fmul r d True
3239     fimul16 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fmul r d False
3240
3241 instance Fimul FPTopReg Ind where
3242     fimul32 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fmul r 0 True
3243     fimul16 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fmul r 0 False
3244
3245
3246 class Fdiv a b where
3247     fdiv :: a -> b -> CodeGen e s ()
3248
3249 instance Fdiv FPTopReg FPReg where
3250     fdiv FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fdiv idx
3251
3252 instance Fdiv FPTopReg Addr where
3253     fdiv FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fdiv a True
3254
3255 instance Fdiv FPTopReg (Disp, Reg32) where
3256     fdiv FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fdiv r d True
3257
3258 instance Fdiv FPTopReg Ind where
3259     fdiv FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fdiv r 0 True
3260
3261 instance Fdiv FPReg FPTopReg where
3262     fdiv (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fdiv idx False
3263
3264
3265 class Fdivp a b where
3266     fdivp :: a -> b -> CodeGen e s ()
3267
3268 instance Fdivp FPReg FPTopReg where
3269     fdivp (FPReg idx) FPTopReg = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_reg x86_fdiv idx True
3270
3271
3272 class Fidiv a b where
3273     fidiv32 :: a -> b -> CodeGen e s ()
3274     fidiv16 :: a -> b -> CodeGen e s ()
3275
3276 instance Fidiv FPTopReg (Disp, Reg32) where
3277     fidiv32 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fdiv r d True
3278     fidiv16 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fdiv r d False
3279
3280 instance Fidiv FPTopReg Ind where
3281     fidiv32 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fdiv r 0 True
3282     fidiv16 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_int_op_membase x86_fdiv r 0 False
3283
3284
3285 class Fdivr a b where
3286     fdivr :: a -> b -> CodeGen e s ()
3287
3288 instance Fdivr FPTopReg FPReg where
3289     fdivr FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fdivr idx
3290
3291 instance Fdivr FPTopReg Addr where
3292     fdivr FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fdivr a True
3293
3294 instance Fdivr FPTopReg (Disp, Reg32) where
3295     fdivr FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fdivr r d True
3296
3297 instance Fdivr FPTopReg Ind where
3298     fdivr FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fdivr r 0 True
3299
3300
3301 class Fcom a b where
3302     fcom :: a -> b -> CodeGen e s ()
3303
3304 instance Fcom FPTopReg FPReg where
3305     fcom FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fcom idx
3306
3307 instance Fcom FPTopReg Addr where
3308     fcom FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fcom a True
3309
3310 instance Fcom FPTopReg (Disp, Reg32) where
3311     fcom FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fcom r d True
3312
3313 instance Fcom FPTopReg Ind where
3314     fcom FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fcom r 0 True
3315
3316
3317 class Fcomp a b where
3318     fcomp :: a -> b -> CodeGen e s ()
3319
3320 instance Fcomp FPTopReg FPReg where
3321     fcomp FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op x86_fcomp idx
3322
3323 instance Fcomp FPTopReg Addr where
3324     fcomp FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_mem x86_fcomp a True
3325
3326 instance Fcomp FPTopReg (Disp, Reg32) where
3327     fcomp FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fcomp r d True
3328
3329 instance Fcomp FPTopReg Ind where
3330     fcomp FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fp_op_membase x86_fcomp r 0 True
3331
3332
3333 class Fld a b where
3334     fld :: a -> b -> CodeGen e s ()
3335
3336 instance Fld FPTopReg FPReg where
3337     fld FPTopReg (FPReg idx) = ensureBufferSize x86_max_instruction_bytes >> x86_fld_reg idx
3338
3339 instance Fld FPTopReg Addr where 
3340     fld FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fld a True
3341
3342 instance Fld FPTopReg (Disp, Reg32) where 
3343     fld FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fld_membase r d True
3344
3345 instance Fld FPTopReg Ind where 
3346     fld FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fld_membase r 0 True
3347
3348 class Fld80 a b where
3349     fld80 :: a -> b -> CodeGen e s ()
3350
3351 instance Fld80 FPTopReg Addr where 
3352     fld80 FPTopReg (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fld80_mem a
3353
3354 instance Fld80 FPTopReg (Disp, Reg32) where 
3355     fld80 FPTopReg (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fld80_membase r d
3356
3357 instance Fld80 FPTopReg Ind where 
3358     fld80 FPTopReg (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fld80_membase r 0
3359
3360 class Fst a where
3361     fst :: a -> CodeGen e s ()
3362
3363 instance Fst Addr where
3364     fst (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fst a True False
3365
3366 instance Fst (Disp, Reg32) where
3367     fst (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fst_membase r d True False
3368
3369 instance Fst Ind where
3370     fst (Ind (Reg32 r)) =  ensureBufferSize x86_max_instruction_bytes >> x86_fst_membase r 0 True False
3371
3372 class Fstp a where
3373     fstp :: a -> CodeGen e s ()
3374
3375 instance Fstp FPReg where
3376     fstp (FPReg r) = ensureBufferSize x86_max_instruction_bytes >> x86_fstp r
3377
3378 instance Fstp Addr where
3379     fstp (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fst a True True
3380
3381 instance Fstp (Disp, Reg32) where
3382     fstp (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fst_membase r d True True
3383
3384 instance Fstp Ind where
3385     fstp (Ind (Reg32 r)) =  ensureBufferSize x86_max_instruction_bytes >> x86_fst_membase r 0 True True
3386
3387
3388 class Fst80 a where
3389     fst80 :: a -> CodeGen e s ()
3390
3391 instance Fst80 Addr where
3392     fst80 (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fst80_mem a
3393
3394 instance Fst80 (Disp, Reg32) where
3395     fst80 (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fst80_membase r d
3396
3397 instance Fst80 Ind where
3398     fst80 (Ind (Reg32 r)) =  ensureBufferSize x86_max_instruction_bytes >> x86_fst80_membase r 0
3399
3400
3401 class Fnstcw a where
3402     fnstcw :: a -> CodeGen e s ()
3403
3404 instance Fnstcw Addr where
3405     fnstcw (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fnstcw a
3406
3407 instance Fnstcw (Disp, Reg32) where
3408     fnstcw (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fnstcw_membase r d
3409
3410 instance Fnstcw Ind where
3411     fnstcw (Ind (Reg32 r)) =  ensureBufferSize x86_max_instruction_bytes >> x86_fnstcw_membase r 0
3412
3413
3414 class Fldcw a where
3415     fldcw :: a -> CodeGen e s ()
3416
3417 instance Fldcw Addr where
3418     fldcw (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fldcw a
3419
3420 instance Fldcw (Disp, Reg32) where
3421     fldcw (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fldcw_membase r d
3422
3423 instance Fldcw Ind where
3424     fldcw (Ind (Reg32 r)) =  ensureBufferSize x86_max_instruction_bytes >> x86_fldcw_membase r 0
3425
3426
3427 class Fild a where
3428     fild :: a -> CodeGen e s ()
3429
3430 instance Fild Addr where 
3431     fild (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fild a FInt32
3432
3433 instance Fild (Disp, Reg32) where 
3434     fild (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fild_membase r d FInt32
3435
3436 instance Fild Ind where 
3437     fild (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fild_membase r 0 FInt32
3438
3439
3440 class Fist a where
3441     fist :: a -> CodeGen e s ()
3442
3443 instance Fist (Disp, Reg32) where 
3444     fist (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fist_membase r d FInt32
3445
3446 instance Fist Ind where 
3447     fist (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fist_membase r 0 FInt32
3448
3449
3450 class Fistp a where
3451     fistp :: a -> CodeGen e s ()
3452
3453 instance Fistp Addr where
3454     fistp (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_fist_pop a FInt32
3455
3456 instance Fistp (Disp, Reg32) where 
3457     fistp (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_fist_pop_membase r d FInt32
3458
3459 instance Fistp Ind where 
3460     fistp (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_fist_pop_membase r 0 FInt32
3461
3462
3463 class Sqrtsd a b where
3464     sqrtsd :: a -> b -> CodeGen e s ()
3465
3466 instance Sqrtsd XMMReg XMMReg where
3467     sqrtsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_reg x86_sse_sd xd xs
3468
3469 instance Sqrtsd XMMReg Addr where
3470     sqrtsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_mem x86_sse_sd xd a
3471
3472 instance Sqrtsd XMMReg Ind where
3473     sqrtsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_sd xd r 0
3474
3475 instance Sqrtsd XMMReg (Disp, Reg32) where
3476     sqrtsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_sd xd r d
3477
3478
3479 class Sqrtss a b where
3480     sqrtss :: a -> b -> CodeGen e s ()
3481
3482 instance Sqrtss XMMReg XMMReg where
3483     sqrtss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_reg x86_sse_ss xd xs
3484
3485 instance Sqrtss XMMReg Addr where
3486     sqrtss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_mem x86_sse_ss xd a
3487
3488 instance Sqrtss XMMReg Ind where
3489     sqrtss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_ss xd r 0
3490
3491 instance Sqrtss XMMReg (Disp, Reg32) where
3492     sqrtss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_ss xd r d
3493
3494
3495 class Sqrtpd a b where
3496     sqrtpd :: a -> b -> CodeGen e s ()
3497
3498 instance Sqrtpd XMMReg XMMReg where
3499     sqrtpd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_reg x86_sse_pd xd xs
3500
3501 instance Sqrtpd XMMReg Addr where
3502     sqrtpd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_mem x86_sse_pd xd a
3503
3504 instance Sqrtpd XMMReg Ind where
3505     sqrtpd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_pd xd r 0
3506
3507 instance Sqrtpd XMMReg (Disp, Reg32) where
3508     sqrtpd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_pd xd r d
3509
3510
3511 class Sqrtps a b where
3512     sqrtps :: a -> b -> CodeGen e s ()
3513
3514 instance Sqrtps XMMReg XMMReg where
3515     sqrtps (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_reg x86_sse_ps xd xs
3516
3517 instance Sqrtps XMMReg Addr where
3518     sqrtps (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_mem x86_sse_ps xd a
3519
3520 instance Sqrtps XMMReg Ind where
3521     sqrtps (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_ps xd r 0
3522
3523 instance Sqrtps XMMReg (Disp, Reg32) where
3524     sqrtps (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sqrt_sse_reg_membase x86_sse_ps xd r d
3525
3526
3527 class Addsd a b where
3528     addsd :: a -> b -> CodeGen e s ()
3529
3530 instance Addsd XMMReg XMMReg where
3531     addsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_reg x86_sse_sd xd xs
3532
3533 instance Addsd XMMReg Addr where
3534     addsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_mem x86_sse_sd xd a
3535
3536 instance Addsd XMMReg Ind where
3537     addsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_sd xd r 0
3538
3539 instance Addsd XMMReg (Disp, Reg32) where
3540     addsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_sd xd r d
3541
3542
3543 class Addss a b where
3544     addss :: a -> b -> CodeGen e s ()
3545
3546 instance Addss XMMReg XMMReg where
3547     addss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_reg x86_sse_ss xd xs
3548
3549 instance Addss XMMReg Addr where
3550     addss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_mem x86_sse_ss xd a
3551
3552 instance Addss XMMReg Ind where
3553     addss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_ss xd r 0
3554
3555 instance Addss XMMReg (Disp, Reg32) where
3556     addss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_ss xd r d
3557
3558
3559 class Addpd a b where
3560     addpd :: a -> b -> CodeGen e s ()
3561
3562 instance Addpd XMMReg XMMReg where
3563     addpd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_reg x86_sse_pd xd xs
3564
3565 instance Addpd XMMReg Addr where
3566     addpd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_mem x86_sse_pd xd a
3567
3568 instance Addpd XMMReg Ind where
3569     addpd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_pd xd r 0
3570
3571 instance Addpd XMMReg (Disp, Reg32) where
3572     addpd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_pd xd r d
3573
3574
3575 class Addps a b where
3576     addps :: a -> b -> CodeGen e s ()
3577
3578 instance Addps XMMReg XMMReg where
3579     addps (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_reg x86_sse_ps xd xs
3580
3581 instance Addps XMMReg Addr where
3582     addps (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_mem x86_sse_ps xd a
3583
3584 instance Addps XMMReg Ind where
3585     addps (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_ps xd r 0
3586
3587 instance Addps XMMReg (Disp, Reg32) where
3588     addps (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_add_sse_reg_membase x86_sse_ps xd r d
3589
3590 class Subsd a b where
3591     subsd :: a -> b -> CodeGen e s ()
3592
3593 instance Subsd XMMReg XMMReg where
3594     subsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_reg x86_sse_sd xd xs
3595
3596 instance Subsd XMMReg Addr where
3597     subsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_mem x86_sse_sd xd a
3598
3599 instance Subsd XMMReg Ind where
3600     subsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_sd xd r 0
3601
3602 instance Subsd XMMReg (Disp, Reg32) where
3603     subsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_sd xd r d
3604
3605
3606 class Subss a b where
3607     subss :: a -> b -> CodeGen e s ()
3608
3609 instance Subss XMMReg XMMReg where
3610     subss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_reg x86_sse_ss xd xs
3611
3612 instance Subss XMMReg Addr where
3613     subss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_mem x86_sse_ss xd a
3614
3615 instance Subss XMMReg Ind where
3616     subss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_ss xd r 0
3617
3618 instance Subss XMMReg (Disp, Reg32) where
3619     subss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_ss xd r d
3620
3621
3622 class Subpd a b where
3623     subpd :: a -> b -> CodeGen e s ()
3624
3625 instance Subpd XMMReg XMMReg where
3626     subpd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_reg x86_sse_pd xd xs
3627
3628 instance Subpd XMMReg Addr where
3629     subpd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_mem x86_sse_pd xd a
3630
3631 instance Subpd XMMReg Ind where
3632     subpd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_pd xd r 0
3633
3634 instance Subpd XMMReg (Disp, Reg32) where
3635     subpd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_pd xd r d
3636
3637
3638 class Subps a b where
3639     subps :: a -> b -> CodeGen e s ()
3640
3641 instance Subps XMMReg XMMReg where
3642     subps (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_reg x86_sse_ps xd xs
3643
3644 instance Subps XMMReg Addr where
3645     subps (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_mem x86_sse_ps xd a
3646
3647 instance Subps XMMReg Ind where
3648     subps (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_ps xd r 0
3649
3650 instance Subps XMMReg (Disp, Reg32) where
3651     subps (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_sub_sse_reg_membase x86_sse_ps xd r d
3652
3653 class Mulsd a b where
3654     mulsd :: a -> b -> CodeGen e s ()
3655
3656 instance Mulsd XMMReg XMMReg where
3657     mulsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_reg x86_sse_sd xd xs
3658
3659 instance Mulsd XMMReg Addr where
3660     mulsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_mem x86_sse_sd xd a
3661
3662 instance Mulsd XMMReg Ind where
3663     mulsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_sd xd r 0
3664
3665 instance Mulsd XMMReg (Disp, Reg32) where
3666     mulsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_sd xd r d
3667
3668
3669 class Mulss a b where
3670     mulss :: a -> b -> CodeGen e s ()
3671
3672 instance Mulss XMMReg XMMReg where
3673     mulss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_reg x86_sse_ss xd xs
3674
3675 instance Mulss XMMReg Addr where
3676     mulss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_mem x86_sse_ss xd a
3677
3678 instance Mulss XMMReg Ind where
3679     mulss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_ss xd r 0
3680
3681 instance Mulss XMMReg (Disp, Reg32) where
3682     mulss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_ss xd r d
3683
3684
3685 class Mulpd a b where
3686     mulpd :: a -> b -> CodeGen e s ()
3687
3688 instance Mulpd XMMReg XMMReg where
3689     mulpd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_reg x86_sse_pd xd xs
3690
3691 instance Mulpd XMMReg Addr where
3692     mulpd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_mem x86_sse_pd xd a
3693
3694 instance Mulpd XMMReg Ind where
3695     mulpd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_pd xd r 0
3696
3697 instance Mulpd XMMReg (Disp, Reg32) where
3698     mulpd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_pd xd r d
3699
3700
3701 class Mulps a b where
3702     mulps :: a -> b -> CodeGen e s ()
3703
3704 instance Mulps XMMReg XMMReg where
3705     mulps (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_reg x86_sse_ps xd xs
3706
3707 instance Mulps XMMReg Addr where
3708     mulps (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_mem x86_sse_ps xd a
3709
3710 instance Mulps XMMReg Ind where
3711     mulps (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_ps xd r 0
3712
3713 instance Mulps XMMReg (Disp, Reg32) where
3714     mulps (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_mul_sse_reg_membase x86_sse_ps xd r d
3715
3716
3717 class Divsd a b where
3718     divsd :: a -> b -> CodeGen e s ()
3719
3720 instance Divsd XMMReg XMMReg where
3721     divsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_reg x86_sse_sd xd xs
3722
3723 instance Divsd XMMReg Addr where
3724     divsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_mem x86_sse_sd xd a
3725
3726 instance Divsd XMMReg Ind where
3727     divsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_sd xd r 0
3728
3729 instance Divsd XMMReg (Disp, Reg32) where
3730     divsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_sd xd r d
3731
3732
3733 class Divss a b where
3734     divss :: a -> b -> CodeGen e s ()
3735
3736 instance Divss XMMReg XMMReg where
3737     divss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_reg x86_sse_ss xd xs
3738
3739 instance Divss XMMReg Addr where
3740     divss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_mem x86_sse_ss xd a
3741
3742 instance Divss XMMReg Ind where
3743     divss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_ss xd r 0
3744
3745 instance Divss XMMReg (Disp, Reg32) where
3746     divss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_ss xd r d
3747
3748
3749 class Divpd a b where
3750     divpd :: a -> b -> CodeGen e s ()
3751
3752 instance Divpd XMMReg XMMReg where
3753     divpd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_reg x86_sse_pd xd xs
3754
3755 instance Divpd XMMReg Addr where
3756     divpd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_mem x86_sse_pd xd a
3757
3758 instance Divpd XMMReg Ind where
3759     divpd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_pd xd r 0
3760
3761 instance Divpd XMMReg (Disp, Reg32) where
3762     divpd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_pd xd r d
3763
3764
3765 class Divps a b where
3766     divps :: a -> b -> CodeGen e s ()
3767
3768 instance Divps XMMReg XMMReg where
3769     divps (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_reg x86_sse_ps xd xs
3770
3771 instance Divps XMMReg Addr where
3772     divps (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_mem x86_sse_ps xd a
3773
3774 instance Divps XMMReg Ind where
3775     divps (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_ps xd r 0
3776
3777 instance Divps XMMReg (Disp, Reg32) where
3778     divps (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_div_sse_reg_membase x86_sse_ps xd r d
3779
3780 class Minsd a b where
3781     minsd :: a -> b -> CodeGen e s ()
3782
3783 instance Minsd XMMReg XMMReg where
3784     minsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_reg x86_sse_sd xd xs
3785
3786 instance Minsd XMMReg Addr where
3787     minsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_mem x86_sse_sd xd a
3788
3789 instance Minsd XMMReg Ind where
3790     minsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_sd xd r 0
3791
3792 instance Minsd XMMReg (Disp, Reg32) where
3793     minsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_sd xd r d
3794
3795
3796 class Minss a b where
3797     minss :: a -> b -> CodeGen e s ()
3798
3799 instance Minss XMMReg XMMReg where
3800     minss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_reg x86_sse_ss xd xs
3801
3802 instance Minss XMMReg Addr where
3803     minss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_mem x86_sse_ss xd a
3804
3805 instance Minss XMMReg Ind where
3806     minss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_ss xd r 0
3807
3808 instance Minss XMMReg (Disp, Reg32) where
3809     minss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_ss xd r d
3810
3811
3812 class Minpd a b where
3813     minpd :: a -> b -> CodeGen e s ()
3814
3815 instance Minpd XMMReg XMMReg where
3816     minpd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_reg x86_sse_pd xd xs
3817
3818 instance Minpd XMMReg Addr where
3819     minpd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_mem x86_sse_pd xd a
3820
3821 instance Minpd XMMReg Ind where
3822     minpd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_pd xd r 0
3823
3824 instance Minpd XMMReg (Disp, Reg32) where
3825     minpd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_pd xd r d
3826
3827
3828 class Minps a b where
3829     minps :: a -> b -> CodeGen e s ()
3830
3831 instance Minps XMMReg XMMReg where
3832     minps (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_reg x86_sse_ps xd xs
3833
3834 instance Minps XMMReg Addr where
3835     minps (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_mem x86_sse_ps xd a
3836
3837 instance Minps XMMReg Ind where
3838     minps (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_ps xd r 0
3839
3840 instance Minps XMMReg (Disp, Reg32) where
3841     minps (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_min_sse_reg_membase x86_sse_ps xd r d
3842
3843
3844 class Maxsd a b where
3845     maxsd :: a -> b -> CodeGen e s ()
3846
3847 instance Maxsd XMMReg XMMReg where
3848     maxsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_reg x86_sse_sd xd xs
3849
3850 instance Maxsd XMMReg Addr where
3851     maxsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_mem x86_sse_sd xd a
3852
3853 instance Maxsd XMMReg Ind where
3854     maxsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_sd xd r 0
3855
3856 instance Maxsd XMMReg (Disp, Reg32) where
3857     maxsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_sd xd r d
3858
3859
3860 class Maxss a b where
3861     maxss :: a -> b -> CodeGen e s ()
3862
3863 instance Maxss XMMReg XMMReg where
3864     maxss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_reg x86_sse_ss xd xs
3865
3866 instance Maxss XMMReg Addr where
3867     maxss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_mem x86_sse_ss xd a
3868
3869 instance Maxss XMMReg Ind where
3870     maxss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_ss xd r 0
3871
3872 instance Maxss XMMReg (Disp, Reg32) where
3873     maxss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_ss xd r d
3874
3875
3876 class Maxpd a b where
3877     maxpd :: a -> b -> CodeGen e s ()
3878
3879 instance Maxpd XMMReg XMMReg where
3880     maxpd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_reg x86_sse_pd xd xs
3881
3882 instance Maxpd XMMReg Addr where
3883     maxpd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_mem x86_sse_pd xd a
3884
3885 instance Maxpd XMMReg Ind where
3886     maxpd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_pd xd r 0
3887
3888 instance Maxpd XMMReg (Disp, Reg32) where
3889     maxpd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_pd xd r d
3890
3891
3892 class Maxps a b where
3893     maxps :: a -> b -> CodeGen e s ()
3894
3895 instance Maxps XMMReg XMMReg where
3896     maxps (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_reg x86_sse_ps xd xs
3897
3898 instance Maxps XMMReg Addr where
3899     maxps (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_mem x86_sse_ps xd a
3900
3901 instance Maxps XMMReg Ind where
3902     maxps (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_ps xd r 0
3903
3904 instance Maxps XMMReg (Disp, Reg32) where
3905     maxps (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_max_sse_reg_membase x86_sse_ps xd r d
3906
3907
3908 class Movss a b where
3909     movss :: a -> b -> CodeGen e s ()
3910
3911 instance Movss XMMReg XMMReg where
3912     movss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_reg x86_sse_ss xd xs
3913
3914 instance Movss XMMReg Addr where
3915     movss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_mem x86_sse_ss xd a
3916
3917 instance Movss Addr XMMReg where
3918     movss (Addr a) (XMMReg xd) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_mem_reg x86_sse_ss a xd
3919
3920 instance Movss XMMReg Ind where
3921     movss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_membase x86_sse_ss xd r 0
3922
3923 instance Movss Ind XMMReg where
3924     movss (Ind (Reg32 r)) (XMMReg xd) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_membase_reg x86_sse_ss r 0 xd
3925
3926 instance Movss XMMReg (Disp, Reg32) where
3927     movss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_membase x86_sse_ss xd r d
3928
3929 instance Movss (Disp, Reg32) XMMReg where
3930     movss (Disp d, Reg32 r) (XMMReg xd) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_membase_reg x86_sse_ss r d xd
3931
3932
3933 class Movsd a b where
3934     movsd :: a -> b -> CodeGen e s ()
3935
3936 instance Movsd XMMReg XMMReg where
3937     movsd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_reg x86_sse_sd xd xs
3938
3939 instance Movsd XMMReg Addr where
3940     movsd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_mem x86_sse_sd xd a
3941
3942 instance Movsd Addr XMMReg where
3943     movsd (Addr a) (XMMReg xd) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_mem_reg x86_sse_sd a xd
3944
3945 instance Movsd XMMReg Ind where
3946     movsd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_membase x86_sse_sd xd r 0
3947
3948 instance Movsd Ind XMMReg where
3949     movsd (Ind (Reg32 r)) (XMMReg xd) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_membase_reg x86_sse_sd r 0 xd
3950
3951 instance Movsd XMMReg (Disp, Reg32) where
3952     movsd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_reg_membase x86_sse_sd xd r d
3953
3954 instance Movsd (Disp, Reg32) XMMReg where
3955     movsd (Disp d, Reg32 r) (XMMReg xd) = ensureBufferSize x86_max_instruction_bytes >> x86_mov_sse_membase_reg x86_sse_sd r d xd
3956
3957
3958 class Movups a b where
3959     movups :: a -> b -> CodeGen e s ()
3960
3961 instance Movups XMMReg XMMReg where
3962     movups (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movups_to_reg xd (xmmLocLowLevel xs)
3963
3964 instance Movups XMMReg Addr where
3965     movups (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movups_to_reg xd (xmmLocLowLevel xs)
3966
3967 instance Movups Addr XMMReg where
3968     movups xd (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_movups_from_reg xs (xmmLocLowLevel xd)
3969
3970 instance Movups XMMReg Ind where
3971     movups (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movups_to_reg xd (xmmLocLowLevel xs)
3972
3973 instance Movups Ind XMMReg where
3974     movups xd (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_movups_from_reg xs (xmmLocLowLevel xd)
3975
3976 instance Movups XMMReg (Disp, Reg32) where
3977     movups (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movups_to_reg xd (xmmLocLowLevel xs)
3978
3979 instance Movups (Disp, Reg32) XMMReg where
3980     movups xd (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_movups_from_reg xs (xmmLocLowLevel xd)
3981
3982
3983 class Movlps a b where
3984     movlps :: a -> b -> CodeGen e s ()
3985
3986 instance Movlps XMMReg XMMReg where
3987     movlps (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movlps_to_reg xd (xmmLocLowLevel xs)
3988
3989 instance Movlps XMMReg Addr where
3990     movlps (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movlps_to_reg xd (xmmLocLowLevel xs)
3991
3992 instance Movlps Addr XMMReg where
3993     movlps xd (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_movlps_from_reg xs (xmmLocLowLevel xd)
3994
3995 instance Movlps XMMReg Ind where
3996     movlps (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movlps_to_reg xd (xmmLocLowLevel xs)
3997
3998 instance Movlps Ind XMMReg where
3999     movlps xd (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_movlps_from_reg xs (xmmLocLowLevel xd)
4000
4001 instance Movlps XMMReg (Disp, Reg32) where
4002     movlps (XMMReg xd) xs = ensureBufferSize x86_max_instruction_bytes >> x86_movlps_to_reg xd (xmmLocLowLevel xs)
4003
4004 instance Movlps (Disp, Reg32) XMMReg where
4005     movlps xd (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_movlps_from_reg xs (xmmLocLowLevel xd)
4006
4007
4008 class Comisd a b where
4009     comisd :: a -> b -> CodeGen e s ()
4010
4011 instance Comisd XMMReg XMMReg where
4012     comisd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_comisd_reg_reg xd xs
4013
4014 instance Comisd XMMReg Addr where
4015     comisd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_comisd_reg_mem xd a
4016
4017 instance Comisd XMMReg Ind where
4018     comisd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_comisd_reg_membase xd r 0
4019
4020 instance Comisd XMMReg (Disp, Reg32) where
4021     comisd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_comisd_reg_membase xd r d
4022
4023
4024 class Comiss a b where
4025     comiss :: a -> b -> CodeGen e s ()
4026
4027 instance Comiss XMMReg XMMReg where
4028     comiss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_comiss_reg_reg xd xs
4029
4030 instance Comiss XMMReg Addr where
4031     comiss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_comiss_reg_mem xd a
4032
4033 instance Comiss XMMReg Ind where
4034     comiss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_comiss_reg_membase xd r 0
4035
4036 instance Comiss XMMReg (Disp, Reg32) where
4037     comiss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_comiss_reg_membase xd r d
4038
4039
4040 class Ucomisd a b where
4041     ucomisd :: a -> b -> CodeGen e s ()
4042
4043 instance Ucomisd XMMReg XMMReg where
4044     ucomisd (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomisd_reg_reg xd xs
4045
4046 instance Ucomisd XMMReg Addr where
4047     ucomisd (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomisd_reg_mem xd a
4048
4049 instance Ucomisd XMMReg Ind where
4050     ucomisd (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomisd_reg_membase xd r 0
4051
4052 instance Ucomisd XMMReg (Disp, Reg32) where
4053     ucomisd (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomisd_reg_membase xd r d
4054
4055
4056 class Ucomiss a b where
4057     ucomiss :: a -> b -> CodeGen e s ()
4058
4059 instance Ucomiss XMMReg XMMReg where
4060     ucomiss (XMMReg xd) (XMMReg xs) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomiss_reg_reg xd xs
4061
4062 instance Ucomiss XMMReg Addr where
4063     ucomiss (XMMReg xd) (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomiss_reg_mem xd a
4064
4065 instance Ucomiss XMMReg Ind where
4066     ucomiss (XMMReg xd) (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomiss_reg_membase xd r 0
4067
4068 instance Ucomiss XMMReg (Disp, Reg32) where
4069     ucomiss (XMMReg xd) (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_ucomiss_reg_membase xd r d
4070
4071
4072 class XMMLocation b => XMMLoc a b | a -> b where
4073     xmmLocLowLevel :: a -> b
4074
4075 instance XMMLoc XMMReg XMMReg where
4076     xmmLocLowLevel = id
4077
4078 instance XMMLoc Addr Mem where
4079     xmmLocLowLevel (Addr a) = Mem a
4080
4081 instance XMMLoc Ind MemBase where
4082     xmmLocLowLevel (Ind (Reg32 r)) = MemBase r 0
4083
4084 instance XMMLoc (Disp, Reg32) MemBase where
4085     xmmLocLowLevel (Disp d, Reg32 r) = MemBase r d
4086
4087
4088 haddps :: XMMLoc xmm a => XMMReg -> xmm -> CodeGen e s ()
4089 haddps (XMMReg dreg) reg =
4090    x86_haddps dreg (xmmLocLowLevel reg)
4091
4092 haddpd :: XMMLoc xmm a => XMMReg -> xmm -> CodeGen e s ()
4093 haddpd (XMMReg dreg) reg =
4094    x86_haddpd dreg (xmmLocLowLevel reg)
4095
4096
4097 shufps :: XMMLoc xmm a => XMMReg -> xmm -> Word8 -> CodeGen e s ()
4098 shufps (XMMReg dreg) reg src =
4099    x86_shufps dreg (xmmLocLowLevel reg) src
4100
4101 shufpd :: XMMLoc xmm a => XMMReg -> xmm -> Word8 -> CodeGen e s ()
4102 shufpd (XMMReg dreg) reg src =
4103    x86_shufpd dreg (xmmLocLowLevel reg) src
4104
4105
4106 cvtdq2ps :: XMMLoc xmm a => XMMReg -> xmm -> CodeGen e s ()
4107 cvtdq2ps (XMMReg dreg) reg =
4108    x86_cvtdq2ps dreg (xmmLocLowLevel reg)
4109
4110 cvttps2dq :: XMMLoc xmm a => XMMReg -> xmm -> CodeGen e s ()
4111 cvttps2dq (XMMReg dreg) reg =
4112    x86_cvttps2dq dreg (xmmLocLowLevel reg)
4113
4114
4115 class Prefetchnta a where
4116     prefetchnta :: a -> CodeGen e s ()
4117
4118 instance Prefetchnta Addr where
4119     prefetchnta (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetchnta_mem a
4120
4121 instance Prefetchnta (Disp, Reg32) where
4122     prefetchnta (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetchnta_membase r d
4123
4124 instance Prefetchnta Ind where
4125     prefetchnta (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetchnta_regp r
4126
4127 class Prefetch0 a where
4128     prefetch0 :: a -> CodeGen e s ()
4129
4130 instance Prefetch0 Addr where
4131     prefetch0 (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch0_mem a
4132
4133 instance Prefetch0 (Disp, Reg32) where
4134     prefetch0 (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch0_membase r d
4135
4136 instance Prefetch0 Ind where
4137     prefetch0 (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch0_regp r
4138
4139 class Prefetch1 a where
4140     prefetch1 :: a -> CodeGen e s ()
4141
4142 instance Prefetch1 Addr where
4143     prefetch1 (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch1_mem a
4144
4145 instance Prefetch1 (Disp, Reg32) where
4146     prefetch1 (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch1_membase r d
4147
4148 instance Prefetch1 Ind where
4149     prefetch1 (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch1_regp r
4150
4151 class Prefetch2 a where
4152     prefetch2 :: a -> CodeGen e s ()
4153
4154 instance Prefetch2 Addr where
4155     prefetch2 (Addr a) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch2_mem a
4156
4157 instance Prefetch2 (Disp, Reg32) where
4158     prefetch2 (Disp d, Reg32 r) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch2_membase r d
4159
4160 instance Prefetch2 Ind where
4161     prefetch2 (Ind (Reg32 r)) = ensureBufferSize x86_max_instruction_bytes >> x86_prefetch2_regp r
4162
4163
4164 ptrToWord32 :: Ptr a -> Word32
4165 ptrToWord32 = fromIntegral . ptrToIntPtr
4166
4167 ptrToInt :: Ptr a -> Int
4168 ptrToInt = fromIntegral . ptrToIntPtr