Fixed ICMD_FCMPx
[cacao.git] / i386 / ngen.c
1 /* i386/ngen.c *****************************************************************
2
3         Copyright (c) 1997 A. Krall, R. Grafl, M. Gschwind, M. Probst
4
5         See file COPYRIGHT for information on usage and disclaimer of warranties
6
7         Contains the codegenerator for an i386 processor.
8         This module generates i386 machine code for a sequence of
9         pseudo commands (ICMDs).
10
11         Authors: Andreas  Krall      EMAIL: cacao@complang.tuwien.ac.at
12                  Reinhard Grafl      EMAIL: cacao@complang.tuwien.ac.at
13
14         Last Change: $Id: ngen.c 258 2003-03-23 14:48:28Z twisti $
15
16 *******************************************************************************/
17
18 #include "jitdef.h"   /* phil */
19
20 /* additional functions and macros to generate code ***************************/
21
22 /* #define BlockPtrOfPC(pc)        block+block_index[pc] */
23 #define BlockPtrOfPC(pc)  ((basicblock *) iptr->target)
24
25
26 #ifdef STATISTICS
27 #define COUNT_SPILLS count_spills++
28 #else
29 #define COUNT_SPILLS
30 #endif
31
32
33 #define CALCOFFSETBYTES(val) \
34     do { \
35         if ((s4) (val) < -128 || (s4) (val) > 127) offset += 4; \
36         else if ((s4) (val) != 0) offset += 1; \
37     } while (0)
38
39
40 /* gen_nullptr_check(objreg) */
41
42 #ifdef SOFTNULLPTRCHECK
43 #define gen_nullptr_check(objreg) \
44         if (checknull) { \
45         i386_alu_imm_reg(I386_CMP, 0, (objreg)); \
46         i386_jcc(I386_CC_E, 0); \
47             mcode_addxnullrefs(mcodeptr); \
48         }
49 #else
50 #define gen_nullptr_check(objreg)
51 #endif
52
53
54 /* MCODECHECK(icnt) */
55
56 #define MCODECHECK(icnt) \
57         if((mcodeptr+(icnt))>mcodeend)mcodeptr=mcode_increase((u1*)mcodeptr)
58
59 /* M_INTMOVE:
60      generates an integer-move from register a to b.
61      if a and b are the same int-register, no code will be generated.
62 */ 
63
64 #define M_INTMOVE(reg,dreg) if ((reg) != (dreg)) { i386_mov_reg_reg((reg),(dreg)); }
65
66
67 /* M_FLTMOVE:
68     generates a floating-point-move from register a to b.
69     if a and b are the same float-register, no code will be generated
70 */ 
71
72 #define M_FLTMOVE(a,b) if(a!=b){M_FMOV(a,b);}
73
74
75 /* var_to_reg_xxx:
76     this function generates code to fetch data from a pseudo-register
77     into a real register. 
78     If the pseudo-register has actually been assigned to a real 
79     register, no code will be emitted, since following operations
80     can use this register directly.
81     
82     v: pseudoregister to be fetched from
83     tempregnum: temporary register to be used if v is actually spilled to ram
84
85     return: the register number, where the operand can be found after 
86             fetching (this wil be either tempregnum or the register
87             number allready given to v)
88 */
89
90 #define var_to_reg_int(regnr,v,tempnr) \
91     do { \
92         if ((v)->flags & INMEMORY) { \
93             COUNT_SPILLS; \
94             i386_mov_membase_reg(REG_SP, (v)->regoff * 8, tempnr); \
95             regnr = tempnr; \
96         } else { \
97             regnr = (v)->regoff; \
98         } \
99     } while (0)
100
101
102
103 #define var_to_reg_flt(regnr,v,tempnr) \
104     do { \
105         if ((v)->flags & INMEMORY) { \
106             COUNT_SPILLS; \
107             i386_fstps_membase(REG_SP, (v)->regoff * 8); \
108             regnr = tempnr; \
109         } else { \
110             panic("floats have to be in memory"); \
111         } \
112     } while (0)
113
114
115 /* reg_of_var:
116     This function determines a register, to which the result of an operation
117     should go, when it is ultimatively intended to store the result in
118     pseudoregister v.
119     If v is assigned to an actual register, this register will be returned.
120     Otherwise (when v is spilled) this function returns tempregnum.
121     If not already done, regoff and flags are set in the stack location.
122 */        
123
124 static int reg_of_var(stackptr v, int tempregnum)
125 {
126         varinfo      *var;
127
128         switch (v->varkind) {
129                 case TEMPVAR:
130                         if (!(v->flags & INMEMORY))
131                                 return(v->regoff);
132                         break;
133                 case STACKVAR:
134                         var = &(interfaces[v->varnum][v->type]);
135                         v->regoff = var->regoff;
136                         if (!(var->flags & INMEMORY))
137                                 return(var->regoff);
138                         break;
139                 case LOCALVAR:
140                         var = &(locals[v->varnum][v->type]);
141                         v->regoff = var->regoff;
142                         if (!(var->flags & INMEMORY))
143                                 return(var->regoff);
144                         break;
145                 case ARGVAR:
146                         v->regoff = v->varnum;
147                         if (IS_FLT_DBL_TYPE(v->type)) {
148                                 if (v->varnum < fltreg_argnum) {
149                                         v->regoff = argfltregs[v->varnum];
150                                         return(argfltregs[v->varnum]);
151                                         }
152                                 }
153                         else
154                                 if (v->varnum < intreg_argnum) {
155                                         v->regoff = argintregs[v->varnum];
156                                         return(argintregs[v->varnum]);
157                                         }
158                         v->regoff -= intreg_argnum;
159                         break;
160                 }
161         v->flags |= INMEMORY;
162         return tempregnum;
163 }
164
165
166 /* store_reg_to_var_xxx:
167     This function generates the code to store the result of an operation
168     back into a spilled pseudo-variable.
169     If the pseudo-variable has not been spilled in the first place, this 
170     function will generate nothing.
171     
172     v ............ Pseudovariable
173     tempregnum ... Number of the temporary registers as returned by
174                    reg_of_var.
175 */      
176
177 #define store_reg_to_var_int(sptr, tempregnum) \
178     do { \
179         if ((sptr)->flags & INMEMORY) { \
180             COUNT_SPILLS; \
181             i386_mov_reg_membase(tempregnum, REG_SP, (sptr)->regoff * 8); \
182         } \
183     } while (0)
184
185
186 #define store_reg_to_var_flt(sptr, tempregnum) \
187     do { \
188         if ((sptr)->type == TYPE_FLT) { \
189             if ((sptr)->flags & INMEMORY) { \
190                 if ((sptr)->varkind == ARGVAR) { \
191                     COUNT_SPILLS; \
192                     /* a little fpu optimization */ \
193                     /*if (iptr[1].opc != ICMD_FSTORE) {*/ \
194                         i386_fstps_membase(REG_SP, (sptr)->regoff * 8); \
195                     /*}*/ \
196                 } \
197             } else { \
198                 panic("floats have to be in memory"); \
199             } \
200         } else { \
201             if ((sptr)->flags & INMEMORY) { \
202                 if ((sptr)->varkind == ARGVAR) { \
203                     COUNT_SPILLS; \
204                     /* a little fpu optimization */ \
205                     /*if (iptr[1].opc != ICMD_FSTORE) {*/ \
206                         i386_fstpl_membase(REG_SP, (sptr)->regoff * 8); \
207                     /*}*/ \
208                 } \
209             } else { \
210                 panic("doubles have to be in memory"); \
211             } \
212         } \
213     } while (0)
214
215
216 /* NullPointerException handlers and exception handling initialisation        */
217
218 typedef struct sigctx_struct {
219
220         long          sc_onstack;           /* sigstack state to restore          */
221         long          sc_mask;              /* signal mask to restore             */
222         long          sc_pc;                /* pc at time of signal               */
223         long          sc_ps;                /* psl to retore                      */
224         long          sc_regs[32];          /* processor regs 0 to 31             */
225         long          sc_ownedfp;           /* fp has been used                   */
226         long          sc_fpregs[32];        /* fp regs 0 to 31                    */
227         unsigned long sc_fpcr;              /* floating point control register    */
228         unsigned long sc_fp_control;        /* software fpcr                      */
229                                             /* rest is unused                     */
230         unsigned long sc_reserved1, sc_reserved2;
231         unsigned long sc_ssize;
232         char          *sc_sbase;
233         unsigned long sc_traparg_a0;
234         unsigned long sc_traparg_a1;
235         unsigned long sc_traparg_a2;
236         unsigned long sc_fp_trap_pc;
237         unsigned long sc_fp_trigger_sum;
238         unsigned long sc_fp_trigger_inst;
239         unsigned long sc_retcode[2];
240 } sigctx_struct;
241
242
243 /* NullPointerException signal handler for hardware null pointer check */
244
245 void catch_NullPointerException(int sig, int code, sigctx_struct *sigctx)
246 {
247         sigset_t nsig;
248         int      instr;
249         long     faultaddr;
250
251         /* Reset signal handler - necessary for SysV, does no harm for BSD */
252
253         instr = *((int*)(sigctx->sc_pc));
254         faultaddr = sigctx->sc_regs[(instr >> 16) & 0x1f];
255
256         if (faultaddr == 0) {
257                 signal(sig, (void*) catch_NullPointerException); /* reinstall handler */
258                 sigemptyset(&nsig);
259                 sigaddset(&nsig, sig);
260                 sigprocmask(SIG_UNBLOCK, &nsig, NULL);           /* unblock signal    */
261                 sigctx->sc_regs[REG_ITMP1_XPTR] =
262                                             (long) proto_java_lang_NullPointerException;
263                 sigctx->sc_regs[REG_ITMP2_XPC] = sigctx->sc_pc;
264                 sigctx->sc_pc = (long) asm_handle_nat_exception;
265                 return;
266                 }
267         else {
268                 faultaddr += (long) ((instr << 16) >> 16);
269                 fprintf(stderr, "faulting address: 0x%16lx\n", faultaddr);
270                 panic("Stack overflow");
271                 }
272 }
273
274 void init_exceptions(void)
275 {
276         /* install signal handlers we need to convert to exceptions */
277
278         if (!checknull) {
279
280 #if defined(SIGSEGV)
281                 signal(SIGSEGV, (void*) catch_NullPointerException);
282 #endif
283
284 #if defined(SIGBUS)
285                 signal(SIGBUS, (void*) catch_NullPointerException);
286 #endif
287                 }
288 }
289
290
291 /* function gen_mcode **********************************************************
292
293         generates machine code
294
295 *******************************************************************************/
296
297 #define         MethodPointer   -8
298 #define         FrameSize       -12
299 #define     IsSync          -16
300 #define     IsLeaf          -20
301 #define     IntSave         -24
302 #define     FltSave         -28
303 #define     ExTableSize     -32
304 #define     ExTableStart    -32
305
306 #if POINTERSIZE == 8
307 #    define     ExEntrySize     -32
308 #    define     ExStartPC       -8
309 #    define     ExEndPC         -16
310 #    define     ExHandlerPC     -24
311 #    define     ExCatchType     -32
312 #else
313 #    define     ExEntrySize     -16
314 #    define     ExStartPC       -4
315 #    define     ExEndPC         -8
316 #    define     ExHandlerPC     -12
317 #    define     ExCatchType     -16
318 #endif
319
320 static void gen_mcode()
321 {
322         int  len, s1, s2, s3, d, bbs;
323         s4   a;
324         s4          *mcodeptr;
325         stackptr    src;
326         varinfo     *var;
327         varinfo     *dst;
328         basicblock  *bptr;
329         instruction *iptr;
330
331         xtable *ex;
332
333         {
334         int p, pa, t, l, r;
335
336         /* TWISTI */
337 /*      savedregs_num = (isleafmethod) ? 0 : 1;           /* space to save the RA */
338
339         /* space to save used callee saved registers */
340
341         savedregs_num += (savintregcnt - maxsavintreguse);
342         savedregs_num += (savfltregcnt - maxsavfltreguse);
343
344         parentargs_base = maxmemuse + savedregs_num;
345
346 #ifdef USE_THREADS                 /* space to save argument of monitor_enter */
347
348         if (checksync && (method->flags & ACC_SYNCHRONIZED))
349                 parentargs_base++;
350
351 #endif
352
353         /* create method header */
354
355         (void) dseg_addaddress(method);                         /* MethodPointer  */
356         (void) dseg_adds4(parentargs_base * 8);                 /* FrameSize      */
357
358 #ifdef USE_THREADS
359
360         /* IsSync contains the offset relative to the stack pointer for the
361            argument of monitor_exit used in the exception handler. Since the
362            offset could be zero and give a wrong meaning of the flag it is
363            offset by one.
364         */
365
366         if (checksync && (method->flags & ACC_SYNCHRONIZED))
367                 (void) dseg_adds4((maxmemuse + 1) * 8);             /* IsSync         */
368         else
369
370 #endif
371
372         (void) dseg_adds4(0);                                   /* IsSync         */
373                                                
374         (void) dseg_adds4(isleafmethod);                        /* IsLeaf         */
375         (void) dseg_adds4(savintregcnt - maxsavintreguse);      /* IntSave        */
376         (void) dseg_adds4(savfltregcnt - maxsavfltreguse);      /* FltSave        */
377         (void) dseg_adds4(exceptiontablelength);                /* ExTableSize    */
378
379         /* create exception table */
380
381         for (ex = extable; ex != NULL; ex = ex->down) {
382
383 #ifdef LOOP_DEBUG       
384                 if (ex->start != NULL)
385                         printf("adding start - %d - ", ex->start->debug_nr);
386                 else {
387                         printf("PANIC - start is NULL");
388                         exit(-1);
389                 }
390 #endif
391
392                 dseg_addtarget(ex->start);
393
394 #ifdef LOOP_DEBUG                       
395                 if (ex->end != NULL)
396                         printf("adding end - %d - ", ex->end->debug_nr);
397                 else {
398                         printf("PANIC - end is NULL");
399                         exit(-1);
400                 }
401 #endif
402
403                 dseg_addtarget(ex->end);
404
405 #ifdef LOOP_DEBUG               
406                 if (ex->handler != NULL)
407                         printf("adding handler - %d\n", ex->handler->debug_nr);
408                 else {
409                         printf("PANIC - handler is NULL");
410                         exit(-1);
411                 }
412 #endif
413
414                 dseg_addtarget(ex->handler);
415            
416                 (void) dseg_addaddress(ex->catchtype);
417                 }
418         
419         /* initialize mcode variables */
420         
421         mcodeptr = (s4*) mcodebase;
422         mcodeend = (s4*) (mcodebase + mcodesize);
423         MCODECHECK(128 + mparamcount);
424
425         /* create stack frame (if necessary) */
426
427         if (parentargs_base) {
428                 i386_alu_imm_reg(I386_SUB, parentargs_base * 8, REG_SP);
429         }
430
431         /* save return address and used callee saved registers */
432
433         p = parentargs_base;
434         if (!isleafmethod) {
435                 /* p--; M_AST (REG_RA, REG_SP, 8*p); -- do we really need this on i386 */
436         }
437         for (r = savintregcnt - 1; r >= maxsavintreguse; r--) {
438                 p--; i386_mov_reg_membase(savintregs[r], REG_SP, p * 8);
439         }
440         for (r = savfltregcnt - 1; r >= maxsavfltreguse; r--) {
441                 p--; M_DST (savfltregs[r], REG_SP, 8 * p);
442         }
443
444         /* save monitorenter argument */
445
446 #ifdef USE_THREADS
447         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
448                 if (method->flags & ACC_STATIC) {
449                         p = dseg_addaddress (class);
450                         M_ALD(REG_ITMP1, REG_PV, p);
451                         M_AST(REG_ITMP1, REG_SP, 8 * maxmemuse);
452
453                 } else {
454                         i386_mov_membase_reg(REG_SP, parentargs_base * 8 + 4, REG_ITMP1);
455                         i386_mov_reg_membase(REG_ITMP1, REG_SP, 8 * maxmemuse);
456                 }
457         }                       
458 #endif
459
460         /* copy argument registers to stack and call trace function with pointer
461            to arguments on stack. ToDo: save floating point registers !!!!!!!!!
462         */
463
464         if (runverbose && isleafmethod) {
465                 M_LDA (REG_SP, REG_SP, -(14*8));
466                 M_AST(REG_RA, REG_SP, 1*8);
467
468                 M_LST(argintregs[0], REG_SP,  2*8);
469                 M_LST(argintregs[1], REG_SP,  3*8);
470                 M_LST(argintregs[2], REG_SP,  4*8);
471                 M_LST(argintregs[3], REG_SP,  5*8);
472                 M_LST(argintregs[4], REG_SP,  6*8);
473                 M_LST(argintregs[5], REG_SP,  7*8);
474
475                 M_DST(argfltregs[0], REG_SP,  8*8);
476                 M_DST(argfltregs[1], REG_SP,  9*8);
477                 M_DST(argfltregs[2], REG_SP, 10*8);
478                 M_DST(argfltregs[3], REG_SP, 11*8);
479                 M_DST(argfltregs[4], REG_SP, 12*8);
480                 M_DST(argfltregs[5], REG_SP, 13*8);
481
482                 p = dseg_addaddress (method);
483                 M_ALD(REG_ITMP1, REG_PV, p);
484                 M_AST(REG_ITMP1, REG_SP, 0);
485 /*              p = dseg_addaddress ((void*) (builtin_trace_args)); */
486                 M_ALD(REG_PV, REG_PV, p);
487                 M_JSR(REG_RA, REG_PV);
488                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
489                 M_ALD(REG_RA, REG_SP, 1*8);
490
491                 M_LLD(argintregs[0], REG_SP,  2*8);
492                 M_LLD(argintregs[1], REG_SP,  3*8);
493                 M_LLD(argintregs[2], REG_SP,  4*8);
494                 M_LLD(argintregs[3], REG_SP,  5*8);
495                 M_LLD(argintregs[4], REG_SP,  6*8);
496                 M_LLD(argintregs[5], REG_SP,  7*8);
497
498                 M_DLD(argfltregs[0], REG_SP,  8*8);
499                 M_DLD(argfltregs[1], REG_SP,  9*8);
500                 M_DLD(argfltregs[2], REG_SP, 10*8);
501                 M_DLD(argfltregs[3], REG_SP, 11*8);
502                 M_DLD(argfltregs[4], REG_SP, 12*8);
503                 M_DLD(argfltregs[5], REG_SP, 13*8);
504
505                 M_LDA (REG_SP, REG_SP, 14*8);
506                 }
507
508         /* take arguments out of register or stack frame */
509
510         for (p = 0, l = 0; p < mparamcount; p++) {
511                 t = mparamtypes[p];
512                 var = &(locals[l][t]);
513                 l++;
514                 if (IS_2_WORD_TYPE(t))    /* increment local counter for 2 word types */
515                         l++;
516                 if (var->type < 0)
517                         continue;
518                 r = var->regoff; 
519                 if (IS_INT_LNG_TYPE(t)) {                    /* integer args          */
520                         if (p < intreg_argnum) {                 /* register arguments    */
521                                 if (!(var->flags & INMEMORY)) {      /* reg arg -> register   */
522                                         M_INTMOVE (argintregs[p], r);
523                                 } else {                             /* reg arg -> spilled    */
524                                         M_LST (argintregs[p], REG_SP, 8 * r);
525                                 }
526                         } else {                                 /* stack arguments       */
527                                 pa = p - intreg_argnum;
528                                 if (!(var->flags & INMEMORY)) {      /* stack arg -> register */ 
529                                         i386_mov_membase_reg(REG_SP, (parentargs_base + pa) * 8 + 4, r);            /* + 4 for return address */
530                                 } else {                             /* stack arg -> spilled  */
531                                         if (IS_2_WORD_TYPE(t)) {
532                                                 i386_mov_membase_reg(REG_SP, (parentargs_base + pa) * 8 + 4, REG_ITMP1);    /* + 4 for return address */
533                                                 i386_mov_membase_reg(REG_SP, (parentargs_base + pa) * 8 + 4 + 4, REG_ITMP2);    /* + 4 for return address */
534                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, r * 8);
535                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, r * 8 + 4);
536
537                                         } else {
538                                                 i386_mov_membase_reg(REG_SP, (parentargs_base + pa) * 8 + 4, REG_ITMP1);    /* + 4 for return address */
539                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, r * 8);
540                                         }
541                                 }
542                         }
543                 
544                 } else {                                     /* floating args         */   
545                         if (p < fltreg_argnum) {                 /* register arguments    */
546                                 if (!(var->flags & INMEMORY)) {      /* reg arg -> register   */
547                                         panic("There are no float argument registers!");
548
549                                 } else {                                         /* reg arg -> spilled    */
550                                         panic("There are no float argument registers!");
551                                 }
552
553                         } else {                                 /* stack arguments       */
554                                 pa = p - fltreg_argnum;
555                                 if (!(var->flags & INMEMORY)) {      /* stack-arg -> register */
556                                         panic("floats have to be in memory!");
557
558                                 } else {                              /* stack-arg -> spilled  */
559 /*                                      i386_mov_membase_reg(REG_SP, (parentargs_base + pa) * 8 + 4, REG_ITMP1); */
560 /*                                      i386_mov_reg_membase(REG_ITMP1, REG_SP, r * 8); */
561                                         if (t == TYPE_FLT) {
562                                                 i386_flds_membase(REG_SP, (parentargs_base + pa) * 8 + 4);
563                                                 i386_fstps_membase(REG_SP, r * 8);
564
565                                         } else {
566                                                 i386_fldl_membase(REG_SP, (parentargs_base + pa) * 8 + 4);
567                                                 i386_fstpl_membase(REG_SP, r * 8);
568                                         }
569                                 }
570                         }
571                 }
572         }  /* end for */
573
574         /* call trace function */
575
576         if (runverbose && !isleafmethod) {
577                 M_LDA (REG_SP, REG_SP, -8);
578                 p = dseg_addaddress (method);
579                 M_ALD(REG_ITMP1, REG_PV, p);
580                 M_AST(REG_ITMP1, REG_SP, 0);
581 /*              p = dseg_addaddress ((void*) (builtin_trace_args)); */
582                 M_ALD(REG_PV, REG_PV, p);
583                 M_JSR(REG_RA, REG_PV);
584                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
585                 M_LDA(REG_SP, REG_SP, 8);
586                 }
587
588         /* call monitorenter function */
589
590 #ifdef USE_THREADS
591         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
592                 i386_mov_membase_reg(REG_SP, 8 * maxmemuse, REG_ITMP1);
593                 i386_alu_imm_reg(I386_SUB, 4, REG_SP);
594                 i386_mov_reg_membase(REG_ITMP1, REG_SP, 0);
595                 i386_mov_imm_reg(builtin_monitorenter, REG_ITMP1);
596                 i386_call_reg(REG_ITMP1);
597                 i386_alu_imm_reg(I386_ADD, 4, REG_SP);
598         }                       
599 #endif
600         }
601
602         /* end of header generation */
603
604         /* walk through all basic blocks */
605         for (/* bbs = block_count, */ bptr = block; /* --bbs >= 0 */ bptr != NULL; bptr = bptr->next) {
606
607                 bptr -> mpc = (int)((u1*) mcodeptr - mcodebase);
608
609                 if (bptr->flags >= BBREACHED) {
610
611                 /* branch resolving */
612
613                 {
614                 branchref *brefs;
615                 for (brefs = bptr->branchrefs; brefs != NULL; brefs = brefs->next) {
616                         gen_resolvebranch((u1*) mcodebase + brefs->branchpos, 
617                                           brefs->branchpos, bptr->mpc);
618                         }
619                 }
620
621                 /* copy interface registers to their destination */
622
623                 src = bptr->instack;
624                 len = bptr->indepth;
625                 MCODECHECK(64+len);
626                 while (src != NULL) {
627                         len--;
628                         if ((len == 0) && (bptr->type != BBTYPE_STD)) {
629                                 d = reg_of_var(src, REG_ITMP1);
630                                 M_INTMOVE(REG_ITMP1, d);
631                                 store_reg_to_var_int(src, d);
632
633                         } else {
634                                 d = reg_of_var(src, REG_ITMP1);
635                                 if ((src->varkind != STACKVAR)) {
636                                         s2 = src->type;
637                                         if (IS_FLT_DBL_TYPE(s2)) {
638                                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
639                                                         s1 = interfaces[len][s2].regoff;
640                                                         M_FLTMOVE(s1, d);
641
642                                                 } else {
643                                                         M_DLD(d, REG_SP, 8 * interfaces[len][s2].regoff);
644                                                 }
645                                                 store_reg_to_var_flt(src, d);
646
647                                         } else {
648                                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
649                                                         s1 = interfaces[len][s2].regoff;
650                                                         M_INTMOVE(s1, d);
651
652                                                 } else {
653                                                         i386_mov_membase_reg(REG_SP, interfaces[len][s2].regoff * 8, d);
654                                                 }
655                                                 store_reg_to_var_int(src, d);
656                                         }
657                                 }
658                         }
659                         src = src->prev;
660                 }
661
662                 /* walk through all instructions */
663                 
664                 src = bptr->instack;
665                 len = bptr->icount;
666                 for (iptr = bptr->iinstr;
667                     len > 0;
668                     src = iptr->dst, len--, iptr++) {
669
670         MCODECHECK(64);           /* an instruction usually needs < 64 words      */
671         switch (iptr->opc) {
672
673                 case ICMD_NOP:        /* ...  ==> ...                                 */
674                         break;
675
676                 case ICMD_NULLCHECKPOP: /* ..., objectref  ==> ...                    */
677                         if (src->flags & INMEMORY) {
678                                 i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
679
680                         } else {
681                                 /* TODO: optimize: test reg,reg */
682                                 i386_alu_imm_reg(I386_CMP, 0, src->regoff);
683                         }
684                         i386_jcc(I386_CC_E, 0);
685                         mcode_addxnullrefs(mcodeptr);
686                         break;
687
688                 /* constant operations ************************************************/
689
690                 case ICMD_ICONST:     /* ...  ==> ..., constant                       */
691                                       /* op1 = 0, val.i = constant                    */
692
693                         d = reg_of_var(iptr->dst, REG_ITMP1);
694                         if (iptr->dst->flags & INMEMORY) {
695                                 i386_mov_imm_membase(iptr->val.i, REG_SP, iptr->dst->regoff * 8);
696                                 i386_mov_imm_membase(0, REG_SP, iptr->dst->regoff * 8 + 4);
697
698                         } else {
699                                 i386_mov_imm_reg(iptr->val.i, d);
700                         }
701                         break;
702
703                 case ICMD_LCONST:     /* ...  ==> ..., constant                       */
704                                       /* op1 = 0, val.l = constant                    */
705
706                         d = reg_of_var(iptr->dst, REG_ITMP1);
707                         if (iptr->dst->flags & INMEMORY) {
708                                 i386_mov_imm_membase(iptr->val.l, REG_SP, iptr->dst->regoff * 8);
709                                 i386_mov_imm_membase(iptr->val.l >> 32, REG_SP, iptr->dst->regoff * 8 + 4);
710                                 
711                         } else {
712                                 panic("longs have to be in memory");
713                         }
714                         break;
715
716                 case ICMD_FCONST:     /* ...  ==> ..., constant                       */
717                                       /* op1 = 0, val.f = constant                    */
718
719                         d = reg_of_var(iptr->dst, REG_FTMP1);
720                         if (iptr->val.f == 0) {
721                                 i386_fldz();
722
723                         } else if (iptr->val.f == 1) {
724                                 i386_fld1();
725
726 /*                      } else if (iptr->val.f == 2) { */
727 /*                              i386_fld1(); */
728 /*                              i386_fld1(); */
729 /*                              i386_faddp(); */
730
731                         } else {
732                                 a = dseg_addfloat(iptr->val.f);
733                                 i386_mov_imm_reg(0, REG_ITMP1);
734                                 dseg_adddata(mcodeptr);
735                                 i386_flds_membase(REG_ITMP1, a);
736                         }
737                         store_reg_to_var_flt(iptr->dst, d);
738                         break;
739                 
740                 case ICMD_DCONST:     /* ...  ==> ..., constant                       */
741                                       /* op1 = 0, val.d = constant                    */
742
743                         d = reg_of_var(iptr->dst, REG_FTMP1);
744                         if (iptr->val.d == 0) {
745                                 i386_fldz();
746
747                         } else if (iptr->val.d == 1) {
748                                 i386_fld1();
749
750                         } else {
751                                 a = dseg_adddouble(iptr->val.d);
752                                 i386_mov_imm_reg(0, REG_ITMP1);
753                                 dseg_adddata(mcodeptr);
754                                 i386_fldl_membase(REG_ITMP1, a);
755                         }
756                         store_reg_to_var_flt(iptr->dst, d);
757                         break;
758
759                 case ICMD_ACONST:     /* ...  ==> ..., constant                       */
760                                       /* op1 = 0, val.a = constant                    */
761
762                         d = reg_of_var(iptr->dst, REG_ITMP1);
763                         if (iptr->dst->flags & INMEMORY) {
764                                 i386_mov_imm_membase(iptr->val.a, REG_SP, iptr->dst->regoff * 8);
765                                 i386_mov_imm_membase(0, REG_SP, iptr->dst->regoff * 8 + 4);
766
767                         } else {
768
769                                 i386_mov_imm_reg(iptr->val.a, iptr->dst->regoff);
770                         }
771                         break;
772
773
774                 /* load/store operations **********************************************/
775
776                 case ICMD_ILOAD:      /* ...  ==> ..., content of local variable      */
777                               /* op1 = local variable                         */
778
779                         d = reg_of_var(iptr->dst, REG_ITMP1);
780                         if ((iptr->dst->varkind == LOCALVAR) &&
781                             (iptr->dst->varnum == iptr->op1)) {
782                                 break;
783                         }
784                         var = &(locals[iptr->op1][iptr->opc - ICMD_ILOAD]);
785                         if (iptr->dst->flags & INMEMORY) {
786                                 if (var->flags & INMEMORY) {
787                                         i386_mov_membase_reg(REG_SP, var->regoff * 8, REG_ITMP1);
788                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
789
790                                 } else {
791                                         i386_mov_reg_membase(var->regoff, REG_SP, iptr->dst->regoff * 8);
792                                 }
793
794                         } else {
795                                 if (var->flags & INMEMORY) {
796                                         i386_mov_membase_reg(REG_SP, var->regoff * 8, iptr->dst->regoff);
797
798                                 } else {
799                                         M_INTMOVE(var->regoff, iptr->dst->regoff);
800                                 }
801                         }
802                         break;
803
804                 case ICMD_ALOAD:      /* ...  ==> ..., content of local variable      */
805                               /* op1 = local variable                         */
806
807                         d = reg_of_var(iptr->dst, REG_ITMP1);
808                         if ((iptr->dst->varkind == LOCALVAR) &&
809                             (iptr->dst->varnum == iptr->op1)) {
810                                 break;
811                         }
812                         var = &(locals[iptr->op1][iptr->opc - ICMD_ILOAD]);
813                         if (iptr->dst->flags & INMEMORY) {
814                                 if (var->flags & INMEMORY) {
815                                         i386_mov_membase_reg(REG_SP, var->regoff * 8, REG_ITMP1);
816                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
817
818                                 } else {
819                                         i386_mov_reg_membase(var->regoff, REG_SP, iptr->dst->regoff * 8);
820                                 }
821
822                         } else {
823                                 if (var->flags & INMEMORY) {
824                                         i386_mov_membase_reg(REG_SP, var->regoff * 8, iptr->dst->regoff);
825
826                                 } else {
827                                         M_INTMOVE(var->regoff, iptr->dst->regoff);
828                                 }
829                         }
830                         break;
831
832                 case ICMD_LLOAD:      /* ...  ==> ..., content of local variable      */
833                                       /* op1 = local variable                         */
834
835                         d = reg_of_var(iptr->dst, REG_ITMP1);
836                         if ((iptr->dst->varkind == LOCALVAR) &&
837                             (iptr->dst->varnum == iptr->op1)) {
838                                 break;
839                         }
840                         var = &(locals[iptr->op1][iptr->opc - ICMD_ILOAD]);
841                         if (iptr->dst->flags & INMEMORY) {
842                                 if (var->flags & INMEMORY) {
843                                         i386_mov_membase_reg(REG_SP, var->regoff * 8, REG_ITMP1);
844                                         i386_mov_membase_reg(REG_SP, var->regoff * 8 + 4, REG_ITMP2);
845                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
846                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
847
848                                 } else {
849                                         i386_mov_reg_membase(var->regoff, REG_SP, iptr->dst->regoff * 8);
850                                 }
851
852                         } else {
853                                 panic("longs have to be in memory");
854                         }
855                         break;
856
857                 case ICMD_FLOAD:      /* ...  ==> ..., content of local variable      */
858                                       /* op1 = local variable                         */
859
860                         d = reg_of_var(iptr->dst, REG_FTMP1);
861 /*                      if ((iptr->dst->varkind == LOCALVAR) && */
862 /*                          (iptr->dst->varnum == iptr->op1)) { */
863 /*                              break; */
864 /*                      } */
865                         var = &(locals[iptr->op1][iptr->opc - ICMD_ILOAD]);
866                         i386_flds_membase(REG_SP, var->regoff * 8);
867                         store_reg_to_var_flt(iptr->dst, d);
868                         break;
869
870                 case ICMD_DLOAD:      /* ...  ==> ..., content of local variable      */
871                                       /* op1 = local variable                         */
872
873                         d = reg_of_var(iptr->dst, REG_FTMP1);
874 /*                      if ((iptr->dst->varkind == LOCALVAR) && */
875 /*                          (iptr->dst->varnum == iptr->op1)) { */
876 /*                              break; */
877 /*                      } */
878                         var = &(locals[iptr->op1][iptr->opc - ICMD_ILOAD]);
879                         i386_fldl_membase(REG_SP, var->regoff * 8);
880                         store_reg_to_var_flt(iptr->dst, d);
881                         break;
882
883                 case ICMD_ISTORE:     /* ..., value  ==> ...                          */
884                                       /* op1 = local variable                         */
885
886                         if ((src->varkind == LOCALVAR) &&
887                             (src->varnum == iptr->op1)) {
888                                 break;
889                         }
890                         var = &(locals[iptr->op1][iptr->opc - ICMD_ISTORE]);
891                         if (var->flags & INMEMORY) {
892                                 if (src->flags & INMEMORY) {
893                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
894                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, var->regoff * 8);
895                                         
896                                 } else {
897                                         i386_mov_reg_membase(src->regoff, REG_SP, var->regoff * 8);
898                                 }
899
900                         } else {
901                                 var_to_reg_int(s1, src, var->regoff);
902                                 M_INTMOVE(s1, var->regoff);
903                         }
904                         break;
905
906                 case ICMD_ASTORE:     /* ..., value  ==> ...                          */
907                                       /* op1 = local variable                         */
908
909                         if ((src->varkind == LOCALVAR) &&
910                             (src->varnum == iptr->op1)) {
911                                 break;
912                         }
913                         var = &(locals[iptr->op1][iptr->opc - ICMD_ISTORE]);
914                         if (var->flags & INMEMORY) {
915                                 if (src->flags & INMEMORY) {
916                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
917                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, var->regoff * 8);
918                                         
919                                 } else {
920                                         i386_mov_reg_membase(src->regoff, REG_SP, var->regoff * 8);
921                                 }
922
923                         } else {
924                                 var_to_reg_int(s1, src, var->regoff);
925                                 M_INTMOVE(s1, var->regoff);
926                         }
927                         break;
928
929                 case ICMD_LSTORE:     /* ..., value  ==> ...                          */
930                                       /* op1 = local variable                         */
931
932                         if ((src->varkind == LOCALVAR) &&
933                             (src->varnum == iptr->op1)) {
934                                 break;
935                         }
936                         var = &(locals[iptr->op1][iptr->opc - ICMD_ISTORE]);
937                         panic("LSTORE");
938 /*                      if (var->flags & INMEMORY) { */
939 /*                              var_to_reg_int(s1, src, REG_ITMP1); */
940 /*                              i386_mov_reg_membase(s1, REG_SP, var->regoff * 8); */
941
942 /*                      } else { */
943 /*                              var_to_reg_int(s1, src, var->regoff); */
944 /*                              M_INTMOVE(s1, var->regoff); */
945 /*                      } */
946                         break;
947
948                 case ICMD_FSTORE:     /* ..., value  ==> ...                          */
949                                       /* op1 = local variable                         */
950
951                         var = &(locals[iptr->op1][iptr->opc - ICMD_ISTORE]);
952                         i386_fstps_membase(REG_SP, var->regoff * 8);
953                         break;
954
955                 case ICMD_DSTORE:     /* ..., value  ==> ...                          */
956                                       /* op1 = local variable                         */
957
958                         var = &(locals[iptr->op1][iptr->opc - ICMD_ISTORE]);
959                         i386_fstpl_membase(REG_SP, var->regoff * 8);
960                         break;
961
962
963                 /* pop/dup/swap operations ********************************************/
964
965                 /* attention: double and longs are only one entry in CACAO ICMDs      */
966
967                 case ICMD_POP:        /* ..., value  ==> ...                          */
968                 case ICMD_POP2:       /* ..., value, value  ==> ...                   */
969                         break;
970
971                         /* TWISTI */
972 /*  #define M_COPY(from,to) \ */
973 /*                      d = reg_of_var(to, REG_IFTMP); \ */
974 /*                      if ((from->regoff != to->regoff) || \ */
975 /*                          ((from->flags ^ to->flags) & INMEMORY)) { \ */
976 /*                              if (IS_FLT_DBL_TYPE(from->type)) { \ */
977 /*                                      var_to_reg_flt(s1, from, d); \ */
978 /*                                      M_FLTMOVE(s1,d); \ */
979 /*                                      store_reg_to_var_flt(to, d); \ */
980 /*                                      }\ */
981 /*                              else { \ */
982 /*                                      var_to_reg_int(s1, from, d); \ */
983 /*                                      M_INTMOVE(s1,d); \ */
984 /*                                      store_reg_to_var_int(to, d); \ */
985 /*                                      }\ */
986 /*                              } */
987 #define M_COPY(from,to) \
988                         if ((from->regoff != to->regoff) || \
989                             ((from->flags ^ to->flags) & INMEMORY)) { \
990                                 if (IS_FLT_DBL_TYPE(from->type)) { \
991                                 d = reg_of_var(to, REG_IFTMP); \
992                                         var_to_reg_flt(s1, from, d); \
993                                         M_FLTMOVE(s1, d); \
994                                         store_reg_to_var_flt(to, d); \
995                                 } else { \
996                                 d = reg_of_var(to, REG_ITMP1); \
997                                         var_to_reg_int(s1, from, d); \
998                                         M_INTMOVE(s1, d); \
999                                         store_reg_to_var_int(to, s1); \
1000                                 }\
1001                         }
1002
1003                 case ICMD_DUP:        /* ..., a ==> ..., a, a                         */
1004                         M_COPY(src, iptr->dst);
1005                         break;
1006
1007                 case ICMD_DUP_X1:     /* ..., a, b ==> ..., b, a, b                   */
1008
1009                         M_COPY(src,       iptr->dst->prev->prev);
1010
1011                 case ICMD_DUP2:       /* ..., a, b ==> ..., a, b, a, b                */
1012
1013                         M_COPY(src,       iptr->dst);
1014                         M_COPY(src->prev, iptr->dst->prev);
1015                         break;
1016
1017                 case ICMD_DUP2_X1:    /* ..., a, b, c ==> ..., b, c, a, b, c          */
1018
1019                         M_COPY(src->prev,       iptr->dst->prev->prev->prev);
1020
1021                 case ICMD_DUP_X2:     /* ..., a, b, c ==> ..., c, a, b, c             */
1022
1023                         M_COPY(src,             iptr->dst);
1024                         M_COPY(src->prev,       iptr->dst->prev);
1025                         M_COPY(src->prev->prev, iptr->dst->prev->prev);
1026                         M_COPY(src, iptr->dst->prev->prev->prev);
1027                         break;
1028
1029                 case ICMD_DUP2_X2:    /* ..., a, b, c, d ==> ..., c, d, a, b, c, d    */
1030
1031                         M_COPY(src,                   iptr->dst);
1032                         M_COPY(src->prev,             iptr->dst->prev);
1033                         M_COPY(src->prev->prev,       iptr->dst->prev->prev);
1034                         M_COPY(src->prev->prev->prev, iptr->dst->prev->prev->prev);
1035                         M_COPY(src,       iptr->dst->prev->prev->prev->prev);
1036                         M_COPY(src->prev, iptr->dst->prev->prev->prev->prev->prev);
1037                         break;
1038
1039                 case ICMD_SWAP:       /* ..., a, b ==> ..., b, a                      */
1040
1041                         M_COPY(src, iptr->dst->prev);
1042                         M_COPY(src->prev, iptr->dst);
1043                         break;
1044
1045
1046                 /* integer operations *************************************************/
1047
1048                 case ICMD_INEG:       /* ..., value  ==> ..., - value                 */
1049
1050                         d = reg_of_var(iptr->dst, REG_ITMP3);
1051                         if (iptr->dst->flags & INMEMORY) {
1052                                 if (src->flags & INMEMORY) {
1053                                         if (src->regoff == iptr->dst->regoff) {
1054                                                 i386_neg_membase(REG_SP, iptr->dst->regoff * 8);
1055
1056                                         } else {
1057                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1058                                                 i386_neg_reg(REG_ITMP1);
1059                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1060                                         }
1061
1062                                 } else {
1063                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1064                                         i386_neg_membase(REG_SP, iptr->dst->regoff * 8);
1065                                 }
1066
1067                         } else {
1068                                 if (src->flags & INMEMORY) {
1069                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1070                                         i386_neg_reg(iptr->dst->regoff);
1071
1072                                 } else {
1073                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1074                                         i386_neg_reg(iptr->dst->regoff);
1075                                 }
1076                         }
1077                         break;
1078
1079                 case ICMD_LNEG:       /* ..., value  ==> ..., - value                 */
1080
1081                         d = reg_of_var(iptr->dst, REG_ITMP3);
1082                         if (iptr->dst->flags & INMEMORY) {
1083                                 if (src->flags & INMEMORY) {
1084                                         if (src->regoff == iptr->dst->regoff) {
1085                                                 i386_neg_membase(REG_SP, iptr->dst->regoff * 8);
1086                                                 i386_alu_imm_membase(I386_ADC, 0, REG_SP, iptr->dst->regoff * 8 + 4);
1087                                                 i386_neg_membase(REG_SP, iptr->dst->regoff * 8 + 4);
1088
1089                                         } else {
1090                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1091                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
1092                                                 i386_neg_reg(REG_ITMP1);
1093                                                 i386_alu_imm_reg(I386_ADC, 0, REG_ITMP2);
1094                                                 i386_neg_reg(REG_ITMP2);
1095                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1096                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1097                                         }
1098                                 }
1099                         }
1100                         break;
1101
1102                 case ICMD_I2L:        /* ..., value  ==> ..., value                   */
1103
1104                         d = reg_of_var(iptr->dst, REG_ITMP3);
1105                         if (iptr->dst->flags & INMEMORY) {
1106                                 if (src->flags & INMEMORY) {
1107                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_EAX);
1108                                         i386_cltd();
1109                                         i386_mov_reg_membase(I386_EAX, REG_SP, iptr->dst->regoff * 8);
1110                                         i386_mov_reg_membase(I386_EDX, REG_SP, iptr->dst->regoff * 8 + 4);
1111
1112                                 } else {
1113                                         M_INTMOVE(src->regoff, I386_EAX);
1114                                         i386_cltd();
1115                                         i386_mov_reg_membase(I386_EAX, REG_SP, iptr->dst->regoff * 8);
1116                                         i386_mov_reg_membase(I386_EDX, REG_SP, iptr->dst->regoff * 8 + 4);
1117                                 }
1118                         }
1119                         break;
1120
1121                 case ICMD_L2I:        /* ..., value  ==> ..., value                   */
1122
1123                         d = reg_of_var(iptr->dst, REG_ITMP3);
1124                         if (iptr->dst->flags & INMEMORY) {
1125                                 if (src->flags & INMEMORY) {
1126                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1127                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1128                                 }
1129
1130                         } else {
1131                                 if (src->flags & INMEMORY) {
1132                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1133                                 }
1134                         }
1135                         break;
1136
1137                 case ICMD_INT2BYTE:   /* ..., value  ==> ..., value                   */
1138
1139                         d = reg_of_var(iptr->dst, REG_ITMP3);
1140                         if (iptr->dst->flags & INMEMORY) {
1141                                 if (src->flags & INMEMORY) {
1142                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1143                                         i386_shift_imm_reg(I386_SHL, 24, REG_ITMP1);
1144                                         i386_shift_imm_reg(I386_SAR, 24, REG_ITMP1);
1145                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1146
1147                                 } else {
1148                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1149                                         i386_shift_imm_membase(I386_SHL, 24, REG_SP, iptr->dst->regoff * 8);
1150                                         i386_shift_imm_membase(I386_SAR, 24, REG_SP, iptr->dst->regoff * 8);
1151                                 }
1152
1153                         } else {
1154                                 if (src->flags & INMEMORY) {
1155                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1156                                         i386_shift_imm_reg(I386_SHL, 24, iptr->dst->regoff);
1157                                         i386_shift_imm_reg(I386_SAR, 24, iptr->dst->regoff);
1158
1159                                 } else {
1160                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1161                                         i386_shift_imm_reg(I386_SHL, 24, iptr->dst->regoff);
1162                                         i386_shift_imm_reg(I386_SAR, 24, iptr->dst->regoff);
1163                                 }
1164                         }
1165                         break;
1166
1167                 case ICMD_INT2CHAR:   /* ..., value  ==> ..., value                   */
1168
1169                         d = reg_of_var(iptr->dst, REG_ITMP3);
1170                         if (iptr->dst->flags & INMEMORY) {
1171                                 if (src->flags & INMEMORY) {
1172                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1173                                         i386_alu_imm_reg(I386_AND, 0x0000ffff, REG_ITMP1);
1174                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1175
1176                                 } else {
1177                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1178                                         i386_alu_imm_membase(I386_AND, 0x0000ffff, REG_SP, iptr->dst->regoff * 8);
1179                                 }
1180
1181                         } else {
1182                                 if (src->flags & INMEMORY) {
1183                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1184                                         i386_alu_imm_reg(I386_AND, 0x0000ffff, iptr->dst->regoff);
1185
1186                                 } else {
1187                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1188                                         i386_alu_imm_reg(I386_AND, 0x0000ffff, iptr->dst->regoff);
1189                                 }
1190                         }
1191                         break;
1192
1193                 case ICMD_INT2SHORT:  /* ..., value  ==> ..., value                   */
1194
1195                         d = reg_of_var(iptr->dst, REG_ITMP3);
1196                         if (iptr->dst->flags & INMEMORY) {
1197                                 if (src->flags & INMEMORY) {
1198                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1199                                         i386_shift_imm_reg(I386_SHL, 16, REG_ITMP1);
1200                                         i386_shift_imm_reg(I386_SAR, 16, REG_ITMP1);
1201                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1202
1203                                 } else {
1204                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1205                                         i386_shift_imm_membase(I386_SHL, 16, REG_SP, iptr->dst->regoff * 8);
1206                                         i386_shift_imm_membase(I386_SAR, 16, REG_SP, iptr->dst->regoff * 8);
1207                                 }
1208
1209                         } else {
1210                                 if (src->flags & INMEMORY) {
1211                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1212                                         i386_shift_imm_reg(I386_SHL, 16, iptr->dst->regoff);
1213                                         i386_shift_imm_reg(I386_SAR, 16, iptr->dst->regoff);
1214
1215                                 } else {
1216                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1217                                         i386_shift_imm_reg(I386_SHL, 16, iptr->dst->regoff);
1218                                         i386_shift_imm_reg(I386_SAR, 16, iptr->dst->regoff);
1219                                 }
1220                         }
1221                         break;
1222
1223
1224                 case ICMD_IADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
1225
1226                         d = reg_of_var(iptr->dst, REG_ITMP3);
1227                         if (iptr->dst->flags & INMEMORY) {
1228                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1229                                         if (src->regoff == iptr->dst->regoff) {
1230                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1231                                                 i386_alu_reg_membase(I386_ADD, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1232
1233                                         } else if (src->prev->regoff == iptr->dst->regoff) {
1234                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1235                                                 i386_alu_reg_membase(I386_ADD, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1236
1237                                         } else {
1238                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1239                                                 i386_alu_membase_reg(I386_ADD, REG_SP, src->regoff * 8, REG_ITMP1);
1240                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1241                                         }
1242
1243                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1244                                         if (src->regoff == iptr->dst->regoff) {
1245                                                 i386_alu_reg_membase(I386_ADD, src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1246
1247                                         } else {
1248                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1249                                                 i386_alu_reg_reg(I386_ADD, src->prev->regoff, REG_ITMP1);
1250                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1251                                         }
1252
1253                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1254                                         if (src->prev->regoff == iptr->dst->regoff) {
1255                                                 i386_alu_reg_membase(I386_ADD, src->regoff, REG_SP, iptr->dst->regoff * 8);
1256                                                 
1257                                         } else {
1258                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1259                                                 i386_alu_reg_reg(I386_ADD, src->regoff, REG_ITMP1);
1260                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1261                                         }
1262
1263                                 } else {
1264                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1265                                         i386_alu_reg_membase(I386_ADD, src->regoff, REG_SP, iptr->dst->regoff * 8);
1266                                 }
1267
1268                         } else {
1269                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1270                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1271                                         i386_alu_membase_reg(I386_ADD, REG_SP, src->regoff * 8, iptr->dst->regoff);
1272
1273                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1274                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1275                                         i386_alu_membase_reg(I386_ADD, REG_SP, src->regoff * 8, iptr->dst->regoff);
1276
1277                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1278                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1279                                         i386_alu_membase_reg(I386_ADD, REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1280
1281                                 } else {
1282                                         if (src->regoff == iptr->dst->regoff) {
1283                                                 i386_alu_reg_reg(I386_ADD, src->prev->regoff, iptr->dst->regoff);
1284
1285                                         } else {
1286                                                 M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1287                                                 i386_alu_reg_reg(I386_ADD, src->regoff, iptr->dst->regoff);
1288                                         }
1289                                 }
1290                         }
1291                         break;
1292
1293                 case ICMD_IADDCONST:  /* ..., value  ==> ..., value + constant        */
1294                                       /* val.i = constant                             */
1295
1296                         d = reg_of_var(iptr->dst, REG_ITMP3);
1297                         if (iptr->dst->flags & INMEMORY) {
1298                                 if (src->flags & INMEMORY) {
1299                                         /*
1300                                          * do not use here inc optimization, because it's slower (???) 
1301                                          */
1302                                         if (src->regoff == iptr->dst->regoff) {
1303                                                 i386_alu_imm_membase(I386_ADD, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1304
1305                                         } else {
1306                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1307                                                 i386_alu_imm_reg(I386_ADD, iptr->val.i, REG_ITMP1);
1308                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1309                                         }
1310
1311                                 } else {
1312                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1313                                         i386_alu_imm_membase(I386_ADD, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1314                                 }
1315
1316                         } else {
1317                                 if (src->flags & INMEMORY) {
1318                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1319
1320                                         if (iptr->val.i == 1) {
1321                                                 i386_inc_reg(iptr->dst->regoff);
1322
1323                                         } else {
1324                                                 i386_alu_imm_reg(I386_ADD, iptr->val.i, iptr->dst->regoff);
1325                                         }
1326
1327                                 } else {
1328                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1329
1330                                         if (iptr->val.i == 1) {
1331                                                 i386_inc_reg(iptr->dst->regoff);
1332
1333                                         } else {
1334                                                 i386_alu_imm_reg(I386_ADD, iptr->val.i, iptr->dst->regoff);
1335                                         }
1336                                 }
1337                         }
1338                         break;
1339
1340                 case ICMD_LADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
1341
1342                         d = reg_of_var(iptr->dst, REG_ITMP3);
1343                         if (iptr->dst->flags & INMEMORY) {
1344                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1345                                         if (src->regoff == iptr->dst->regoff) {
1346                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1347                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
1348                                                 i386_alu_reg_membase(I386_ADD, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1349                                                 i386_alu_reg_membase(I386_ADC, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1350
1351                                         } else if (src->prev->regoff == iptr->dst->regoff) {
1352                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1353                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
1354                                                 i386_alu_reg_membase(I386_ADD, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1355                                                 i386_alu_reg_membase(I386_ADC, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1356
1357                                         } else {
1358                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1359                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
1360                                                 i386_alu_membase_reg(I386_ADD, REG_SP, src->regoff * 8, REG_ITMP1);
1361                                                 i386_alu_membase_reg(I386_ADC, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
1362                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1363                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1364                                         }
1365
1366                                 }
1367                         }
1368                         break;
1369
1370                 case ICMD_LADDCONST:  /* ..., value  ==> ..., value + constant        */
1371                                       /* val.l = constant                             */
1372
1373                         d = reg_of_var(iptr->dst, REG_ITMP3);
1374                         if (iptr->dst->flags & INMEMORY) {
1375                                 if (src->flags & INMEMORY) {
1376                                         if (src->regoff == iptr->dst->regoff) {
1377                                                 i386_alu_imm_membase(I386_ADD, iptr->val.l, REG_SP, iptr->dst->regoff * 8);
1378                                                 i386_alu_imm_membase(I386_ADC, iptr->val.l >> 32, REG_SP, iptr->dst->regoff * 8 + 4);
1379
1380                                         } else {
1381                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1382                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
1383                                                 i386_alu_imm_reg(I386_ADD, iptr->val.l, REG_ITMP1);
1384                                                 i386_alu_imm_reg(I386_ADC, iptr->val.l >> 32, REG_ITMP2);
1385                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1386                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1387                                         }
1388                                 }
1389                         }
1390                         break;
1391
1392                 case ICMD_ISUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
1393
1394                         d = reg_of_var(iptr->dst, REG_ITMP3);
1395                         if (iptr->dst->flags & INMEMORY) {
1396                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1397                                         if (src->prev->regoff == iptr->dst->regoff) {
1398                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1399                                                 i386_alu_reg_membase(I386_SUB, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1400
1401                                         } else {
1402                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1403                                                 i386_alu_membase_reg(I386_SUB, REG_SP, src->regoff * 8, REG_ITMP1);
1404                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1405                                         }
1406
1407                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1408                                         M_INTMOVE(src->prev->regoff, REG_ITMP1);
1409                                         i386_alu_membase_reg(I386_SUB, REG_SP, src->regoff * 8, REG_ITMP1);
1410                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1411
1412                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1413                                         if (src->prev->regoff == iptr->dst->regoff) {
1414                                                 i386_alu_reg_membase(I386_SUB, src->regoff, REG_SP, iptr->dst->regoff * 8);
1415
1416                                         } else {
1417                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1418                                                 i386_alu_reg_reg(I386_SUB, src->regoff, REG_ITMP1);
1419                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1420                                         }
1421
1422                                 } else {
1423                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1424                                         i386_alu_reg_membase(I386_SUB, src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1425                                 }
1426
1427                         } else {
1428                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1429                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1430                                         i386_alu_membase_reg(I386_SUB, REG_SP, src->regoff * 8, iptr->dst->regoff);
1431
1432                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1433                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1434                                         i386_alu_membase_reg(I386_SUB, REG_SP, src->regoff * 8, iptr->dst->regoff);
1435
1436                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1437                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1438                                         i386_alu_reg_reg(I386_SUB, src->regoff, iptr->dst->regoff);
1439
1440                                 } else {
1441                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1442                                         i386_alu_reg_reg(I386_SUB, src->regoff, iptr->dst->regoff);
1443                                 }
1444                         }
1445                         break;
1446
1447                 case ICMD_ISUBCONST:  /* ..., value  ==> ..., value + constant        */
1448                                       /* val.i = constant                             */
1449
1450                         d = reg_of_var(iptr->dst, REG_ITMP3);
1451                         if (iptr->dst->flags & INMEMORY) {
1452                                 if (src->flags & INMEMORY) {
1453                                         if (src->regoff == iptr->dst->regoff) {
1454                                                 i386_alu_imm_membase(I386_SUB, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1455
1456                                         } else {
1457                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1458                                                 i386_alu_imm_reg(I386_SUB, iptr->val.i, REG_ITMP1);
1459                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1460                                         }
1461
1462                                 } else {
1463                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1464                                         i386_alu_imm_membase(I386_SUB, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1465                                 }
1466
1467                         } else {
1468                                 if (src->flags & INMEMORY) {
1469                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1470                                         i386_alu_imm_reg(I386_SUB, iptr->val.i, iptr->dst->regoff);
1471
1472                                 } else {
1473                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1474                                         i386_alu_imm_reg(I386_SUB, iptr->val.i, iptr->dst->regoff);
1475                                 }
1476                         }
1477                         break;
1478
1479                 case ICMD_LSUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
1480
1481                         d = reg_of_var(iptr->dst, REG_ITMP3);
1482                         if (iptr->dst->flags & INMEMORY) {
1483                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1484                                         if (src->prev->regoff == iptr->dst->regoff) {
1485                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1486                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
1487                                                 i386_alu_reg_membase(I386_SUB, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1488                                                 i386_alu_reg_membase(I386_SBB, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1489
1490                                         } else {
1491                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1492                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
1493                                                 i386_alu_membase_reg(I386_SUB, REG_SP, src->regoff * 8, REG_ITMP1);
1494                                                 i386_alu_membase_reg(I386_SBB, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
1495                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1496                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1497                                         }
1498                                 }
1499                         }
1500                         break;
1501
1502                 case ICMD_LSUBCONST:  /* ..., value  ==> ..., value - constant        */
1503                                       /* val.l = constant                             */
1504
1505                         d = reg_of_var(iptr->dst, REG_ITMP3);
1506                         if (iptr->dst->flags & INMEMORY) {
1507                                 if (src->flags & INMEMORY) {
1508                                         if (src->regoff == iptr->dst->regoff) {
1509                                                 i386_alu_imm_membase(I386_SUB, iptr->val.l, REG_SP, iptr->dst->regoff * 8);
1510                                                 i386_alu_imm_membase(I386_SBB, iptr->val.l >> 32, REG_SP, iptr->dst->regoff * 8 + 4);
1511
1512                                         } else {
1513                                                 /* TODO: could be size optimized with lea -- see gcc output */
1514                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1515                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
1516                                                 i386_alu_imm_reg(I386_SUB, iptr->val.l, REG_ITMP1);
1517                                                 i386_alu_imm_reg(I386_SBB, iptr->val.l >> 32, REG_ITMP2);
1518                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1519                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
1520                                         }
1521                                 }
1522                         }
1523                         break;
1524
1525                 case ICMD_IMUL:       /* ..., val1, val2  ==> ..., val1 * val2        */
1526
1527                         d = reg_of_var(iptr->dst, REG_ITMP3);
1528                         if (iptr->dst->flags & INMEMORY) {
1529                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1530                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1531                                         i386_imul_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1532                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1533
1534                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1535                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1536                                         i386_imul_reg_reg(src->prev->regoff, REG_ITMP1);
1537                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1538
1539                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1540                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1541                                         i386_imul_reg_reg(src->regoff, REG_ITMP1);
1542                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1543
1544                                 } else {
1545                                         i386_mov_reg_reg(src->prev->regoff, REG_ITMP1);
1546                                         i386_imul_reg_reg(src->regoff, REG_ITMP1);
1547                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1548                                 }
1549
1550                         } else {
1551                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1552                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1553                                         i386_imul_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1554
1555                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1556                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1557                                         i386_imul_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1558
1559                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1560                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1561                                         i386_imul_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1562
1563                                 } else {
1564                                         if (src->regoff == iptr->dst->regoff) {
1565                                                 i386_imul_reg_reg(src->prev->regoff, iptr->dst->regoff);
1566
1567                                         } else {
1568                                                 M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1569                                                 i386_imul_reg_reg(src->regoff, iptr->dst->regoff);
1570                                         }
1571                                 }
1572                         }
1573                         break;
1574
1575                 case ICMD_IMULCONST:  /* ..., value  ==> ..., value * constant        */
1576                                       /* val.i = constant                             */
1577
1578                         d = reg_of_var(iptr->dst, REG_ITMP3);
1579                         if (iptr->dst->flags & INMEMORY) {
1580                                 if (src->flags & INMEMORY) {
1581                                         i386_imul_imm_membase_reg(iptr->val.i, REG_SP, src->regoff * 8, REG_ITMP1);
1582                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1583
1584                                 } else {
1585                                         i386_imul_imm_reg_reg(iptr->val.i, src->regoff, REG_ITMP1);
1586                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1587                                 }
1588
1589                         } else {
1590                                 if (src->flags & INMEMORY) {
1591                                         i386_imul_imm_membase_reg(iptr->val.i, REG_SP, src->regoff * 8, iptr->dst->regoff);
1592
1593                                 } else {
1594                                         i386_imul_imm_reg_reg(iptr->val.i, src->regoff, iptr->dst->regoff);
1595                                 }
1596                         }
1597                         break;
1598
1599                 case ICMD_LMUL:       /* ..., val1, val2  ==> ..., val1 * val2        */
1600
1601                         d = reg_of_var(iptr->dst, REG_ITMP1);
1602                         if (iptr->dst->flags & INMEMORY) {
1603                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1604                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_EAX);              /* mem -> EAX             */
1605                                         /* optimize move EAX -> REG_ITMP3 is slower??? */
1606 /*                                      i386_mov_reg_reg(I386_EAX, REG_ITMP3); */
1607                                         i386_mul_membase(REG_SP, src->prev->regoff * 8);                      /* mem * EAX -> EDX:EAX   */
1608
1609                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP3);             /* mem -> ITMP3           */
1610                                         i386_imul_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP3);  /* mem * ITMP3 -> ITMP3   */
1611                                         i386_alu_reg_reg(I386_ADD, REG_ITMP3, I386_EDX);                      /* ITMP3 + EDX -> EDX     */
1612
1613                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP3);             /* mem -> ITMP3           */
1614                                         i386_imul_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP3);  /* mem * ITMP3 -> ITMP3   */
1615
1616                                         i386_alu_reg_reg(I386_ADD, REG_ITMP3, I386_EDX);                      /* ITMP3 + EDX -> EDX     */
1617                                         i386_mov_reg_membase(I386_EAX, REG_SP, iptr->dst->regoff * 8);
1618                                         i386_mov_reg_membase(I386_EDX, REG_SP, iptr->dst->regoff * 8 + 4);
1619                                 }
1620                         }
1621                         break;
1622
1623                 case ICMD_LMULCONST:  /* ..., value  ==> ..., value * constant        */
1624                                       /* val.l = constant                             */
1625
1626                         d = reg_of_var(iptr->dst, REG_ITMP1);
1627                         if (iptr->dst->flags & INMEMORY) {
1628                                 if (src->flags & INMEMORY) {
1629                                         i386_mov_imm_reg(iptr->val.l, I386_EAX);                              /* imm -> EAX             */
1630                                         i386_mul_membase(REG_SP, src->regoff * 8);                            /* mem * EAX -> EDX:EAX   */
1631                                         /* TODO: optimize move EAX -> REG_ITMP3 */
1632                                         i386_mov_imm_reg(iptr->val.l, REG_ITMP3);                             /* imm -> ITMP3           */
1633                                         i386_imul_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP3);        /* mem * ITMP3 -> ITMP3   */
1634
1635                                         i386_alu_reg_reg(I386_ADD, REG_ITMP3, I386_EDX);                      /* ITMP3 + EDX -> EDX     */
1636                                         i386_mov_imm_reg(iptr->val.l >> 32, REG_ITMP3);                       /* imm -> ITMP3           */
1637                                         i386_imul_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP3);        /* mem * ITMP3 -> ITMP3   */
1638
1639                                         i386_alu_reg_reg(I386_ADD, REG_ITMP3, I386_EDX);                      /* ITMP3 + EDX -> EDX     */
1640                                         i386_mov_reg_membase(I386_EAX, REG_SP, iptr->dst->regoff * 8);
1641                                         i386_mov_reg_membase(I386_EDX, REG_SP, iptr->dst->regoff * 8 + 4);
1642                                 }
1643                         }
1644                         break;
1645
1646                 case ICMD_IDIV:       /* ..., val1, val2  ==> ..., val1 / val2        */
1647
1648                         d = reg_of_var(iptr->dst, REG_ITMP3);
1649                         if (src->prev->flags & INMEMORY) {
1650                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, I386_EAX);
1651
1652                         } else {
1653                                 M_INTMOVE(src->prev->regoff, I386_EAX);
1654                         }
1655                         
1656                         i386_cltd();
1657
1658                         if (src->flags & INMEMORY) {
1659                                 i386_idiv_membase(REG_SP, src->regoff * 8);
1660
1661                         } else {
1662                                 i386_idiv_reg(src->regoff);
1663                         }
1664
1665                         if (iptr->dst->flags & INMEMORY) {
1666                                 i386_mov_reg_membase(I386_EAX, REG_SP, iptr->dst->regoff * 8);
1667
1668                         } else {
1669                                 M_INTMOVE(I386_EAX, iptr->dst->regoff);
1670                         }
1671                         break;
1672
1673                 case ICMD_IREM:       /* ..., val1, val2  ==> ..., val1 % val2        */
1674
1675                         d = reg_of_var(iptr->dst, REG_ITMP3);
1676                         if (src->prev->flags & INMEMORY) {
1677                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, I386_EAX);
1678
1679                         } else {
1680                                 M_INTMOVE(src->prev->regoff, I386_EAX);
1681                         }
1682                         
1683                         i386_cltd();
1684
1685                         if (src->flags & INMEMORY) {
1686                                 i386_idiv_membase(REG_SP, src->regoff * 8);
1687
1688                         } else {
1689                                 i386_idiv_reg(src->regoff);
1690                         }
1691
1692                         if (iptr->dst->flags & INMEMORY) {
1693                                 i386_mov_reg_membase(I386_EDX, REG_SP, iptr->dst->regoff * 8);
1694
1695                         } else {
1696                                 M_INTMOVE(I386_EDX, iptr->dst->regoff);
1697                         }
1698                         break;
1699
1700                 case ICMD_IDIVPOW2:   /* ..., value  ==> ..., value >> constant       */
1701                                       /* val.i = constant                             */
1702
1703                         d = reg_of_var(iptr->dst, REG_ITMP3);
1704                         if (iptr->dst->flags & INMEMORY) {
1705                                 if (src->flags & INMEMORY) {
1706                                         if (src->regoff == iptr->dst->regoff) {
1707                                                 i386_shift_imm_membase(I386_SAR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1708
1709                                         } else {
1710                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1711                                                 i386_shift_imm_reg(I386_SAR, iptr->val.i, REG_ITMP1);
1712                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1713                                         }
1714
1715                                 } else {
1716                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1717                                         i386_shift_imm_membase(I386_SAR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1718                                 }
1719
1720                         } else {
1721                                 if (src->flags & INMEMORY) {
1722                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1723                                         i386_shift_imm_reg(I386_SAR, iptr->val.i, iptr->dst->regoff);
1724
1725                                 } else {
1726                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
1727                                         i386_shift_imm_reg(I386_SAR, iptr->val.i, iptr->dst->regoff);
1728                                 }
1729                         }
1730                         break;
1731
1732                 case ICMD_LDIVPOW2:   /* ..., value  ==> ..., value >> constant       */
1733                                       /* val.i = constant                             */
1734
1735                         var_to_reg_int(s1, src, REG_ITMP1);
1736                         d = reg_of_var(iptr->dst, REG_ITMP3);
1737                         if (iptr->val.i <= 15) {
1738                                 M_LDA(REG_ITMP2, s1, (1 << iptr->val.i) -1);
1739                                 M_CMOVGE(s1, s1, REG_ITMP2);
1740                                 }
1741                         else {
1742                                 M_SRA_IMM(s1, 63, REG_ITMP2);
1743                                 M_SRL_IMM(REG_ITMP2, 64 - iptr->val.i, REG_ITMP2);
1744                                 M_LADD(s1, REG_ITMP2, REG_ITMP2);
1745                                 }
1746                         M_SRA_IMM(REG_ITMP2, iptr->val.i, d);
1747                         store_reg_to_var_int(iptr->dst, d);
1748                         break;
1749
1750                 case ICMD_ISHL:       /* ..., val1, val2  ==> ..., val1 << val2       */
1751
1752                         d = reg_of_var(iptr->dst, REG_ITMP2);
1753                         if (iptr->dst->flags & INMEMORY) {
1754                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1755                                         if (src->prev->regoff == iptr->dst->regoff) {
1756                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1757                                                 i386_shift_membase(I386_SHL, REG_SP, iptr->dst->regoff * 8);
1758
1759                                         } else {
1760                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1761                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1762                                                 i386_shift_reg(I386_SHL, REG_ITMP1);
1763                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1764                                         }
1765
1766                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1767                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1768                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1769                                         i386_shift_membase(I386_SHL, REG_SP, iptr->dst->regoff * 8);
1770
1771                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1772                                         if (src->prev->regoff == iptr->dst->regoff) {
1773                                                 M_INTMOVE(src->regoff, I386_ECX);
1774                                                 i386_shift_membase(I386_SHL, REG_SP, iptr->dst->regoff * 8);
1775
1776                                         } else {
1777                                                 M_INTMOVE(src->regoff, I386_ECX);
1778                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1779                                                 i386_shift_reg(I386_SHL, REG_ITMP1);
1780                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1781                                         }
1782
1783                                 } else {
1784                                         M_INTMOVE(src->regoff, I386_ECX);
1785                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1786                                         i386_shift_membase(I386_SHL, REG_SP, iptr->dst->regoff * 8);
1787                                 }
1788
1789                         } else {
1790                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1791                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1792                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1793                                         i386_shift_reg(I386_SHL, iptr->dst->regoff);
1794
1795                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1796                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1797                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1798                                         i386_shift_reg(I386_SHL, iptr->dst->regoff);
1799
1800                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1801                                         M_INTMOVE(src->regoff, I386_ECX);
1802                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1803                                         i386_shift_reg(I386_SHL, iptr->dst->regoff);
1804
1805                                 } else {
1806                                         M_INTMOVE(src->regoff, I386_ECX);
1807                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1808                                         i386_shift_reg(I386_SHL, iptr->dst->regoff);
1809                                 }
1810                         }
1811                         break;
1812
1813                 case ICMD_ISHLCONST:  /* ..., value  ==> ..., value << constant       */
1814                                       /* val.i = constant                             */
1815
1816                         d = reg_of_var(iptr->dst, REG_ITMP1);
1817                         if ((src->flags & INMEMORY) && (iptr->dst->flags & INMEMORY)) {
1818                                 if (src->regoff == iptr->dst->regoff) {
1819                                         i386_shift_imm_membase(I386_SHL, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1820
1821                                 } else {
1822                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1823                                         i386_shift_imm_reg(I386_SHL, iptr->val.i, REG_ITMP1);
1824                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1825                                 }
1826
1827                         } else if ((src->flags & INMEMORY) && !(iptr->dst->flags & INMEMORY)) {
1828                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1829                                 i386_shift_imm_reg(I386_SHL, iptr->val.i, iptr->dst->regoff);
1830                                 
1831                         } else if (!(src->flags & INMEMORY) && (iptr->dst->flags & INMEMORY)) {
1832                                 i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1833                                 i386_shift_imm_membase(I386_SHL, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1834
1835                         } else {
1836                                 M_INTMOVE(src->regoff, iptr->dst->regoff);
1837                                 i386_shift_imm_reg(I386_SHL, iptr->val.i, iptr->dst->regoff);
1838                         }
1839                         break;
1840
1841                 case ICMD_ISHR:       /* ..., val1, val2  ==> ..., val1 >> val2       */
1842
1843                         d = reg_of_var(iptr->dst, REG_ITMP2);
1844                         if (iptr->dst->flags & INMEMORY) {
1845                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1846                                         if (src->prev->regoff == iptr->dst->regoff) {
1847                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1848                                                 i386_shift_membase(I386_SAR, REG_SP, iptr->dst->regoff * 8);
1849
1850                                         } else {
1851                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1852                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1853                                                 i386_shift_reg(I386_SAR, REG_ITMP1);
1854                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1855                                         }
1856
1857                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1858                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1859                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1860                                         i386_shift_membase(I386_SAR, REG_SP, iptr->dst->regoff * 8);
1861
1862                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1863                                         if (src->prev->regoff == iptr->dst->regoff) {
1864                                                 M_INTMOVE(src->regoff, I386_ECX);
1865                                                 i386_shift_membase(I386_SAR, REG_SP, iptr->dst->regoff * 8);
1866
1867                                         } else {
1868                                                 M_INTMOVE(src->regoff, I386_ECX);
1869                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1870                                                 i386_shift_reg(I386_SAR, REG_ITMP1);
1871                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1872                                         }
1873
1874                                 } else {
1875                                         M_INTMOVE(src->regoff, I386_ECX);
1876                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1877                                         i386_shift_membase(I386_SAR, REG_SP, iptr->dst->regoff * 8);
1878                                 }
1879
1880                         } else {
1881                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1882                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1883                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1884                                         i386_shift_reg(I386_SAR, iptr->dst->regoff);
1885
1886                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1887                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1888                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1889                                         i386_shift_reg(I386_SAR, iptr->dst->regoff);
1890
1891                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1892                                         M_INTMOVE(src->regoff, I386_ECX);
1893                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1894                                         i386_shift_reg(I386_SAR, iptr->dst->regoff);
1895
1896                                 } else {
1897                                         M_INTMOVE(src->regoff, I386_ECX);
1898                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1899                                         i386_shift_reg(I386_SAR, iptr->dst->regoff);
1900                                 }
1901                         }
1902                         break;
1903
1904                 case ICMD_ISHRCONST:  /* ..., value  ==> ..., value >> constant       */
1905                                       /* val.i = constant                             */
1906
1907                         d = reg_of_var(iptr->dst, REG_ITMP1);
1908                         if ((src->flags & INMEMORY) && (iptr->dst->flags & INMEMORY)) {
1909                                 if (src->regoff == iptr->dst->regoff) {
1910                                         i386_shift_imm_membase(I386_SAR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1911
1912                                 } else {
1913                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
1914                                         i386_shift_imm_reg(I386_SAR, iptr->val.i, REG_ITMP1);
1915                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1916                                 }
1917
1918                         } else if ((src->flags & INMEMORY) && !(iptr->dst->flags & INMEMORY)) {
1919                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
1920                                 i386_shift_imm_reg(I386_SAR, iptr->val.i, iptr->dst->regoff);
1921                                 
1922                         } else if (!(src->flags & INMEMORY) && (iptr->dst->flags & INMEMORY)) {
1923                                 i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
1924                                 i386_shift_imm_membase(I386_SAR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
1925
1926                         } else {
1927                                 M_INTMOVE(src->regoff, iptr->dst->regoff);
1928                                 i386_shift_imm_reg(I386_SAR, iptr->val.i, iptr->dst->regoff);
1929                         }
1930                         break;
1931
1932                 case ICMD_IUSHR:      /* ..., val1, val2  ==> ..., val1 >>> val2      */
1933
1934                         d = reg_of_var(iptr->dst, REG_ITMP2);
1935                         if (iptr->dst->flags & INMEMORY) {
1936                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1937                                         if (src->prev->regoff == iptr->dst->regoff) {
1938                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1939                                                 i386_shift_membase(I386_SHR, REG_SP, iptr->dst->regoff * 8);
1940
1941                                         } else {
1942                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1943                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1944                                                 i386_shift_reg(I386_SHR, REG_ITMP1);
1945                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1946                                         }
1947
1948                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1949                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1950                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1951                                         i386_shift_membase(I386_SHR, REG_SP, iptr->dst->regoff * 8);
1952
1953                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1954                                         if (src->prev->regoff == iptr->dst->regoff) {
1955                                                 M_INTMOVE(src->regoff, I386_ECX);
1956                                                 i386_shift_membase(I386_SHR, REG_SP, iptr->dst->regoff * 8);
1957
1958                                         } else {
1959                                                 M_INTMOVE(src->regoff, I386_ECX);
1960                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
1961                                                 i386_shift_reg(I386_SHR, REG_ITMP1);
1962                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
1963                                         }
1964
1965                                 } else {
1966                                         M_INTMOVE(src->regoff, I386_ECX);
1967                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
1968                                         i386_shift_membase(I386_SHR, REG_SP, iptr->dst->regoff * 8);
1969                                 }
1970
1971                         } else {
1972                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1973                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1974                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1975                                         i386_shift_reg(I386_SHR, iptr->dst->regoff);
1976
1977                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
1978                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
1979                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1980                                         i386_shift_reg(I386_SHR, iptr->dst->regoff);
1981
1982                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
1983                                         M_INTMOVE(src->regoff, I386_ECX);
1984                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
1985                                         i386_shift_reg(I386_SHR, iptr->dst->regoff);
1986
1987                                 } else {
1988                                         M_INTMOVE(src->regoff, I386_ECX);
1989                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
1990                                         i386_shift_reg(I386_SHR, iptr->dst->regoff);
1991                                 }
1992                         }
1993                         break;
1994
1995                 case ICMD_IUSHRCONST: /* ..., value  ==> ..., value >>> constant      */
1996                                       /* val.i = constant                             */
1997
1998                         d = reg_of_var(iptr->dst, REG_ITMP1);
1999                         if ((src->flags & INMEMORY) && (iptr->dst->flags & INMEMORY)) {
2000                                 if (src->regoff == iptr->dst->regoff) {
2001                                         i386_shift_imm_membase(I386_SHR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2002
2003                                 } else {
2004                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2005                                         i386_shift_imm_reg(I386_SHR, iptr->val.i, REG_ITMP1);
2006                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2007                                 }
2008
2009                         } else if ((src->flags & INMEMORY) && !(iptr->dst->flags & INMEMORY)) {
2010                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
2011                                 i386_shift_imm_reg(I386_SHR, iptr->val.i, iptr->dst->regoff);
2012                                 
2013                         } else if (!(src->flags & INMEMORY) && (iptr->dst->flags & INMEMORY)) {
2014                                 i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
2015                                 i386_shift_imm_membase(I386_SHR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2016
2017                         } else {
2018                                 M_INTMOVE(src->regoff, iptr->dst->regoff);
2019                                 i386_shift_imm_reg(I386_SHR, iptr->val.i, iptr->dst->regoff);
2020                         }
2021                         break;
2022
2023                 case ICMD_LSHL:       /* ..., val1, val2  ==> ..., val1 << val2       */
2024
2025                         d = reg_of_var(iptr->dst, REG_ITMP1);
2026                         if (iptr->dst->flags & INMEMORY ){
2027                                 if (src->prev->flags & INMEMORY) {
2028                                         if (src->prev->regoff == iptr->dst->regoff) {
2029                                                 if (src->flags & INMEMORY) {
2030                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2031                                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
2032                                                         i386_shld_reg_membase(REG_ITMP1, REG_SP, src->prev->regoff * 8 + 4);
2033                                                         i386_shift_membase(I386_SHL, REG_SP, iptr->dst->regoff * 8);
2034
2035                                                 } else {
2036                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2037                                                         M_INTMOVE(src->regoff, I386_ECX);
2038                                                         i386_shld_reg_membase(REG_ITMP1, REG_SP, src->prev->regoff * 8 + 4);
2039                                                         i386_shift_membase(I386_SHL, REG_SP, iptr->dst->regoff * 8);
2040                                                 }
2041
2042                                         } else {
2043                                                 if (src->flags & INMEMORY) {
2044                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2045                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2046                                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
2047                                                         i386_shld_reg_reg(REG_ITMP1, REG_ITMP2);
2048                                                         i386_shift_reg(I386_SHL, REG_ITMP1);
2049                                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2050                                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2051
2052                                                 } else {
2053                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2054                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2055                                                         M_INTMOVE(src->regoff, I386_ECX);
2056                                                         i386_shld_reg_reg(REG_ITMP1, REG_ITMP2);
2057                                                         i386_shift_reg(I386_SHL, REG_ITMP1);
2058                                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2059                                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2060                                                 }
2061                                         }
2062                                 }
2063                         }
2064                         break;
2065
2066 /*              case ICMD_LSHLCONST:  /* ..., value  ==> ..., value << constant       */
2067 /*                                    /* val.l = constant                             */
2068
2069 /*                      var_to_reg_int(s1, src, REG_ITMP1); */
2070 /*                      d = reg_of_var(iptr->dst, REG_ITMP3); */
2071 /*                      M_SLL_IMM(s1, iptr->val.l & 0x3f, d); */
2072 /*                      store_reg_to_var_int(iptr->dst, d); */
2073 /*                      break; */
2074
2075                 case ICMD_LSHR:       /* ..., val1, val2  ==> ..., val1 >> val2       */
2076
2077                         d = reg_of_var(iptr->dst, REG_ITMP1);
2078                         if (iptr->dst->flags & INMEMORY ){
2079                                 if (src->prev->flags & INMEMORY) {
2080                                         if (src->prev->regoff == iptr->dst->regoff) {
2081                                                 if (src->flags & INMEMORY) {
2082                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2083                                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
2084                                                         i386_shrd_reg_membase(REG_ITMP1, REG_SP, src->prev->regoff * 8 + 4);
2085                                                         i386_shift_membase(I386_SAR, REG_SP, iptr->dst->regoff * 8);
2086
2087                                                 } else {
2088                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2089                                                         M_INTMOVE(src->regoff, I386_ECX);
2090                                                         i386_shrd_reg_membase(REG_ITMP1, REG_SP, src->prev->regoff * 8 + 4);
2091                                                         i386_shift_membase(I386_SAR, REG_SP, iptr->dst->regoff * 8);
2092                                                 }
2093
2094                                         } else {
2095                                                 if (src->flags & INMEMORY) {
2096                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2097                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2098                                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
2099                                                         i386_shrd_reg_reg(REG_ITMP1, REG_ITMP2);
2100                                                         i386_shift_reg(I386_SAR, REG_ITMP1);
2101                                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2102                                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2103
2104                                                 } else {
2105                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2106                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2107                                                         M_INTMOVE(src->regoff, I386_ECX);
2108                                                         i386_shrd_reg_reg(REG_ITMP1, REG_ITMP2);
2109                                                         i386_shift_reg(I386_SAR, REG_ITMP1);
2110                                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2111                                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2112                                                 }
2113                                         }
2114                                 }
2115                         }
2116                         break;
2117
2118 /*              case ICMD_LSHRCONST:  /* ..., value  ==> ..., value >> constant       */
2119 /*                                    /* val.l = constant                             */
2120
2121 /*                      var_to_reg_int(s1, src, REG_ITMP1); */
2122 /*                      d = reg_of_var(iptr->dst, REG_ITMP3); */
2123 /*                      M_SRA_IMM(s1, iptr->val.l & 0x3f, d); */
2124 /*                      store_reg_to_var_int(iptr->dst, d); */
2125 /*                      break; */
2126
2127                 case ICMD_LUSHR:      /* ..., val1, val2  ==> ..., val1 >>> val2      */
2128
2129                         d = reg_of_var(iptr->dst, REG_ITMP1);
2130                         if (iptr->dst->flags & INMEMORY ){
2131                                 if (src->prev->flags & INMEMORY) {
2132                                         if (src->prev->regoff == iptr->dst->regoff) {
2133                                                 if (src->flags & INMEMORY) {
2134                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2135                                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
2136                                                         i386_shrd_reg_membase(REG_ITMP1, REG_SP, src->prev->regoff * 8 + 4);
2137                                                         i386_shift_membase(I386_SHR, REG_SP, iptr->dst->regoff * 8);
2138
2139                                                 } else {
2140                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2141                                                         M_INTMOVE(src->regoff, I386_ECX);
2142                                                         i386_shrd_reg_membase(REG_ITMP1, REG_SP, src->prev->regoff * 8 + 4);
2143                                                         i386_shift_membase(I386_SHR, REG_SP, iptr->dst->regoff * 8);
2144                                                 }
2145
2146                                         } else {
2147                                                 if (src->flags & INMEMORY) {
2148                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2149                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2150                                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, I386_ECX);
2151                                                         i386_shrd_reg_reg(REG_ITMP1, REG_ITMP2);
2152                                                         i386_shift_reg(I386_SHR, REG_ITMP1);
2153                                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2154                                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2155
2156                                                 } else {
2157                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2158                                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2159                                                         M_INTMOVE(src->regoff, I386_ECX);
2160                                                         i386_shrd_reg_reg(REG_ITMP1, REG_ITMP2);
2161                                                         i386_shift_reg(I386_SHR, REG_ITMP1);
2162                                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2163                                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2164                                                 }
2165                                         }
2166                                 }
2167                         }
2168                         break;
2169
2170 /*              case ICMD_LUSHRCONST: /* ..., value  ==> ..., value >>> constant      */
2171 /*                                    /* val.l = constant                             */
2172
2173 /*                      var_to_reg_int(s1, src, REG_ITMP1); */
2174 /*                      d = reg_of_var(iptr->dst, REG_ITMP3); */
2175 /*                      M_SRL_IMM(s1, iptr->val.l & 0x3f, d); */
2176 /*                      store_reg_to_var_int(iptr->dst, d); */
2177 /*                      break; */
2178
2179                 case ICMD_IAND:       /* ..., val1, val2  ==> ..., val1 & val2        */
2180
2181                         d = reg_of_var(iptr->dst, REG_ITMP1);
2182                         if (iptr->dst->flags & INMEMORY) {
2183                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2184                                         if (src->regoff == iptr->dst->regoff) {
2185                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2186                                                 i386_alu_reg_membase(I386_AND, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2187
2188                                         } else if (src->prev->regoff == iptr->dst->regoff) {
2189                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2190                                                 i386_alu_reg_membase(I386_AND, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2191
2192                                         } else {
2193                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2194                                                 i386_alu_membase_reg(I386_AND, REG_SP, src->regoff * 8, REG_ITMP1);
2195                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2196                                         }
2197
2198                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
2199                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2200                                         i386_alu_reg_reg(I386_AND, src->prev->regoff, REG_ITMP1);
2201                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2202
2203                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2204                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2205                                         i386_alu_reg_reg(I386_AND, src->regoff, REG_ITMP1);
2206                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2207
2208                                 } else {
2209                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
2210                                         i386_alu_reg_membase(I386_AND, src->regoff, REG_SP, iptr->dst->regoff * 8);
2211                                 }
2212
2213                         } else {
2214                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2215                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
2216                                         i386_alu_membase_reg(I386_AND, REG_SP, src->regoff * 8, iptr->dst->regoff);
2217
2218                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
2219                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
2220                                         i386_alu_membase_reg(I386_AND, REG_SP, src->regoff * 8, iptr->dst->regoff);
2221
2222                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2223                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
2224                                         i386_alu_membase_reg(I386_AND, REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
2225
2226                                 } else {
2227                                         if (src->regoff == iptr->dst->regoff) {
2228                                                 i386_alu_reg_reg(I386_AND, src->prev->regoff, iptr->dst->regoff);
2229
2230                                         } else {
2231                                                 M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
2232                                                 i386_alu_reg_reg(I386_AND, src->regoff, iptr->dst->regoff);
2233                                         }
2234                                 }
2235                         }
2236                         break;
2237
2238                 case ICMD_IANDCONST:  /* ..., value  ==> ..., value & constant        */
2239                                       /* val.i = constant                             */
2240
2241                         d = reg_of_var(iptr->dst, REG_ITMP1);
2242                         if (iptr->dst->flags & INMEMORY) {
2243                                 if (src->flags & INMEMORY) {
2244                                         if (src->regoff == iptr->dst->regoff) {
2245                                                 i386_alu_imm_membase(I386_AND, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2246
2247                                         } else {
2248                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2249                                                 i386_alu_imm_reg(I386_AND, iptr->val.i, REG_ITMP1);
2250                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2251                                         }
2252
2253                                 } else {
2254                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
2255                                         i386_alu_imm_membase(I386_AND, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2256                                 }
2257
2258                         } else {
2259                                 if (src->flags & INMEMORY) {
2260                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
2261                                         i386_alu_imm_reg(I386_AND, iptr->val.i, iptr->dst->regoff);
2262
2263                                 } else {
2264                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
2265                                         i386_alu_imm_reg(I386_AND, iptr->val.i, iptr->dst->regoff);
2266                                 }
2267                         }
2268                         break;
2269
2270                 case ICMD_LAND:       /* ..., val1, val2  ==> ..., val1 & val2        */
2271
2272                         d = reg_of_var(iptr->dst, REG_ITMP1);
2273                         if (iptr->dst->flags & INMEMORY) {
2274                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2275                                         if (src->regoff == iptr->dst->regoff) {
2276                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2277                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2278                                                 i386_alu_reg_membase(I386_AND, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2279                                                 i386_alu_reg_membase(I386_AND, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2280
2281                                         } else if (src->prev->regoff == iptr->dst->regoff) {
2282                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2283                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2284                                                 i386_alu_reg_membase(I386_AND, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2285                                                 i386_alu_reg_membase(I386_AND, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2286
2287                                         } else {
2288                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2289                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2290                                                 i386_alu_membase_reg(I386_AND, REG_SP, src->regoff * 8, REG_ITMP1);
2291                                                 i386_alu_membase_reg(I386_AND, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2292                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2293                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2294                                         }
2295                                 }
2296                         }
2297                         break;
2298
2299                 case ICMD_LANDCONST:  /* ..., value  ==> ..., value & constant        */
2300                                       /* val.l = constant                             */
2301
2302                         d = reg_of_var(iptr->dst, REG_ITMP1);
2303                         if (iptr->dst->flags & INMEMORY) {
2304                                 if (src->flags & INMEMORY) {
2305                                         if (src->regoff == iptr->dst->regoff) {
2306                                                 i386_alu_imm_membase(I386_AND, iptr->val.l, REG_SP, iptr->dst->regoff * 8);
2307                                                 i386_alu_imm_membase(I386_AND, iptr->val.l >> 32, REG_SP, iptr->dst->regoff * 8 + 4);
2308
2309                                         } else {
2310                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2311                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2312                                                 i386_alu_imm_reg(I386_AND, iptr->val.l, REG_ITMP1);
2313                                                 i386_alu_imm_reg(I386_AND, iptr->val.l >> 32, REG_ITMP2);
2314                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2315                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2316                                         }
2317                                 }
2318                         }
2319                         break;
2320
2321                 case ICMD_IREMPOW2:   /* ..., value  ==> ..., value % constant        */
2322                                       /* val.i = constant                             */
2323
2324                         /* TWISTI */
2325 /*                      var_to_reg_int(s1, src, REG_ITMP1); */
2326 /*                      d = reg_of_var(iptr->dst, REG_ITMP3); */
2327 /*                      if (s1 == d) { */
2328 /*                              M_MOV(s1, REG_ITMP1); */
2329 /*                              s1 = REG_ITMP1; */
2330 /*                              } */
2331 /*                      if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) { */
2332 /*                              M_AND_IMM(s1, iptr->val.i, d); */
2333 /*                              M_BGEZ(s1, 3); */
2334 /*                              M_ISUB(REG_ZERO, s1, d); */
2335 /*                              M_AND_IMM(d, iptr->val.i, d); */
2336 /*                              } */
2337 /*                      else if (iptr->val.i == 0xffff) { */
2338 /*                              M_CZEXT(s1, d); */
2339 /*                              M_BGEZ(s1, 3); */
2340 /*                              M_ISUB(REG_ZERO, s1, d); */
2341 /*                              M_CZEXT(d, d); */
2342 /*                              } */
2343 /*                      else if (iptr->val.i == 0xffffff) { */
2344 /*                              M_ZAPNOT_IMM(s1, 0x07, d); */
2345 /*                              M_BGEZ(s1, 3); */
2346 /*                              M_ISUB(REG_ZERO, s1, d); */
2347 /*                              M_ZAPNOT_IMM(d, 0x07, d); */
2348 /*                              } */
2349 /*                      else { */
2350 /*  /*                                  ICONST(REG_ITMP2, iptr->val.i); */
2351 /*                              M_AND(s1, REG_ITMP2, d); */
2352 /*                              M_BGEZ(s1, 3); */
2353 /*                              M_ISUB(REG_ZERO, s1, d); */
2354 /*                              M_AND(d, REG_ITMP2, d); */
2355 /*                              } */
2356 /*                      M_ISUB(REG_ZERO, d, d); */
2357 /*                      store_reg_to_var_int(iptr->dst, d); */
2358 /*                      break; */
2359                         var_to_reg_int(s1, src, REG_ITMP1);
2360                         d = reg_of_var(iptr->dst, REG_ITMP3);
2361                         if (s1 == d) {
2362                                 M_MOV(s1, REG_ITMP1);
2363                                 s1 = REG_ITMP1;
2364
2365                         } 
2366
2367                         /* TODO: optimize and/or calc jump offset for AND value */
2368 /*                      M_INTMOVE(s1, d); */
2369 /*                      i386_alu_imm_reg(I386_AND, iptr->val.i, d); */
2370 /*                      i386_alu_imm_reg(I386_CMP, 0, s1); */
2371 /*                      i386_jcc(I386_CC_GE, 2 + 2 + 6 + 2);     */
2372 /*                      M_INTMOVE(s1, d); */
2373 /*                      i386_neg_reg(d); */
2374 /*                      i386_alu_imm_reg(I386_AND, iptr->val.i, d); */
2375 /*                      i386_neg_reg(d); */
2376
2377                         /* TODO: optimize */
2378                         M_INTMOVE(s1, I386_EAX);
2379                         i386_cltd();
2380                         i386_alu_reg_reg(I386_XOR, I386_EDX, I386_EAX);
2381                         i386_alu_reg_reg(I386_SUB, I386_EDX, I386_EAX);
2382                         i386_alu_reg_reg(I386_AND, iptr->val.i, I386_EAX);
2383                         i386_alu_reg_reg(I386_XOR, I386_EDX, I386_EAX);
2384                         i386_alu_reg_reg(I386_SUB, I386_EDX, I386_EAX);
2385                         M_INTMOVE(I386_EAX, d);
2386
2387                         store_reg_to_var_int(iptr->dst, d);
2388                         break;
2389
2390                 case ICMD_IREM0X10001:  /* ..., value  ==> ..., value % 0x100001      */
2391                 
2392 /*          b = value & 0xffff;
2393                         a = value >> 16;
2394                         a = ((b - a) & 0xffff) + (b < a);
2395 */
2396
2397                         var_to_reg_int(s1, src, REG_ITMP1);
2398                         d = reg_of_var(iptr->dst, REG_ITMP3);
2399                         if (s1 == d) {
2400                                 M_MOV(s1, REG_ITMP3);
2401                                 s1 = REG_ITMP3;
2402                                 }
2403                         M_BLTZ(s1, 7);
2404             M_CZEXT(s1, REG_ITMP2);
2405                         M_SRA_IMM(s1, 16, d);
2406                         M_CMPLT(REG_ITMP2, d, REG_ITMP1);
2407                         M_ISUB(REG_ITMP2, d, d);
2408             M_CZEXT(d, d);
2409                         M_IADD(d, REG_ITMP1, d);
2410                         M_BR(11 + (s1 == REG_ITMP1));
2411                         M_ISUB(REG_ZERO, s1, REG_ITMP1);
2412             M_CZEXT(REG_ITMP1, REG_ITMP2);
2413                         M_SRA_IMM(REG_ITMP1, 16, d);
2414                         M_CMPLT(REG_ITMP2, d, REG_ITMP1);
2415                         M_ISUB(REG_ITMP2, d, d);
2416             M_CZEXT(d, d);
2417                         M_IADD(d, REG_ITMP1, d);
2418                         M_ISUB(REG_ZERO, d, d);
2419                         if (s1 == REG_ITMP1) {
2420                                 var_to_reg_int(s1, src, REG_ITMP1);
2421                                 }
2422                         M_SLL_IMM(s1, 33, REG_ITMP2);
2423                         M_CMPEQ(REG_ITMP2, REG_ZERO, REG_ITMP2);
2424                         M_ISUB(d, REG_ITMP2, d);
2425                         store_reg_to_var_int(iptr->dst, d);
2426                         break;
2427
2428                 case ICMD_LREMPOW2:   /* ..., value  ==> ..., value % constant        */
2429                                       /* val.l = constant                             */
2430
2431                         var_to_reg_int(s1, src, REG_ITMP1);
2432                         d = reg_of_var(iptr->dst, REG_ITMP3);
2433                         if (s1 == d) {
2434                                 M_MOV(s1, REG_ITMP1);
2435                                 s1 = REG_ITMP1;
2436                                 }
2437                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
2438                                 M_AND_IMM(s1, iptr->val.l, d);
2439                                 M_BGEZ(s1, 3);
2440                                 M_LSUB(REG_ZERO, s1, d);
2441                                 M_AND_IMM(d, iptr->val.l, d);
2442                                 }
2443                         else if (iptr->val.l == 0xffffL) {
2444                                 M_CZEXT(s1, d);
2445                                 M_BGEZ(s1, 3);
2446                                 M_LSUB(REG_ZERO, s1, d);
2447                                 M_CZEXT(d, d);
2448                                 }
2449                         else if (iptr->val.l == 0xffffffL) {
2450                                 M_ZAPNOT_IMM(s1, 0x07, d);
2451                                 M_BGEZ(s1, 3);
2452                                 M_LSUB(REG_ZERO, s1, d);
2453                                 M_ZAPNOT_IMM(d, 0x07, d);
2454                                 }
2455                         else if (iptr->val.l == 0xffffffffL) {
2456                                 M_IZEXT(s1, d);
2457                                 M_BGEZ(s1, 3);
2458                                 M_LSUB(REG_ZERO, s1, d);
2459                                 M_IZEXT(d, d);
2460                                 }
2461                         else if (iptr->val.l == 0xffffffffffL) {
2462                                 M_ZAPNOT_IMM(s1, 0x1f, d);
2463                                 M_BGEZ(s1, 3);
2464                                 M_LSUB(REG_ZERO, s1, d);
2465                                 M_ZAPNOT_IMM(d, 0x1f, d);
2466                                 }
2467                         else if (iptr->val.l == 0xffffffffffffL) {
2468                                 M_ZAPNOT_IMM(s1, 0x3f, d);
2469                                 M_BGEZ(s1, 3);
2470                                 M_LSUB(REG_ZERO, s1, d);
2471                                 M_ZAPNOT_IMM(d, 0x3f, d);
2472                                 }
2473                         else if (iptr->val.l == 0xffffffffffffffL) {
2474                                 M_ZAPNOT_IMM(s1, 0x7f, d);
2475                                 M_BGEZ(s1, 3);
2476                                 M_LSUB(REG_ZERO, s1, d);
2477                                 M_ZAPNOT_IMM(d, 0x7f, d);
2478                                 }
2479                         else {
2480 /*                              LCONST(REG_ITMP2, iptr->val.l); */
2481                                 M_AND(s1, REG_ITMP2, d);
2482                                 M_BGEZ(s1, 3);
2483                                 M_LSUB(REG_ZERO, s1, d);
2484                                 M_AND(d, REG_ITMP2, d);
2485                                 }
2486                         M_LSUB(REG_ZERO, d, d);
2487                         store_reg_to_var_int(iptr->dst, d);
2488                         break;
2489
2490                 case ICMD_LREM0X10001:/* ..., value  ==> ..., value % 0x10001         */
2491
2492                         var_to_reg_int(s1, src, REG_ITMP1);
2493                         d = reg_of_var(iptr->dst, REG_ITMP3);
2494                         if (s1 == d) {
2495                                 M_MOV(s1, REG_ITMP3);
2496                                 s1 = REG_ITMP3;
2497                                 }
2498                         M_CZEXT(s1, REG_ITMP2);
2499                         M_SRA_IMM(s1, 16, d);
2500                         M_CMPLT(REG_ITMP2, d, REG_ITMP1);
2501                         M_LSUB(REG_ITMP2, d, d);
2502             M_CZEXT(d, d);
2503                         M_LADD(d, REG_ITMP1, d);
2504                         M_LDA(REG_ITMP2, REG_ZERO, -1);
2505                         M_SRL_IMM(REG_ITMP2, 33, REG_ITMP2);
2506                         if (s1 == REG_ITMP1) {
2507                                 var_to_reg_int(s1, src, REG_ITMP1);
2508                                 }
2509                         M_CMPULT(s1, REG_ITMP2, REG_ITMP2);
2510                         M_BNEZ(REG_ITMP2, 11);
2511                         M_LDA(d, REG_ZERO, -257);
2512                         M_ZAPNOT_IMM(d, 0xcd, d);
2513                         M_LSUB(REG_ZERO, s1, REG_ITMP2);
2514                         M_CMOVGE(s1, s1, REG_ITMP2);
2515                         M_UMULH(REG_ITMP2, d, REG_ITMP2);
2516                         M_SRL_IMM(REG_ITMP2, 16, REG_ITMP2);
2517                         M_LSUB(REG_ZERO, REG_ITMP2, d);
2518                         M_CMOVGE(s1, REG_ITMP2, d);
2519                         M_SLL_IMM(d, 16, REG_ITMP2);
2520                         M_LADD(d, REG_ITMP2, d);
2521                         M_LSUB(s1, d, d);
2522                         store_reg_to_var_int(iptr->dst, d);
2523                         break;
2524
2525                 case ICMD_IOR:        /* ..., val1, val2  ==> ..., val1 | val2        */
2526
2527                         d = reg_of_var(iptr->dst, REG_ITMP1);
2528                         if (iptr->dst->flags & INMEMORY) {
2529                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2530                                         if (src->regoff == iptr->dst->regoff) {
2531                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2532                                                 i386_alu_reg_membase(I386_OR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2533
2534                                         } else if (src->prev->regoff == iptr->dst->regoff) {
2535                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2536                                                 i386_alu_reg_membase(I386_OR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2537
2538                                         } else {
2539                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2540                                                 i386_alu_membase_reg(I386_OR, REG_SP, src->regoff * 8, REG_ITMP1);
2541                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2542                                         }
2543
2544                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
2545                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2546                                         i386_alu_reg_reg(I386_OR, src->prev->regoff, REG_ITMP1);
2547                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2548
2549                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2550                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2551                                         i386_alu_reg_reg(I386_OR, src->regoff, REG_ITMP1);
2552                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2553
2554                                 } else {
2555                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
2556                                         i386_alu_reg_membase(I386_OR, src->regoff, REG_SP, iptr->dst->regoff * 8);
2557                                 }
2558
2559                         } else {
2560                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2561                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
2562                                         i386_alu_membase_reg(I386_OR, REG_SP, src->regoff * 8, iptr->dst->regoff);
2563
2564                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
2565                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
2566                                         i386_alu_membase_reg(I386_OR, REG_SP, src->regoff * 8, iptr->dst->regoff);
2567
2568                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2569                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
2570                                         i386_alu_membase_reg(I386_OR, REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
2571
2572                                 } else {
2573                                         if (src->regoff == iptr->dst->regoff) {
2574                                                 i386_alu_reg_reg(I386_OR, src->prev->regoff, iptr->dst->regoff);
2575
2576                                         } else {
2577                                                 M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
2578                                                 i386_alu_reg_reg(I386_OR, src->regoff, iptr->dst->regoff);
2579                                         }
2580                                 }
2581                         }
2582                         break;
2583
2584                 case ICMD_IORCONST:   /* ..., value  ==> ..., value | constant        */
2585                                       /* val.i = constant                             */
2586
2587                         d = reg_of_var(iptr->dst, REG_ITMP1);
2588                         if (iptr->dst->flags & INMEMORY) {
2589                                 if (src->flags & INMEMORY) {
2590                                         if (src->regoff == iptr->dst->regoff) {
2591                                                 i386_alu_imm_membase(I386_OR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2592
2593                                         } else {
2594                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2595                                                 i386_alu_imm_reg(I386_OR, iptr->val.i, REG_ITMP1);
2596                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2597                                         }
2598
2599                                 } else {
2600                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
2601                                         i386_alu_imm_membase(I386_OR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2602                                 }
2603
2604                         } else {
2605                                 if (src->flags & INMEMORY) {
2606                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
2607                                         i386_alu_imm_reg(I386_OR, iptr->val.i, iptr->dst->regoff);
2608
2609                                 } else {
2610                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
2611                                         i386_alu_imm_reg(I386_OR, iptr->val.i, iptr->dst->regoff);
2612                                 }
2613                         }
2614                         break;
2615
2616                 case ICMD_LOR:        /* ..., val1, val2  ==> ..., val1 | val2        */
2617
2618                         d = reg_of_var(iptr->dst, REG_ITMP1);
2619                         if (iptr->dst->flags & INMEMORY) {
2620                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2621                                         if (src->regoff == iptr->dst->regoff) {
2622                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2623                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2624                                                 i386_alu_reg_membase(I386_OR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2625                                                 i386_alu_reg_membase(I386_OR, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2626
2627                                         } else if (src->prev->regoff == iptr->dst->regoff) {
2628                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2629                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2630                                                 i386_alu_reg_membase(I386_OR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2631                                                 i386_alu_reg_membase(I386_OR, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2632
2633                                         } else {
2634                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2635                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2636                                                 i386_alu_membase_reg(I386_OR, REG_SP, src->regoff * 8, REG_ITMP1);
2637                                                 i386_alu_membase_reg(I386_OR, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2638                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2639                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2640                                         }
2641                                 }
2642                         }
2643                         break;
2644
2645                 case ICMD_LORCONST:   /* ..., value  ==> ..., value | constant        */
2646                                       /* val.l = constant                             */
2647
2648                         d = reg_of_var(iptr->dst, REG_ITMP1);
2649                         if (iptr->dst->flags & INMEMORY) {
2650                                 if (src->flags & INMEMORY) {
2651                                         if (src->regoff == iptr->dst->regoff) {
2652                                                 i386_alu_imm_membase(I386_OR, iptr->val.l, REG_SP, iptr->dst->regoff * 8);
2653                                                 i386_alu_imm_membase(I386_OR, iptr->val.l >> 32, REG_SP, iptr->dst->regoff * 8 + 4);
2654
2655                                         } else {
2656                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2657                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2658                                                 i386_alu_imm_reg(I386_OR, iptr->val.l, REG_ITMP1);
2659                                                 i386_alu_imm_reg(I386_OR, iptr->val.l >> 32, REG_ITMP2);
2660                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2661                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2662                                         }
2663                                 }
2664                         }
2665                         break;
2666
2667                 case ICMD_IXOR:       /* ..., val1, val2  ==> ..., val1 ^ val2        */
2668
2669                         d = reg_of_var(iptr->dst, REG_ITMP1);
2670                         if (iptr->dst->flags & INMEMORY) {
2671                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2672                                         if (src->regoff == iptr->dst->regoff) {
2673                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2674                                                 i386_alu_reg_membase(I386_XOR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2675
2676                                         } else if (src->prev->regoff == iptr->dst->regoff) {
2677                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2678                                                 i386_alu_reg_membase(I386_XOR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2679
2680                                         } else {
2681                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2682                                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8, REG_ITMP1);
2683                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2684                                         }
2685
2686                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
2687                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2688                                         i386_alu_reg_reg(I386_XOR, src->prev->regoff, REG_ITMP1);
2689                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2690
2691                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2692                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2693                                         i386_alu_reg_reg(I386_XOR, src->regoff, REG_ITMP1);
2694                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2695
2696                                 } else {
2697                                         i386_mov_reg_membase(src->prev->regoff, REG_SP, iptr->dst->regoff * 8);
2698                                         i386_alu_reg_membase(I386_XOR, src->regoff, REG_SP, iptr->dst->regoff * 8);
2699                                 }
2700
2701                         } else {
2702                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2703                                         i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
2704                                         i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8, iptr->dst->regoff);
2705
2706                                 } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
2707                                         M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
2708                                         i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8, iptr->dst->regoff);
2709
2710                                 } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2711                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
2712                                         i386_alu_membase_reg(I386_XOR, REG_SP, src->prev->regoff * 8, iptr->dst->regoff);
2713
2714                                 } else {
2715                                         if (src->regoff == iptr->dst->regoff) {
2716                                                 i386_alu_reg_reg(I386_XOR, src->prev->regoff, iptr->dst->regoff);
2717
2718                                         } else {
2719                                                 M_INTMOVE(src->prev->regoff, iptr->dst->regoff);
2720                                                 i386_alu_reg_reg(I386_XOR, src->regoff, iptr->dst->regoff);
2721                                         }
2722                                 }
2723                         }
2724                         break;
2725
2726                 case ICMD_IXORCONST:  /* ..., value  ==> ..., value ^ constant        */
2727                                       /* val.i = constant                             */
2728
2729                         d = reg_of_var(iptr->dst, REG_ITMP1);
2730                         if (iptr->dst->flags & INMEMORY) {
2731                                 if (src->flags & INMEMORY) {
2732                                         if (src->regoff == iptr->dst->regoff) {
2733                                                 i386_alu_imm_membase(I386_XOR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2734
2735                                         } else {
2736                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2737                                                 i386_alu_imm_reg(I386_XOR, iptr->val.i, REG_ITMP1);
2738                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2739                                         }
2740
2741                                 } else {
2742                                         i386_mov_reg_membase(src->regoff, REG_SP, iptr->dst->regoff * 8);
2743                                         i386_alu_imm_membase(I386_XOR, iptr->val.i, REG_SP, iptr->dst->regoff * 8);
2744                                 }
2745
2746                         } else {
2747                                 if (src->flags & INMEMORY) {
2748                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, iptr->dst->regoff);
2749                                         i386_alu_imm_reg(I386_XOR, iptr->val.i, iptr->dst->regoff);
2750
2751                                 } else {
2752                                         M_INTMOVE(src->regoff, iptr->dst->regoff);
2753                                         i386_alu_imm_reg(I386_XOR, iptr->val.i, iptr->dst->regoff);
2754                                 }
2755                         }
2756                         break;
2757
2758                 case ICMD_LXOR:       /* ..., val1, val2  ==> ..., val1 ^ val2        */
2759
2760                         d = reg_of_var(iptr->dst, REG_ITMP1);
2761                         if (iptr->dst->flags & INMEMORY) {
2762                                 if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
2763                                         if (src->regoff == iptr->dst->regoff) {
2764                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2765                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2766                                                 i386_alu_reg_membase(I386_XOR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2767                                                 i386_alu_reg_membase(I386_XOR, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2768
2769                                         } else if (src->prev->regoff == iptr->dst->regoff) {
2770                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2771                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2772                                                 i386_alu_reg_membase(I386_XOR, REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2773                                                 i386_alu_reg_membase(I386_XOR, REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2774
2775                                         } else {
2776                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
2777                                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
2778                                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8, REG_ITMP1);
2779                                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2780                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2781                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2782                                         }
2783                                 }
2784                         }
2785                         break;
2786
2787                 case ICMD_LXORCONST:  /* ..., value  ==> ..., value ^ constant        */
2788                                       /* val.l = constant                             */
2789
2790                         d = reg_of_var(iptr->dst, REG_ITMP1);
2791                         if (iptr->dst->flags & INMEMORY) {
2792                                 if (src->flags & INMEMORY) {
2793                                         if (src->regoff == iptr->dst->regoff) {
2794                                                 i386_alu_imm_membase(I386_XOR, iptr->val.l, REG_SP, iptr->dst->regoff * 8);
2795                                                 i386_alu_imm_membase(I386_XOR, iptr->val.l >> 32, REG_SP, iptr->dst->regoff * 8 + 4);
2796
2797                                         } else {
2798                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
2799                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
2800                                                 i386_alu_imm_reg(I386_XOR, iptr->val.l, REG_ITMP1);
2801                                                 i386_alu_imm_reg(I386_XOR, iptr->val.l >> 32, REG_ITMP2);
2802                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, iptr->dst->regoff * 8);
2803                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8 + 4);
2804                                         }
2805                                 }
2806                         }
2807                         break;
2808
2809
2810                 case ICMD_LCMP:       /* ..., val1, val2  ==> ..., val1 cmp val2      */
2811
2812                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2813                         var_to_reg_int(s2, src, REG_ITMP2);
2814                         d = reg_of_var(iptr->dst, REG_ITMP3);
2815                         M_CMPLT(s1, s2, REG_ITMP3);
2816                         M_CMPLT(s2, s1, REG_ITMP1);
2817                         M_LSUB (REG_ITMP1, REG_ITMP3, d);
2818                         store_reg_to_var_int(iptr->dst, d);
2819                         break;
2820
2821                 case ICMD_IINC:       /* ..., value  ==> ..., value + constant        */
2822                                       /* op1 = variable, val.i = constant             */
2823
2824                         var = &(locals[iptr->op1][TYPE_INT]);
2825                         if (var->flags & INMEMORY) {
2826                                 if (iptr->val.i == 1) {
2827                                         i386_inc_membase(REG_SP, var->regoff * 8);
2828  
2829                                 } else if (iptr->val.i == -1) {
2830                                         i386_dec_membase(REG_SP, var->regoff * 8);
2831
2832                                 } else {
2833                                         i386_alu_imm_membase(I386_ADD, iptr->val.i, REG_SP, var->regoff * 8);
2834                                 }
2835
2836                         } else {
2837                                 if (iptr->val.i == 1) {
2838                                         i386_inc_reg(var->regoff);
2839  
2840                                 } else if (iptr->val.i == -1) {
2841                                         i386_dec_reg(var->regoff);
2842
2843                                 } else {
2844                                         i386_alu_imm_reg(I386_ADD, iptr->val.i, var->regoff);
2845                                 }
2846                         }
2847                         break;
2848
2849
2850                 /* floating operations ************************************************/
2851
2852                 case ICMD_FNEG:       /* ..., value  ==> ..., - value                 */
2853                 case ICMD_DNEG:       /* ..., value  ==> ..., - value                 */
2854
2855                         d = reg_of_var(iptr->dst, REG_FTMP3);
2856                         i386_fchs();
2857                         store_reg_to_var_flt(iptr->dst, d);
2858                         break;
2859
2860                 case ICMD_FADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
2861                 case ICMD_DADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
2862
2863                         d = reg_of_var(iptr->dst, REG_FTMP3);
2864                         i386_faddp();
2865                         store_reg_to_var_flt(iptr->dst, d);
2866                         break;
2867
2868                 case ICMD_FSUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
2869                 case ICMD_DSUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
2870
2871                         d = reg_of_var(iptr->dst, REG_FTMP3);
2872                         i386_fsubp();
2873                         store_reg_to_var_flt(iptr->dst, d);
2874                         break;
2875
2876                 case ICMD_FMUL:       /* ..., val1, val2  ==> ..., val1 * val2        */
2877                 case ICMD_DMUL:       /* ..., val1, val2  ==> ..., val1 * val2        */
2878
2879                         d = reg_of_var(iptr->dst, REG_FTMP3);
2880                         i386_fmulp();
2881                         store_reg_to_var_flt(iptr->dst, d);
2882                         break;
2883
2884                 case ICMD_FDIV:       /* ..., val1, val2  ==> ..., val1 / val2        */
2885                 case ICMD_DDIV:       /* ..., val1, val2  ==> ..., val1 / val2        */
2886
2887                         d = reg_of_var(iptr->dst, REG_FTMP3);
2888                         i386_fdivp();
2889                         store_reg_to_var_flt(iptr->dst, d);
2890                         break;
2891
2892                 case ICMD_FREM:       /* ..., val1, val2  ==> ..., val1 % val2        */
2893                 case ICMD_DREM:       /* ..., val1, val2  ==> ..., val1 % val2        */
2894
2895                         d = reg_of_var(iptr->dst, REG_FTMP3);
2896                         i386_fprem1();
2897                         store_reg_to_var_flt(iptr->dst, d);
2898                         break;
2899
2900                 case ICMD_I2F:       /* ..., value  ==> ..., (float) value            */
2901                 case ICMD_I2D:       /* ..., value  ==> ..., (double) value           */
2902
2903                         d = reg_of_var(iptr->dst, REG_FTMP1);
2904                         if (src->flags & INMEMORY) {
2905                                 i386_fildl_membase(REG_SP, src->regoff * 8);
2906
2907                         } else {
2908                                 a = dseg_adds4(0);
2909                                 i386_mov_imm_reg(0, REG_ITMP1);
2910                                 dseg_adddata(mcodeptr);
2911                                 i386_mov_reg_membase(src->regoff, REG_ITMP1, a);
2912                                 i386_fildl_membase(REG_ITMP1, a);
2913                         }
2914                         store_reg_to_var_flt(iptr->dst, d);
2915                         break;
2916
2917                 case ICMD_L2F:       /* ..., value  ==> ..., (float) value            */
2918                 case ICMD_L2D:       /* ..., value  ==> ..., (double) value           */
2919
2920                         d = reg_of_var(iptr->dst, REG_FTMP1);
2921                         if (src->flags & INMEMORY) {
2922                                 i386_fildll_membase(REG_SP, src->regoff * 8);
2923                         } else {
2924                                 panic("longs have to be in memory");
2925                         }
2926                         store_reg_to_var_flt(iptr->dst, d);
2927                         break;
2928                         
2929                 case ICMD_F2I:       /* ..., value  ==> ..., (int) value              */
2930                 case ICMD_D2I:
2931
2932                         d = reg_of_var(iptr->dst, REG_ITMP1);
2933                         if (iptr->dst->flags & INMEMORY) {
2934                                 i386_fistl_membase(REG_SP, iptr->dst->regoff * 8);
2935
2936                         } else {
2937                                 a = dseg_adds4(0);
2938                                 i386_mov_imm_reg(0, REG_ITMP1);
2939                                 dseg_adddata(mcodeptr);
2940                                 i386_fistpl_membase(REG_ITMP1, a);
2941                                 i386_mov_membase_reg(REG_ITMP1, a, iptr->dst->regoff);
2942                         }
2943                         break;
2944
2945                 case ICMD_F2L:       /* ..., value  ==> ..., (long) value             */
2946                 case ICMD_D2L:
2947
2948                         d = reg_of_var(iptr->dst, REG_ITMP1);
2949                         if (iptr->dst->flags & INMEMORY) {
2950                                 i386_fistpll_membase(REG_SP, iptr->dst->regoff * 8);
2951
2952                         } else {
2953                                 panic("longs have to be in memory");
2954                         }
2955                         break;
2956
2957                 case ICMD_F2D:       /* ..., value  ==> ..., (double) value           */
2958
2959                         /* nothing to do */
2960                         break;
2961
2962                 case ICMD_D2F:       /* ..., value  ==> ..., (float) value            */
2963
2964                         /* nothing to do */
2965                         break;
2966
2967                 case ICMD_FCMPL:      /* ..., val1, val2  ==> ..., val1 fcmpl val2    */
2968                 case ICMD_DCMPL:
2969
2970                         d = reg_of_var(iptr->dst, REG_ITMP3);
2971                         i386_alu_reg_reg(I386_XOR, d, d);
2972                         i386_fucom();
2973                         i386_fnstsw();
2974                         i386_sahf();
2975                         i386_jcc(I386_CC_E, 6 + 1 + 5 + 1);
2976                         i386_jcc(I386_CC_B, 1 + 5);
2977                         i386_dec_reg(d);
2978                         i386_jmp(1);
2979                         i386_inc_reg(d);
2980                         store_reg_to_var_int(iptr->dst, d);
2981                         break;
2982
2983                 case ICMD_FCMPG:      /* ..., val1, val2  ==> ..., val1 fcmpg val2    */
2984                 case ICMD_DCMPG:
2985
2986                         d = reg_of_var(iptr->dst, REG_ITMP3);
2987                         i386_alu_reg_reg(I386_XOR, d, d);
2988                         i386_fucom();
2989                         i386_fnstsw();
2990                         i386_sahf();
2991                         i386_jcc(I386_CC_E, 6 + 1 + 5 + 1);
2992                         i386_jcc(I386_CC_B, 1 + 5);
2993                         i386_dec_reg(d);
2994                         i386_jmp(1);
2995                         i386_inc_reg(d);
2996                         store_reg_to_var_int(iptr->dst, d);
2997                         break;
2998
2999
3000                 /* memory operations **************************************************/
3001
3002                         /* #define gen_bound_check \
3003                         if (checkbounds) {\
3004                                 M_ILD(REG_ITMP3, s1, OFFSET(java_arrayheader, size));\
3005                                 M_CMPULT(s2, REG_ITMP3, REG_ITMP3);\
3006                                 M_BEQZ(REG_ITMP3, 0);\
3007                                 mcode_addxboundrefs(mcodeptr);\
3008                                 }
3009                         */
3010
3011 #define gen_bound_check \
3012             if (checkbounds) { \
3013                 i386_alu_reg_membase(I386_CMP, s2, s1, OFFSET(java_arrayheader, size)); \
3014                 i386_jcc(I386_CC_L, 0); \
3015                                 mcode_addxboundrefs(mcodeptr); \
3016             }
3017
3018                 case ICMD_ARRAYLENGTH: /* ..., arrayref  ==> ..., length              */
3019
3020                         var_to_reg_int(s1, src, REG_ITMP1);
3021                         d = reg_of_var(iptr->dst, REG_ITMP3);
3022                         gen_nullptr_check(s1);
3023                         i386_mov_membase_reg(s1, OFFSET(java_arrayheader, size), d);
3024                         store_reg_to_var_int(iptr->dst, d);
3025                         break;
3026
3027                 case ICMD_AALOAD:     /* ..., arrayref, index  ==> ..., value         */
3028
3029                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3030                         var_to_reg_int(s2, src, REG_ITMP2);
3031                         d = reg_of_var(iptr->dst, REG_ITMP3);
3032                         if (iptr->op1 == 0) {
3033                                 gen_nullptr_check(s1);
3034                                 gen_bound_check;
3035                         }
3036                         i386_mov_memindex_reg(OFFSET(java_objectarray, data[0]), s1, s2, 2, d);
3037                         store_reg_to_var_int(iptr->dst, d);
3038                         break;
3039
3040                 case ICMD_LALOAD:     /* ..., arrayref, index  ==> ..., value         */
3041
3042                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3043                         var_to_reg_int(s2, src, REG_ITMP2);
3044                         d = reg_of_var(iptr->dst, REG_ITMP3);
3045                         if (iptr->op1 == 0) {
3046                                 gen_nullptr_check(s1);
3047                                 gen_bound_check;
3048                         }
3049                         
3050                         if (iptr->dst->flags & INMEMORY) {
3051                                 i386_mov_memindex_reg(OFFSET(java_longarray, data[0]), s1, s2, 2, REG_ITMP3);
3052                                 i386_mov_reg_membase(REG_ITMP3, REG_SP, iptr->dst->regoff * 8);
3053                                 i386_mov_memindex_reg(OFFSET(java_longarray, data[0]) + 4, s1, s2, 2, REG_ITMP3);
3054                                 i386_mov_reg_membase(REG_ITMP3, REG_SP, iptr->dst->regoff * 8 + 4);
3055                         }
3056                         break;
3057
3058                 case ICMD_IALOAD:     /* ..., arrayref, index  ==> ..., value         */
3059
3060                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3061                         var_to_reg_int(s2, src, REG_ITMP2);
3062                         d = reg_of_var(iptr->dst, REG_ITMP3);
3063                         if (iptr->op1 == 0) {
3064                                 gen_nullptr_check(s1);
3065                                 gen_bound_check;
3066                         }
3067                         i386_mov_memindex_reg(OFFSET(java_intarray, data[0]), s1, s2, 2, d);
3068                         store_reg_to_var_int(iptr->dst, d);
3069                         break;
3070
3071                 case ICMD_FALOAD:     /* ..., arrayref, index  ==> ..., value         */
3072
3073                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3074                         var_to_reg_int(s2, src, REG_ITMP2);
3075                         d = reg_of_var(iptr->dst, REG_FTMP3);
3076                         if (iptr->op1 == 0) {
3077                                 gen_nullptr_check(s1);
3078                                 gen_bound_check;
3079                                 }
3080                         i386_flds_memindex(OFFSET(java_floatarray, data[0]), s1, s2, 2);
3081                         store_reg_to_var_flt(iptr->dst, d);
3082                         break;
3083
3084                 case ICMD_DALOAD:     /* ..., arrayref, index  ==> ..., value         */
3085
3086                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3087                         var_to_reg_int(s2, src, REG_ITMP2);
3088                         d = reg_of_var(iptr->dst, REG_FTMP3);
3089                         if (iptr->op1 == 0) {
3090                                 gen_nullptr_check(s1);
3091                                 gen_bound_check;
3092                         }
3093                         i386_fldl_memindex(OFFSET(java_doublearray, data[0]), s1, s2, 3);
3094                         store_reg_to_var_flt(iptr->dst, d);
3095                         break;
3096
3097                 case ICMD_CALOAD:     /* ..., arrayref, index  ==> ..., value         */
3098
3099                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3100                         var_to_reg_int(s2, src, REG_ITMP2);
3101                         d = reg_of_var(iptr->dst, REG_ITMP3);
3102                         if (iptr->op1 == 0) {
3103                                 gen_nullptr_check(s1);
3104                                 gen_bound_check;
3105                         }
3106                         i386_movzwl_memindex_reg(OFFSET(java_chararray, data[0]), s1, s2, 1, d);
3107                         store_reg_to_var_int(iptr->dst, d);
3108                         break;                  
3109
3110                 case ICMD_SALOAD:     /* ..., arrayref, index  ==> ..., value         */
3111
3112                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3113                         var_to_reg_int(s2, src, REG_ITMP2);
3114                         d = reg_of_var(iptr->dst, REG_ITMP3);
3115                         if (iptr->op1 == 0) {
3116                                 gen_nullptr_check(s1);
3117                                 gen_bound_check;
3118                         }
3119                         i386_movswl_memindex_reg(OFFSET(java_shortarray, data[0]), s1, s2, 1, d);
3120                         store_reg_to_var_int(iptr->dst, d);
3121                         break;
3122
3123                 case ICMD_BALOAD:     /* ..., arrayref, index  ==> ..., value         */
3124
3125                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3126                         var_to_reg_int(s2, src, REG_ITMP2);
3127                         d = reg_of_var(iptr->dst, REG_ITMP3);
3128                         if (iptr->op1 == 0) {
3129                                 gen_nullptr_check(s1);
3130                                 gen_bound_check;
3131                         }
3132                         i386_movzbl_memindex_reg(OFFSET(java_bytearray, data[0]), s1, s2, 0, d);
3133 /*                      i386_alu_reg_reg(I386_XOR, REG_ITMP3, REG_ITMP3); */
3134 /*                      i386_movb_memindex_reg(OFFSET(java_bytearray, data[0]), s1, s2, 0, REG_ITMP3); */
3135 /*                      M_INTMOVE(REG_ITMP3, d); */
3136                         store_reg_to_var_int(iptr->dst, d);
3137                         break;
3138
3139
3140                 case ICMD_AASTORE:    /* ..., arrayref, index, value  ==> ...         */
3141
3142                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3143                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3144                         if (iptr->op1 == 0) {
3145                                 gen_nullptr_check(s1);
3146                                 gen_bound_check;
3147                         }
3148                         var_to_reg_int(s3, src, REG_ITMP3);
3149                         i386_mov_reg_memindex(s3, OFFSET(java_objectarray, data[0]), s1, s2, 2);
3150                         break;
3151
3152                 case ICMD_LASTORE:    /* ..., arrayref, index, value  ==> ...         */
3153
3154                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3155                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3156                         if (iptr->op1 == 0) {
3157                                 gen_nullptr_check(s1);
3158                                 gen_bound_check;
3159                         }
3160
3161                         if (src->flags & INMEMORY) {
3162                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP3);
3163                                 i386_mov_reg_memindex(REG_ITMP3, OFFSET(java_longarray, data[0]), s1, s2, 2);
3164                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP3);
3165                                 i386_mov_reg_memindex(REG_ITMP3, OFFSET(java_longarray, data[0]) + 4, s1, s2, 2);
3166                         }
3167                         break;
3168
3169                 case ICMD_IASTORE:    /* ..., arrayref, index, value  ==> ...         */
3170
3171                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3172                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3173                         if (iptr->op1 == 0) {
3174                                 gen_nullptr_check(s1);
3175                                 gen_bound_check;
3176                         }
3177                         var_to_reg_int(s3, src, REG_ITMP3);
3178                         i386_mov_reg_memindex(s3, OFFSET(java_intarray, data[0]), s1, s2, 2);
3179                         break;
3180
3181                 case ICMD_FASTORE:    /* ..., arrayref, index, value  ==> ...         */
3182
3183                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3184                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3185                         if (iptr->op1 == 0) {
3186                                 gen_nullptr_check(s1);
3187                                 gen_bound_check;
3188                         }
3189                         i386_fstps_memindex(OFFSET(java_floatarray, data[0]), s1, s2, 2);
3190                         break;
3191
3192                 case ICMD_DASTORE:    /* ..., arrayref, index, value  ==> ...         */
3193
3194                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3195                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3196                         if (iptr->op1 == 0) {
3197                                 gen_nullptr_check(s1);
3198                                 gen_bound_check;
3199                         }
3200                         i386_fstpl_memindex(OFFSET(java_doublearray, data[0]), s1, s2, 3);
3201                         break;
3202
3203                 case ICMD_CASTORE:    /* ..., arrayref, index, value  ==> ...         */
3204
3205                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3206                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3207                         if (iptr->op1 == 0) {
3208                                 gen_nullptr_check(s1);
3209                                 gen_bound_check;
3210                         }
3211                         var_to_reg_int(s3, src, REG_ITMP3);
3212                         i386_movw_reg_memindex(s3, OFFSET(java_chararray, data[0]), s1, s2, 1);
3213                         break;
3214
3215                 case ICMD_SASTORE:    /* ..., arrayref, index, value  ==> ...         */
3216
3217                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3218                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3219                         if (iptr->op1 == 0) {
3220                                 gen_nullptr_check(s1);
3221                                 gen_bound_check;
3222                                 }
3223                         var_to_reg_int(s3, src, REG_ITMP3);
3224                         i386_movw_reg_memindex(s3, OFFSET(java_shortarray, data[0]), s1, s2, 1);
3225                         break;
3226
3227                 case ICMD_BASTORE:    /* ..., arrayref, index, value  ==> ...         */
3228
3229                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
3230                         var_to_reg_int(s2, src->prev, REG_ITMP2);
3231                         if (iptr->op1 == 0) {
3232                                 gen_nullptr_check(s1);
3233                                 gen_bound_check;
3234                         }
3235                         var_to_reg_int(s3, src, REG_ITMP3);
3236                         M_INTMOVE(s3, REG_ITMP3);    /* because EBP, ESI, EDI have no xH and xL bytes */
3237                         i386_movb_reg_memindex(REG_ITMP3, OFFSET(java_bytearray, data[0]), s1, s2, 0);
3238                         break;
3239
3240
3241                 case ICMD_PUTSTATIC:  /* ..., value  ==> ...                          */
3242                                       /* op1 = type, val.a = field address            */
3243
3244                         a = dseg_addaddress(&(((fieldinfo *)(iptr->val.a))->value));
3245                         /* here it's slightly slower */
3246                         i386_mov_imm_reg(0, REG_ITMP2);
3247                         dseg_adddata(mcodeptr);
3248                         i386_mov_membase_reg(REG_ITMP2, a, REG_ITMP3);
3249                         switch (iptr->op1) {
3250                                 case TYPE_INT:
3251                                         var_to_reg_int(s2, src, REG_ITMP1);
3252                                         i386_mov_reg_membase(s2, REG_ITMP3, 0);
3253                                         break;
3254                                 case TYPE_LNG:
3255                                         if (src->flags & INMEMORY) {
3256                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3257                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
3258                                                 i386_mov_reg_membase(REG_ITMP1, REG_ITMP3, 0);
3259                                                 i386_mov_reg_membase(REG_ITMP2, REG_ITMP3, 0 + 4);
3260                                         } else {
3261                                                 panic("longs have to be in memory");
3262                                         }
3263                                         break;
3264                                 case TYPE_ADR:
3265                                         var_to_reg_int(s2, src, REG_ITMP1);
3266                                         i386_mov_reg_membase(s2, REG_ITMP3, 0);
3267                                         break;
3268                                 case TYPE_FLT:
3269                                         if (src->flags & INMEMORY) {
3270                                                 i386_flds_membase(REG_SP, src->regoff * 8);
3271                                                 i386_fstps_membase(REG_ITMP3, 0);
3272                                         } else {
3273                                                 panic("floats have to be in memory");
3274                                         }
3275                                         break;
3276                                 case TYPE_DBL:
3277                                         if (src->flags & INMEMORY) {
3278                                                 i386_fldl_membase(REG_SP, src->regoff * 8);
3279                                                 i386_fstpl_membase(REG_ITMP3, 0);
3280                                         } else {
3281                                                 panic("doubles have to be in memory");
3282                                         }
3283                                         break;
3284                                 default: panic ("internal error");
3285                                 }
3286                         break;
3287
3288                 case ICMD_GETSTATIC:  /* ...  ==> ..., value                          */
3289                                       /* op1 = type, val.a = field address            */
3290
3291                         a = dseg_addaddress(&(((fieldinfo *)(iptr->val.a))->value));
3292                         i386_mov_imm_reg(0, REG_ITMP1);
3293                         dseg_adddata(mcodeptr);
3294                         i386_mov_membase_reg(REG_ITMP1, a, REG_ITMP1);
3295                         switch (iptr->op1) {
3296                                 case TYPE_INT:
3297                                         d = reg_of_var(iptr->dst, REG_ITMP3);
3298                                         i386_mov_membase_reg(REG_ITMP1, 0, d);
3299                                         store_reg_to_var_int(iptr->dst, d);
3300                                         break;
3301                                 case TYPE_LNG:
3302                                         d = reg_of_var(iptr->dst, REG_ITMP3);
3303                                         if (iptr->dst->flags & INMEMORY) {
3304                                                 i386_mov_membase_reg(REG_ITMP1, 0, REG_ITMP2);
3305                                                 i386_mov_membase_reg(REG_ITMP1, 4, REG_ITMP3);
3306                                                 i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8);
3307                                                 i386_mov_reg_membase(REG_ITMP3, REG_SP, iptr->dst->regoff * 8 + 4);
3308                                         } else {
3309                                                 panic("longs have to be in memory");
3310                                         }
3311                                         break;
3312                                 case TYPE_ADR:
3313                                         d = reg_of_var(iptr->dst, REG_ITMP3);
3314                                         i386_mov_membase_reg(REG_ITMP1, 0, d);
3315                                         store_reg_to_var_int(iptr->dst, d);
3316                                         break;
3317                                 case TYPE_FLT:
3318                                         d = reg_of_var(iptr->dst, REG_ITMP3);
3319                                         if (iptr->dst->flags & INMEMORY) {
3320                                                 i386_flds_membase(REG_ITMP1, 0);
3321                                                 i386_fstps_membase(REG_SP, iptr->dst->regoff * 8);
3322                                         } else {
3323                                                 panic("floats have to be in memory");
3324                                         }
3325                                         break;
3326                                 case TYPE_DBL:                          
3327                                         d = reg_of_var(iptr->dst, REG_ITMP3);
3328                                         if (iptr->dst->flags & INMEMORY) {
3329                                                 i386_fldl_membase(REG_ITMP1, 0);
3330                                                 i386_fstpl_membase(REG_SP, iptr->dst->regoff * 8);
3331                                         } else {
3332                                                 panic("doubles have to be in memory");
3333                                         }
3334                                         break;
3335                                 default: panic ("internal error");
3336                                 }
3337                         break;
3338
3339                 case ICMD_PUTFIELD:   /* ..., value  ==> ...                          */
3340                                       /* op1 = type, val.i = field offset             */
3341
3342                         a = ((fieldinfo *)(iptr->val.a))->offset;
3343                         switch (iptr->op1) {
3344                                 case TYPE_INT:
3345                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3346                                         var_to_reg_int(s2, src, REG_ITMP2);
3347                                         gen_nullptr_check(s1);
3348                                         i386_mov_reg_membase(s2, s1, a);
3349                                         break;
3350                                 case TYPE_LNG:
3351                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3352                                         gen_nullptr_check(s1);
3353                                         if (src->flags & INMEMORY) {
3354                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP2);
3355                                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP3);
3356                                                 i386_mov_reg_membase(REG_ITMP2, s1, a);
3357                                                 i386_mov_reg_membase(REG_ITMP3, s1, a + 4);
3358                                         } else {
3359                                                 panic("longs have to be in memory");
3360                                         }
3361                                         break;
3362                                 case TYPE_ADR:
3363                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3364                                         var_to_reg_int(s2, src, REG_ITMP2);
3365                                         gen_nullptr_check(s1);
3366                                         i386_mov_reg_membase(s2, s1, a);
3367                                         break;
3368                                 case TYPE_FLT:
3369                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3370                                         gen_nullptr_check(s1);
3371                                         if (src->flags & INMEMORY) {
3372                                                 i386_fstps_membase(s1, a);
3373                                         } else {
3374                                                 panic("floats have to be in memory");
3375                                         }
3376                                         break;
3377                                 case TYPE_DBL:
3378                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
3379                                         gen_nullptr_check(s1);
3380                                         if (src->flags & INMEMORY) {
3381                                                 i386_fstpl_membase(s1, a);
3382                                         } else {
3383                                                 panic("doubles have to be in memory");
3384                                         }
3385                                         break;
3386                                 default: panic ("internal error");
3387                                 }
3388                         break;
3389
3390                 case ICMD_GETFIELD:   /* ...  ==> ..., value                          */
3391                                       /* op1 = type, val.i = field offset             */
3392
3393                         a = ((fieldinfo *)(iptr->val.a))->offset;
3394                         switch (iptr->op1) {
3395                                 case TYPE_INT:
3396                                         var_to_reg_int(s1, src, REG_ITMP1);
3397                                         d = reg_of_var(iptr->dst, REG_ITMP3);
3398                                         gen_nullptr_check(s1);
3399                                         i386_mov_membase_reg(s1, a, d);
3400                                         store_reg_to_var_int(iptr->dst, d);
3401                                         break;
3402                                 case TYPE_LNG:
3403                                         var_to_reg_int(s1, src, REG_ITMP1);
3404 /*                                      d = reg_of_var(iptr->dst, REG_ITMP3); */
3405                                         gen_nullptr_check(s1);
3406                                         i386_mov_membase_reg(s1, a, REG_ITMP2);
3407                                         i386_mov_membase_reg(s1, a + 4, REG_ITMP3);
3408                                         i386_mov_reg_membase(REG_ITMP2, REG_SP, iptr->dst->regoff * 8);
3409                                         i386_mov_reg_membase(REG_ITMP3, REG_SP, iptr->dst->regoff * 8 + 4);
3410 /*                                      store_reg_to_var_int(iptr->dst, d); */
3411                                         break;
3412                                 case TYPE_ADR:
3413                                         var_to_reg_int(s1, src, REG_ITMP1);
3414                                         d = reg_of_var(iptr->dst, REG_ITMP3);
3415                                         gen_nullptr_check(s1);
3416                                         i386_mov_membase_reg(s1, a, d);
3417                                         store_reg_to_var_int(iptr->dst, d);
3418                                         break;
3419                                 case TYPE_FLT:
3420                                         var_to_reg_int(s1, src, REG_ITMP1);
3421                                         d = reg_of_var(iptr->dst, REG_FTMP1);
3422                                         gen_nullptr_check(s1);
3423                                         i386_flds_membase(s1, a);
3424 /*                                      store_reg_to_var_flt(iptr->dst, d); */
3425                                         break;
3426                                 case TYPE_DBL:                          
3427                                         var_to_reg_int(s1, src, REG_ITMP1);
3428                                         d = reg_of_var(iptr->dst, REG_FTMP1);
3429                                         gen_nullptr_check(s1);
3430                                         i386_fldl_membase(s1, a);
3431 /*                                      store_reg_to_var_flt(iptr->dst, d); */
3432                                         break;
3433                                 default: panic ("internal error");
3434                                 }
3435                         break;
3436
3437
3438                 /* branch operations **************************************************/
3439
3440                         /* TWISTI */
3441 /*  #define ALIGNCODENOP {if((int)((long)mcodeptr&7)){M_NOP;}} */
3442 #define ALIGNCODENOP do {} while (0)
3443
3444                 case ICMD_ATHROW:       /* ..., objectref ==> ... (, objectref)       */
3445
3446                         var_to_reg_int(s1, src, REG_ITMP1);
3447                         M_INTMOVE(s1, REG_ITMP1_XPTR);
3448                         i386_mov_imm_reg(asm_handle_exception, REG_ITMP2);
3449                         i386_call_reg(REG_ITMP2);
3450                         i386_nop();         /* nop ensures that XPC is less than the end */
3451                                             /* of basic block                            */
3452                         ALIGNCODENOP;
3453                         break;
3454
3455                 case ICMD_GOTO:         /* ... ==> ...                                */
3456                                         /* op1 = target JavaVM pc                     */
3457
3458                         i386_jmp(0);
3459                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3460                         ALIGNCODENOP;
3461                         break;
3462
3463                 case ICMD_JSR:          /* ... ==> ...                                */
3464                                         /* op1 = target JavaVM pc                     */
3465
3466                         i386_call_imm(0);
3467                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3468                         break;
3469                         
3470                 case ICMD_RET:          /* ... ==> ...                                */
3471                                         /* op1 = local variable                       */
3472
3473                         i386_ret();
3474                         break;
3475
3476                 case ICMD_IFNULL:       /* ..., value ==> ...                         */
3477                                         /* op1 = target JavaVM pc                     */
3478
3479                         if (src->flags & INMEMORY) {
3480                                 i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
3481
3482                         } else {
3483                                 i386_alu_imm_reg(I386_CMP, 0, src->regoff);
3484                         }
3485                         i386_jcc(I386_CC_E, 0);
3486                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3487                         break;
3488
3489                 case ICMD_IFNONNULL:    /* ..., value ==> ...                         */
3490                                         /* op1 = target JavaVM pc                     */
3491
3492                         if (src->flags & INMEMORY) {
3493                                 i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
3494
3495                         } else {
3496                                 i386_alu_imm_reg(I386_CMP, 0, src->regoff);
3497                         }
3498                         i386_jcc(I386_CC_NE, 0);
3499                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3500                         break;
3501
3502                 case ICMD_IFEQ:         /* ..., value ==> ...                         */
3503                                         /* op1 = target JavaVM pc, val.i = constant   */
3504
3505                         if (src->flags & INMEMORY) {
3506                                 i386_alu_imm_membase(I386_CMP, iptr->val.i, REG_SP, src->regoff * 8);
3507
3508                         } else {
3509                                 i386_alu_imm_reg(I386_CMP, iptr->val.i, src->regoff);
3510                         }
3511                         i386_jcc(I386_CC_E, 0);
3512                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3513                         break;
3514
3515                 case ICMD_IFLT:         /* ..., value ==> ...                         */
3516                                         /* op1 = target JavaVM pc, val.i = constant   */
3517
3518                         if (src->flags & INMEMORY) {
3519                                 i386_alu_imm_membase(I386_CMP, iptr->val.i, REG_SP, src->regoff * 8);
3520
3521                         } else {
3522                                 i386_alu_imm_reg(I386_CMP, iptr->val.i, src->regoff);
3523                         }
3524                         i386_jcc(I386_CC_L, 0);
3525                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3526                         break;
3527
3528                 case ICMD_IFLE:         /* ..., value ==> ...                         */
3529                                         /* op1 = target JavaVM pc, val.i = constant   */
3530
3531                         if (src->flags & INMEMORY) {
3532                                 i386_alu_imm_membase(I386_CMP, iptr->val.i, REG_SP, src->regoff * 8);
3533
3534                         } else {
3535                                 i386_alu_imm_reg(I386_CMP, iptr->val.i, src->regoff);
3536                         }
3537                         i386_jcc(I386_CC_LE, 0);
3538                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3539                         break;
3540
3541                 case ICMD_IFNE:         /* ..., value ==> ...                         */
3542                                         /* op1 = target JavaVM pc, val.i = constant   */
3543
3544                         if (src->flags & INMEMORY) {
3545                                 i386_alu_imm_membase(I386_CMP, iptr->val.i, REG_SP, src->regoff * 8);
3546
3547                         } else {
3548                                 i386_alu_imm_reg(I386_CMP, iptr->val.i, src->regoff);
3549                         }
3550                         i386_jcc(I386_CC_NE, 0);
3551                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3552                         break;
3553
3554                 case ICMD_IFGT:         /* ..., value ==> ...                         */
3555                                         /* op1 = target JavaVM pc, val.i = constant   */
3556
3557                         if (src->flags & INMEMORY) {
3558                                 i386_alu_imm_membase(I386_CMP, iptr->val.i, REG_SP, src->regoff * 8);
3559
3560                         } else {
3561                                 i386_alu_imm_reg(I386_CMP, iptr->val.i, src->regoff);
3562                         }
3563                         i386_jcc(I386_CC_G, 0);
3564                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3565                         break;
3566
3567                 case ICMD_IFGE:         /* ..., value ==> ...                         */
3568                                         /* op1 = target JavaVM pc, val.i = constant   */
3569
3570                         if (src->flags & INMEMORY) {
3571                                 i386_alu_imm_membase(I386_CMP, iptr->val.i, REG_SP, src->regoff * 8);
3572
3573                         } else {
3574                                 i386_alu_imm_reg(I386_CMP, iptr->val.i, src->regoff);
3575                         }
3576                         i386_jcc(I386_CC_GE, 0);
3577                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3578                         break;
3579
3580                 case ICMD_IF_LEQ:       /* ..., value ==> ...                         */
3581                                         /* op1 = target JavaVM pc, val.l = constant   */
3582
3583                         if (src->flags & INMEMORY) {
3584                                 if (iptr->val.l == 0) {
3585                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3586                                         i386_alu_membase_reg(I386_OR, REG_SP, src->regoff * 8 + 4, REG_ITMP1);
3587
3588                                 } else if (iptr->val.l > 0 && iptr->val.l <= 0x00000000ffffffff) {
3589                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3590                                         i386_alu_imm_reg(I386_XOR, iptr->val.l, REG_ITMP1);
3591                                         i386_alu_membase_reg(I386_OR, REG_SP, src->regoff * 8 + 4, REG_ITMP1);
3592                                         
3593                                 } else {
3594                                         i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_ITMP2);
3595                                         i386_alu_imm_reg(I386_XOR, iptr->val.l >> 32, REG_ITMP2);
3596                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3597                                         i386_alu_imm_reg(I386_XOR, iptr->val.l, REG_ITMP1);
3598                                         i386_alu_reg_reg(I386_OR, REG_ITMP2, REG_ITMP1);
3599                                 }
3600                         }
3601                         i386_test_reg_reg(REG_ITMP1, REG_ITMP1);
3602                         i386_jcc(I386_CC_NE, 0);
3603                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3604                         break;
3605
3606                 case ICMD_IF_LLT:       /* ..., value ==> ...                         */
3607                                         /* op1 = target JavaVM pc, val.l = constant   */
3608
3609                         /* TODO: optimize as in IF_LEQ */
3610                         if (src->flags & INMEMORY) {
3611                                 int offset;
3612                                 i386_alu_imm_membase(I386_CMP, iptr->val.l >> 32, REG_SP, src->regoff * 8 + 4);
3613                                 i386_jcc(I386_CC_L, 0);
3614                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3615
3616                                 offset = 4 + 6;
3617                                 if (src->regoff > 0) offset++;
3618                                 if (src->regoff > 31) offset += 3;
3619                                 
3620                                 i386_jcc(I386_CC_G, offset);
3621
3622                                 i386_alu_imm_membase(I386_CMP, iptr->val.l, REG_SP, src->regoff * 8);
3623                                 i386_jcc(I386_CC_B, 0);
3624                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3625                         }                       
3626                         break;
3627
3628                 case ICMD_IF_LLE:       /* ..., value ==> ...                         */
3629                                         /* op1 = target JavaVM pc, val.l = constant   */
3630
3631                         /* TODO: optimize as in IF_LEQ */
3632                         if (src->flags & INMEMORY) {
3633                                 int offset;
3634                                 i386_alu_imm_membase(I386_CMP, iptr->val.l >> 32, REG_SP, src->regoff * 8 + 4);
3635                                 i386_jcc(I386_CC_L, 0);
3636                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3637
3638                                 offset = 4 + 6;
3639                                 if (src->regoff > 0) offset++;
3640                                 if (src->regoff > 31) offset += 3;
3641                                 
3642                                 i386_jcc(I386_CC_G, offset);
3643
3644                                 i386_alu_imm_membase(I386_CMP, iptr->val.l, REG_SP, src->regoff * 8);
3645                                 i386_jcc(I386_CC_BE, 0);
3646                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3647                         }                       
3648                         break;
3649
3650                 case ICMD_IF_LNE:       /* ..., value ==> ...                         */
3651                                         /* op1 = target JavaVM pc, val.l = constant   */
3652
3653                         /* TODO: optimize for val.l == 0 */
3654                         if (src->flags & INMEMORY) {
3655                                 i386_mov_imm_reg(iptr->val.l, REG_ITMP1);
3656                                 i386_mov_imm_reg(iptr->val.l >> 32, REG_ITMP2);
3657                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8, REG_ITMP1);
3658                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
3659                                 i386_alu_reg_reg(I386_OR, REG_ITMP2, REG_ITMP1);
3660                                 i386_test_reg_reg(REG_ITMP1, REG_ITMP1);
3661                         }                       
3662                         i386_jcc(I386_CC_NE, 0);
3663                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3664                         break;
3665
3666                 case ICMD_IF_LGT:       /* ..., value ==> ...                         */
3667                                         /* op1 = target JavaVM pc, val.l = constant   */
3668
3669                         /* TODO: optimize as in IF_LEQ */
3670                         if (src->flags & INMEMORY) {
3671                                 int offset;
3672                                 i386_alu_imm_membase(I386_CMP, iptr->val.l >> 32, REG_SP, src->regoff * 8 + 4);
3673                                 i386_jcc(I386_CC_G, 0);
3674                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3675
3676                                 offset = 4 + 6;
3677                                 if (src->regoff > 0) offset++;
3678                                 if (src->regoff > 31) offset += 3;
3679                                 if ((iptr->val.l & 0x00000000ffffffff) < -128 || (iptr->val.l & 0x00000000ffffffff) > 127) offset += 3;
3680
3681                                 i386_jcc(I386_CC_L, offset);
3682
3683                                 i386_alu_imm_membase(I386_CMP, iptr->val.l, REG_SP, src->regoff * 8);
3684                                 i386_jcc(I386_CC_A, 0);
3685                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3686                         }                       
3687                         break;
3688
3689                 case ICMD_IF_LGE:       /* ..., value ==> ...                         */
3690                                         /* op1 = target JavaVM pc, val.l = constant   */
3691
3692                         /* TODO: optimize as in IF_LEQ */
3693                         if (src->flags & INMEMORY) {
3694                                 int offset;
3695                                 i386_alu_imm_membase(I386_CMP, iptr->val.l >> 32, REG_SP, src->regoff * 8 + 4);
3696                                 i386_jcc(I386_CC_G, 0);
3697                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3698
3699                                 offset = 4 + 6;
3700                                 if (src->regoff > 0) offset++;
3701                                 if (src->regoff > 31) offset += 3;
3702
3703                                 i386_jcc(I386_CC_L, offset);
3704
3705                                 i386_alu_imm_membase(I386_CMP, iptr->val.l, REG_SP, src->regoff * 8);
3706                                 i386_jcc(I386_CC_AE, 0);
3707                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3708                         }                       
3709                         break;
3710
3711                 case ICMD_IF_ICMPEQ:    /* ..., value, value ==> ...                  */
3712                 case ICMD_IF_ACMPEQ:    /* op1 = target JavaVM pc                     */
3713
3714                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3715                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3716                                 i386_alu_reg_membase(I386_CMP, REG_ITMP1, REG_SP, src->prev->regoff * 8);
3717
3718                         } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
3719                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, src->prev->regoff);
3720
3721                         } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3722                                 i386_alu_reg_membase(I386_CMP, src->regoff, REG_SP, src->prev->regoff * 8);
3723
3724                         } else {
3725                                 i386_alu_reg_reg(I386_CMP, src->regoff, src->prev->regoff);
3726                         }
3727                         i386_jcc(I386_CC_E, 0);
3728                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3729                         break;
3730
3731                 case ICMD_IF_LCMPEQ:    /* ..., value, value ==> ...                  */
3732                                         /* op1 = target JavaVM pc                     */
3733
3734                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3735                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
3736                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
3737                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8, REG_ITMP1);
3738                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
3739                                 i386_alu_reg_reg(I386_OR, REG_ITMP2, REG_ITMP1);
3740                                 i386_test_reg_reg(REG_ITMP1, REG_ITMP1);
3741                         }                       
3742                         i386_jcc(I386_CC_E, 0);
3743                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3744                         break;
3745
3746                 case ICMD_IF_ICMPNE:    /* ..., value, value ==> ...                  */
3747                 case ICMD_IF_ACMPNE:    /* op1 = target JavaVM pc                     */
3748
3749                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3750                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3751                                 i386_alu_reg_membase(I386_CMP, REG_ITMP1, REG_SP, src->prev->regoff * 8);
3752
3753                         } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
3754                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, src->prev->regoff);
3755
3756                         } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3757                                 i386_alu_reg_membase(I386_CMP, src->regoff, REG_SP, src->prev->regoff * 8);
3758
3759                         } else {
3760                                 i386_alu_reg_reg(I386_CMP, src->regoff, src->prev->regoff);
3761                         }
3762                         i386_jcc(I386_CC_NE, 0);
3763                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3764                         break;
3765
3766                 case ICMD_IF_LCMPNE:    /* ..., value, value ==> ...                  */
3767                                         /* op1 = target JavaVM pc                     */
3768
3769                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3770                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
3771                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP2);
3772                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8, REG_ITMP1);
3773                                 i386_alu_membase_reg(I386_XOR, REG_SP, src->regoff * 8 + 4, REG_ITMP2);
3774                                 i386_alu_reg_reg(I386_OR, REG_ITMP2, REG_ITMP1);
3775                                 i386_test_reg_reg(REG_ITMP1, REG_ITMP1);
3776                         }                       
3777                         i386_jcc(I386_CC_NE, 0);
3778                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3779                         break;
3780
3781                 case ICMD_IF_ICMPLT:    /* ..., value, value ==> ...                  */
3782                                         /* op1 = target JavaVM pc                     */
3783
3784                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3785                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3786                                 i386_alu_reg_membase(I386_CMP, REG_ITMP1, REG_SP, src->prev->regoff * 8);
3787
3788                         } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
3789                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, src->prev->regoff);
3790
3791                         } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3792                                 i386_alu_reg_membase(I386_CMP, src->regoff, REG_SP, src->prev->regoff * 8);
3793
3794                         } else {
3795                                 i386_alu_reg_reg(I386_CMP, src->regoff, src->prev->regoff);
3796                         }
3797                         i386_jcc(I386_CC_L, 0);
3798                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3799                         break;
3800
3801                 case ICMD_IF_LCMPLT:    /* ..., value, value ==> ...                  */
3802                                     /* op1 = target JavaVM pc                     */
3803
3804                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3805                                 int offset;
3806                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP1);
3807                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8 + 4, REG_ITMP1);
3808                                 i386_jcc(I386_CC_L, 0);
3809                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3810
3811                                 offset = 3 + 3 + 6;
3812                                 if (src->prev->regoff > 0) offset++;
3813                                 if (src->prev->regoff > 31) offset += 3;
3814
3815                                 if (src->regoff > 0) offset++;
3816                                 if (src->regoff > 31) offset += 3;
3817
3818                                 i386_jcc(I386_CC_G, offset);
3819
3820                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
3821                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, REG_ITMP1);
3822                                 i386_jcc(I386_CC_B, 0);
3823                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3824                         }                       
3825                         break;
3826
3827                 case ICMD_IF_ICMPGT:    /* ..., value, value ==> ...                  */
3828                                         /* op1 = target JavaVM pc                     */
3829
3830                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3831                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3832                                 i386_alu_reg_membase(I386_CMP, REG_ITMP1, REG_SP, src->prev->regoff * 8);
3833
3834                         } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
3835                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, src->prev->regoff);
3836
3837                         } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3838                                 i386_alu_reg_membase(I386_CMP, src->regoff, REG_SP, src->prev->regoff * 8);
3839
3840                         } else {
3841                                 i386_alu_reg_reg(I386_CMP, src->regoff, src->prev->regoff);
3842                         }
3843                         i386_jcc(I386_CC_G, 0);
3844                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3845                         break;
3846
3847                 case ICMD_IF_LCMPGT:    /* ..., value, value ==> ...                  */
3848                                 /* op1 = target JavaVM pc                     */
3849
3850                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3851                                 int offset;
3852                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP1);
3853                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8 + 4, REG_ITMP1);
3854                                 i386_jcc(I386_CC_G, 0);
3855                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3856
3857                                 offset = 3 + 3 + 6;
3858                                 if (src->prev->regoff > 0) offset++;
3859                                 if (src->prev->regoff > 31) offset += 3;
3860
3861                                 if (src->regoff > 0) offset++;
3862                                 if (src->regoff > 31) offset += 3;
3863
3864                                 i386_jcc(I386_CC_L, offset);
3865
3866                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
3867                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, REG_ITMP1);
3868                                 i386_jcc(I386_CC_A, 0);
3869                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3870                         }                       
3871                         break;
3872
3873                 case ICMD_IF_ICMPLE:    /* ..., value, value ==> ...                  */
3874                                         /* op1 = target JavaVM pc                     */
3875
3876                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3877                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3878                                 i386_alu_reg_membase(I386_CMP, REG_ITMP1, REG_SP, src->prev->regoff * 8);
3879
3880                         } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
3881                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, src->prev->regoff);
3882
3883                         } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3884                                 i386_alu_reg_membase(I386_CMP, src->regoff, REG_SP, src->prev->regoff * 8);
3885
3886                         } else {
3887                                 i386_alu_reg_reg(I386_CMP, src->regoff, src->prev->regoff);
3888                         }
3889                         i386_jcc(I386_CC_LE, 0);
3890                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3891                         break;
3892
3893                 case ICMD_IF_LCMPLE:    /* ..., value, value ==> ...                  */
3894                                         /* op1 = target JavaVM pc                     */
3895
3896                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3897                                 int offset;
3898                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP1);
3899                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8 + 4, REG_ITMP1);
3900                                 i386_jcc(I386_CC_L, 0);
3901                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3902
3903                                 offset = 3 + 3 + 6;
3904                                 if (src->prev->regoff > 0) offset++;
3905                                 if (src->prev->regoff > 31) offset += 3;
3906
3907                                 if (src->regoff > 0) offset++;
3908                                 if (src->regoff > 31) offset += 3;
3909
3910                                 i386_jcc(I386_CC_G, offset);
3911
3912                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
3913                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, REG_ITMP1);
3914                                 i386_jcc(I386_CC_BE, 0);
3915                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3916                         }                       
3917                         break;
3918
3919                 case ICMD_IF_ICMPGE:    /* ..., value, value ==> ...                  */
3920                                         /* op1 = target JavaVM pc                     */
3921
3922                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3923                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
3924                                 i386_alu_reg_membase(I386_CMP, REG_ITMP1, REG_SP, src->prev->regoff * 8);
3925
3926                         } else if ((src->flags & INMEMORY) && !(src->prev->flags & INMEMORY)) {
3927                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, src->prev->regoff);
3928
3929                         } else if (!(src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3930                                 i386_alu_reg_membase(I386_CMP, src->regoff, REG_SP, src->prev->regoff * 8);
3931
3932                         } else {
3933                                 i386_alu_reg_reg(I386_CMP, src->regoff, src->prev->regoff);
3934                         }
3935                         i386_jcc(I386_CC_GE, 0);
3936                         mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3937                         break;
3938
3939                 case ICMD_IF_LCMPGE:    /* ..., value, value ==> ...                  */
3940                                     /* op1 = target JavaVM pc                     */
3941
3942                         if ((src->flags & INMEMORY) && (src->prev->flags & INMEMORY)) {
3943                                 int offset;
3944                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8 + 4, REG_ITMP1);
3945                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8 + 4, REG_ITMP1);
3946                                 i386_jcc(I386_CC_G, 0);
3947                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3948
3949                                 offset = 3 + 3 + 6;
3950                                 if (src->prev->regoff > 0) offset++;
3951                                 if (src->prev->regoff > 31) offset += 3;
3952
3953                                 if (src->regoff > 0) offset++;
3954                                 if (src->regoff > 31) offset += 3;
3955
3956                                 i386_jcc(I386_CC_L, offset);
3957
3958                                 i386_mov_membase_reg(REG_SP, src->prev->regoff * 8, REG_ITMP1);
3959                                 i386_alu_membase_reg(I386_CMP, REG_SP, src->regoff * 8, REG_ITMP1);
3960                                 i386_jcc(I386_CC_AE, 0);
3961                                 mcode_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
3962                         }                       
3963                         break;
3964
3965                 /* (value xx 0) ? IFxx_ICONST : ELSE_ICONST                           */
3966
3967                 case ICMD_ELSE_ICONST:  /* handled by IFxx_ICONST                     */
3968                         break;
3969
3970                 case ICMD_IFEQ_ICONST:  /* ..., value ==> ..., constant               */
3971                                         /* val.i = constant                           */
3972
3973                         /* TWISTI: checked */
3974                         d = reg_of_var(iptr->dst, REG_ITMP3);
3975                         if (iptr->dst->flags & INMEMORY) {
3976                                 int offset = 0;
3977
3978                                 if (src->flags & INMEMORY) {
3979                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
3980
3981                                 } else {
3982                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
3983                                 }
3984
3985                                 offset += 7;
3986                                 if (iptr->dst->regoff > 0) offset += 1;
3987                                 if (iptr->dst->regoff > 31) offset += 3;
3988         
3989                                 i386_jcc(I386_CC_NE, offset + (iptr[1].opc == ICMD_ELSE_ICONST) ? 5 + offset : 0);
3990                                 i386_mov_imm_membase(iptr->val.i, REG_SP, iptr->dst->regoff * 8);
3991
3992                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
3993                                         i386_jmp(offset);
3994                                         i386_mov_imm_membase(iptr[1].val.i, REG_SP, iptr->dst->regoff * 8);
3995                                 }
3996
3997                         } else {
3998                                 if (src->flags & INMEMORY) {
3999                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4000
4001                                 } else {
4002                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4003                                 }
4004
4005                                 i386_jcc(I386_CC_NE, (iptr[1].opc == ICMD_ELSE_ICONST) ? 10 : 5);
4006                                 i386_mov_imm_reg(iptr->val.i, iptr->dst->regoff);
4007
4008                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4009                                         i386_jmp(5);
4010                                         i386_mov_imm_reg(iptr[1].val.i, iptr->dst->regoff);
4011                                 }
4012                         }
4013                         break;
4014
4015                 case ICMD_IFNE_ICONST:  /* ..., value ==> ..., constant               */
4016                                         /* val.i = constant                           */
4017
4018                         /* TWISTI: checked */
4019                         d = reg_of_var(iptr->dst, REG_ITMP3);
4020                         if (iptr->dst->flags & INMEMORY) {
4021                                 int offset = 0;
4022
4023                                 if (src->flags & INMEMORY) {
4024                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4025
4026                                 } else {
4027                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4028                                 }
4029
4030                                 offset += 7;
4031                                 if (iptr->dst->regoff > 0) offset += 1;
4032                                 if (iptr->dst->regoff > 31) offset += 3;
4033         
4034                                 i386_jcc(I386_CC_E, offset + (iptr[1].opc == ICMD_ELSE_ICONST) ? 5 + offset : 0);
4035                                 i386_mov_imm_membase(iptr->val.i, REG_SP, iptr->dst->regoff * 8);
4036
4037                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4038                                         i386_jmp(offset);
4039                                         i386_mov_imm_membase(iptr[1].val.i, REG_SP, iptr->dst->regoff * 8);
4040                                 }
4041
4042                         } else {
4043                                 if (src->flags & INMEMORY) {
4044                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4045
4046                                 } else {
4047                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4048                                 }
4049
4050                                 i386_jcc(I386_CC_E, (iptr[1].opc == ICMD_ELSE_ICONST) ? 10 : 5);
4051                                 i386_mov_imm_reg(iptr->val.i, iptr->dst->regoff);
4052
4053                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4054                                         i386_jmp(5);
4055                                         i386_mov_imm_reg(iptr[1].val.i, iptr->dst->regoff);
4056                                 }
4057                         }
4058                         break;
4059
4060                 case ICMD_IFLT_ICONST:  /* ..., value ==> ..., constant               */
4061                                         /* val.i = constant                           */
4062
4063                         /* TWISTI: checked */
4064                         d = reg_of_var(iptr->dst, REG_ITMP3);
4065                         if (iptr->dst->flags & INMEMORY) {
4066                                 int offset = 0;
4067
4068                                 if (src->flags & INMEMORY) {
4069                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4070
4071                                 } else {
4072                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4073                                 }
4074
4075                                 offset += 7;
4076                                 if (iptr->dst->regoff > 0) offset += 1;
4077                                 if (iptr->dst->regoff > 31) offset += 3;
4078         
4079                                 i386_jcc(I386_CC_GE, offset + (iptr[1].opc == ICMD_ELSE_ICONST) ? 5 + offset : 0);
4080                                 i386_mov_imm_membase(iptr->val.i, REG_SP, iptr->dst->regoff * 8);
4081
4082                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4083                                         i386_jmp(offset);
4084                                         i386_mov_imm_membase(iptr[1].val.i, REG_SP, iptr->dst->regoff * 8);
4085                                 }
4086
4087                         } else {
4088                                 if (src->flags & INMEMORY) {
4089                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4090
4091                                 } else {
4092                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4093                                 }
4094
4095                                 i386_jcc(I386_CC_GE, (iptr[1].opc == ICMD_ELSE_ICONST) ? 10 : 5);
4096                                 i386_mov_imm_reg(iptr->val.i, iptr->dst->regoff);
4097
4098                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4099                                         i386_jmp(5);
4100                                         i386_mov_imm_reg(iptr[1].val.i, iptr->dst->regoff);
4101                                 }
4102                         }
4103                         break;
4104
4105                 case ICMD_IFGE_ICONST:  /* ..., value ==> ..., constant               */
4106                                         /* val.i = constant                           */
4107
4108                         /* TWISTI: checked */
4109                         d = reg_of_var(iptr->dst, REG_ITMP3);
4110                         if (iptr->dst->flags & INMEMORY) {
4111                                 int offset = 0;
4112
4113                                 if (src->flags & INMEMORY) {
4114                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4115
4116                                 } else {
4117                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4118                                 }
4119
4120                                 offset += 7;
4121                                 if (iptr->dst->regoff > 0) offset += 1;
4122                                 if (iptr->dst->regoff > 31) offset += 3;
4123         
4124                                 i386_jcc(I386_CC_L, offset + (iptr[1].opc == ICMD_ELSE_ICONST) ? 5 + offset : 0);
4125                                 i386_mov_imm_membase(iptr->val.i, REG_SP, iptr->dst->regoff * 8);
4126
4127                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4128                                         i386_jmp(offset);
4129                                         i386_mov_imm_membase(iptr[1].val.i, REG_SP, iptr->dst->regoff * 8);
4130                                 }
4131
4132                         } else {
4133                                 if (src->flags & INMEMORY) {
4134                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4135
4136                                 } else {
4137                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4138                                 }
4139
4140                                 i386_jcc(I386_CC_L, (iptr[1].opc == ICMD_ELSE_ICONST) ? 10 : 5);
4141                                 i386_mov_imm_reg(iptr->val.i, iptr->dst->regoff);
4142
4143                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4144                                         i386_jmp(5);
4145                                         i386_mov_imm_reg(iptr[1].val.i, iptr->dst->regoff);
4146                                 }
4147                         }
4148                         break;
4149
4150                 case ICMD_IFGT_ICONST:  /* ..., value ==> ..., constant               */
4151                                         /* val.i = constant                           */
4152
4153                         var_to_reg_int(s1, src, REG_ITMP1);
4154                         d = reg_of_var(iptr->dst, REG_ITMP3);
4155                         s3 = iptr->val.i;
4156                         if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4157                                 if ((s3 == 1) && (iptr[1].val.i == 0)) {
4158                                         M_CMPLT(REG_ZERO, s1, d);
4159                                         store_reg_to_var_int(iptr->dst, d);
4160                                         break;
4161                                         }
4162                                 if ((s3 == 0) && (iptr[1].val.i == 1)) {
4163                                         M_CMPLE(s1, REG_ZERO, d);
4164                                         store_reg_to_var_int(iptr->dst, d);
4165                                         break;
4166                                         }
4167                                 if (s1 == d) {
4168                                         M_MOV(s1, REG_ITMP1);
4169                                         s1 = REG_ITMP1;
4170                                         }
4171 /*                              ICONST(d, iptr[1].val.i); */
4172                                 }
4173                         if ((s3 >= 0) && (s3 <= 255)) {
4174                                 M_CMOVGT_IMM(s1, s3, d);
4175                                 }
4176                         else {
4177 /*                              ICONST(REG_ITMP2, s3); */
4178                                 M_CMOVGT(s1, REG_ITMP2, d);
4179                                 }
4180                         store_reg_to_var_int(iptr->dst, d);
4181                         break;
4182
4183                 case ICMD_IFLE_ICONST:  /* ..., value ==> ..., constant               */
4184                                         /* val.i = constant                           */
4185
4186                         /* TWISTI: checked */
4187                         d = reg_of_var(iptr->dst, REG_ITMP3);
4188                         if (iptr->dst->flags & INMEMORY) {
4189                                 int offset = 0;
4190
4191                                 if (src->flags & INMEMORY) {
4192                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4193
4194                                 } else {
4195                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4196                                 }
4197
4198                                 offset += 7;
4199                                 if (iptr->dst->regoff > 0) offset += 1;
4200                                 if (iptr->dst->regoff > 31) offset += 3;
4201         
4202                                 i386_jcc(I386_CC_G, offset + (iptr[1].opc == ICMD_ELSE_ICONST) ? 5 + offset : 0);
4203                                 i386_mov_imm_membase(iptr->val.i, REG_SP, iptr->dst->regoff * 8);
4204
4205                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4206                                         i386_jmp(offset);
4207                                         i386_mov_imm_membase(iptr[1].val.i, REG_SP, iptr->dst->regoff * 8);
4208                                 }
4209
4210                         } else {
4211                                 if (src->flags & INMEMORY) {
4212                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4213
4214                                 } else {
4215                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4216                                 }
4217
4218                                 i386_jcc(I386_CC_G, (iptr[1].opc == ICMD_ELSE_ICONST) ? 10 : 5);
4219                                 i386_mov_imm_reg(iptr->val.i, iptr->dst->regoff);
4220
4221                                 if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
4222                                         i386_jmp(5);
4223                                         i386_mov_imm_reg(iptr[1].val.i, iptr->dst->regoff);
4224                                 }
4225                         }
4226                         break;
4227
4228
4229                 case ICMD_IRETURN:      /* ..., retvalue ==> ...                      */
4230                 case ICMD_ARETURN:
4231
4232 #ifdef USE_THREADS
4233                         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
4234                                 i386_mov_membase_reg(REG_SP, 8 * maxmemuse, REG_ITMP1);
4235                                 i386_alu_imm_reg(I386_SUB, 4, REG_SP);
4236                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, 0);
4237                                 i386_mov_imm_reg(builtin_monitorexit, REG_ITMP1);
4238                                 i386_call_reg(REG_ITMP1);
4239                                 i386_alu_imm_reg(I386_ADD, 4, REG_SP);
4240                         }
4241 #endif
4242                         var_to_reg_int(s1, src, REG_RESULT);
4243                         M_INTMOVE(s1, REG_RESULT);
4244                         goto nowperformreturn;
4245
4246                 case ICMD_LRETURN:      /* ..., retvalue ==> ...                      */
4247
4248 #ifdef USE_THREADS
4249                         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
4250                                 i386_mov_membase_reg(REG_SP, 8 * maxmemuse, REG_ITMP1);
4251                                 i386_alu_imm_reg(I386_SUB, 4, REG_SP);
4252                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, 0);
4253                                 i386_mov_imm_reg(builtin_monitorexit, REG_ITMP1);
4254                                 i386_call_reg(REG_ITMP1);
4255                                 i386_alu_imm_reg(I386_ADD, 4, REG_SP);
4256                         }
4257 #endif
4258                         if (src->flags & INMEMORY) {
4259                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_RESULT);
4260                                 i386_mov_membase_reg(REG_SP, src->regoff * 8 + 4, REG_RESULT2);
4261
4262                         } else {
4263                                 panic("longs have to be in memory");
4264                         }
4265                         goto nowperformreturn;
4266
4267                 case ICMD_FRETURN:      /* ..., retvalue ==> ...                      */
4268                 case ICMD_DRETURN:
4269
4270 #ifdef USE_THREADS
4271                         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
4272                                 i386_mov_membase_reg(REG_SP, 8 * maxmemuse, REG_ITMP1);
4273                                 i386_alu_imm_reg(I386_SUB, 4, REG_SP);
4274                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, 0);
4275                                 i386_mov_imm_reg(builtin_monitorexit, REG_ITMP1);
4276                                 i386_call_reg(REG_ITMP1);
4277                                 i386_alu_imm_reg(I386_ADD, 4, REG_SP);
4278                         }
4279 #endif
4280                         /* value should already be in st(0) */
4281                         goto nowperformreturn;
4282
4283                 case ICMD_RETURN:      /* ...  ==> ...                                */
4284
4285 #ifdef USE_THREADS
4286                         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
4287                                 i386_mov_membase_reg(REG_SP, 8 * maxmemuse, REG_ITMP1);
4288                                 i386_alu_imm_reg(I386_SUB, 4, REG_SP);
4289                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, 0);
4290                                 i386_mov_imm_reg(builtin_monitorexit, REG_ITMP1);
4291                                 i386_call_reg(REG_ITMP1);
4292                                 i386_alu_imm_reg(I386_ADD, 4, REG_SP);
4293                         }
4294 #endif
4295
4296 nowperformreturn:
4297                         {
4298                         int r, p;
4299                         
4300                         p = parentargs_base;
4301                         
4302                         /* restore return address                                         */
4303
4304                         if (!isleafmethod) {
4305                                 /* p--; M_LLD (REG_RA, REG_SP, 8 * p); -- do we really need this on i386 */
4306                         }
4307
4308                         /* restore saved registers                                        */
4309
4310                         for (r = savintregcnt - 1; r >= maxsavintreguse; r--) {
4311                                 p--; i386_mov_membase_reg(REG_SP, p * 8, savintregs[r]);
4312                         }
4313                         for (r = savfltregcnt - 1; r >= maxsavfltreguse; r--) {
4314                                 p--; M_DLD(savfltregs[r], REG_SP, 8 * p);
4315                         }
4316
4317                         /* deallocate stack                                               */
4318
4319                         if (parentargs_base) {
4320                                 i386_alu_imm_reg(I386_ADD, parentargs_base * 8, REG_SP);
4321                         }
4322
4323                         /* call trace function */
4324
4325                         if (runverbose) {
4326                                 M_LDA (REG_SP, REG_SP, -24);
4327                                 M_AST(REG_RA, REG_SP, 0);
4328                                 M_LST(REG_RESULT, REG_SP, 8);
4329                                 M_DST(REG_FRESULT, REG_SP,16);
4330                                 a = dseg_addaddress (method);
4331                                 M_ALD(argintregs[0], REG_PV, a);
4332                                 M_MOV(REG_RESULT, argintregs[1]);
4333                                 M_FLTMOVE(REG_FRESULT, argfltregs[2]);
4334                                 a = dseg_addaddress ((void*) (builtin_displaymethodstop));
4335                                 M_ALD(REG_PV, REG_PV, a);
4336                                 M_JSR (REG_RA, REG_PV);
4337                                 s1 = (int)((u1*) mcodeptr - mcodebase);
4338                                 if (s1<=32768) M_LDA (REG_PV, REG_RA, -s1);
4339                                 else {
4340                                         s4 ml=-s1, mh=0;
4341                                         while (ml<-32768) { ml+=65536; mh--; }
4342                                         M_LDA (REG_PV, REG_RA, ml );
4343                                         M_LDAH (REG_PV, REG_PV, mh );
4344                                         }
4345                                 M_DLD(REG_FRESULT, REG_SP,16);
4346                                 M_LLD(REG_RESULT, REG_SP, 8);
4347                                 M_ALD(REG_RA, REG_SP, 0);
4348                                 M_LDA (REG_SP, REG_SP, 24);
4349                                 }
4350
4351                         i386_ret();
4352                         ALIGNCODENOP;
4353                         }
4354                         break;
4355
4356
4357                 case ICMD_TABLESWITCH:  /* ..., index ==> ...                         */
4358                         {
4359                                 s4 i, l, *s4ptr;
4360                                 void **tptr;
4361
4362                                 tptr = (void **) iptr->target;
4363
4364                                 s4ptr = iptr->val.a;
4365                                 l = s4ptr[1];                          /* low     */
4366                                 i = s4ptr[2];                          /* high    */
4367
4368                                 var_to_reg_int(s1, src, REG_ITMP1);
4369                                 if (l == 0) {
4370                                         M_INTMOVE(s1, REG_ITMP1);
4371                                 } else if (l <= 32768) {
4372                                         i386_alu_imm_reg(I386_SUB, l, REG_ITMP1);
4373                                 }
4374                                 i = i - l + 1;
4375
4376                 /* range check */
4377
4378                                 i386_alu_imm_reg(I386_CMP, i - 1, REG_ITMP1);
4379                                 i386_jcc(I386_CC_A, 0);
4380
4381                 /* mcode_addreference(BlockPtrOfPC(s4ptr[0]), mcodeptr); */
4382                                 mcode_addreference((basicblock *) tptr[0], mcodeptr);
4383
4384                                 /* build jump table top down and use address of lowest entry */
4385
4386                 /* s4ptr += 3 + i; */
4387                                 tptr += i;
4388
4389                                 while (--i >= 0) {
4390                                         /* dseg_addtarget(BlockPtrOfPC(*--s4ptr)); */
4391                                         dseg_addtarget((basicblock *) tptr[0]); 
4392                                         --tptr;
4393                                 }
4394
4395                                 /* length of dataseg after last dseg_addtarget is used by load */
4396
4397                                 i386_mov_imm_reg(0, REG_ITMP2);
4398                                 dseg_adddata(mcodeptr);
4399                                 i386_mov_memindex_reg(-dseglen, REG_ITMP2, REG_ITMP1, 2, REG_ITMP3);
4400                                 i386_jmp_reg(REG_ITMP3);
4401                                 ALIGNCODENOP;
4402                         }
4403                         break;
4404
4405
4406                 case ICMD_LOOKUPSWITCH: /* ..., key ==> ...                           */
4407                         {
4408                                 s4 i, l, val, *s4ptr;
4409                                 void **tptr;
4410
4411                                 tptr = (void **) iptr->target;
4412
4413                                 s4ptr = iptr->val.a;
4414                                 l = s4ptr[0];                          /* default  */
4415                                 i = s4ptr[1];                          /* count    */
4416                         
4417                                 MCODECHECK((i<<2)+8);
4418                                 var_to_reg_int(s1, src, REG_ITMP1);    /* reg compare should always be faster */
4419                                 while (--i >= 0) {
4420                                         s4ptr += 2;
4421                                         ++tptr;
4422
4423                                         val = s4ptr[0];
4424                                         i386_alu_imm_reg(I386_CMP, val, s1);
4425                                         i386_jcc(I386_CC_E, 0);
4426                                         /* mcode_addreference(BlockPtrOfPC(s4ptr[1]), mcodeptr); */
4427                                         mcode_addreference((basicblock *) tptr[0], mcodeptr); 
4428                                 }
4429
4430                                 i386_jmp(0);
4431                                 /* mcode_addreference(BlockPtrOfPC(l), mcodeptr); */
4432                         
4433                                 tptr = (void **) iptr->target;
4434                                 mcode_addreference((basicblock *) tptr[0], mcodeptr);
4435
4436                                 ALIGNCODENOP;
4437                         }
4438                         break;
4439
4440
4441                 case ICMD_BUILTIN3:     /* ..., arg1, arg2, arg3 ==> ...              */
4442                                         /* op1 = return type, val.a = function pointer*/
4443                         s3 = 3;
4444                         goto gen_method;
4445
4446                 case ICMD_BUILTIN2:     /* ..., arg1, arg2 ==> ...                    */
4447                                         /* op1 = return type, val.a = function pointer*/
4448                         s3 = 2;
4449                         goto gen_method;
4450
4451                 case ICMD_BUILTIN1:     /* ..., arg1 ==> ...                          */
4452                                         /* op1 = return type, val.a = function pointer*/
4453                         s3 = 1;
4454                         goto gen_method;
4455
4456                 case ICMD_INVOKESTATIC: /* ..., [arg1, [arg2 ...]] ==> ...            */
4457                                         /* op1 = arg count, val.a = method pointer    */
4458
4459                 case ICMD_INVOKESPECIAL:/* ..., objectref, [arg1, [arg2 ...]] ==> ... */
4460                                         /* op1 = arg count, val.a = method pointer    */
4461
4462                 case ICMD_INVOKEVIRTUAL:/* ..., objectref, [arg1, [arg2 ...]] ==> ... */
4463                                         /* op1 = arg count, val.a = method pointer    */
4464
4465                 case ICMD_INVOKEINTERFACE:/*.., objectref, [arg1, [arg2 ...]] ==> ... */
4466                                         /* op1 = arg count, val.a = method pointer    */
4467
4468                         s3 = iptr->op1;
4469
4470 gen_method: {
4471                         methodinfo   *m;
4472                         classinfo    *ci;
4473
4474                         MCODECHECK((s3 << 1) + 64);
4475
4476                         /* copy arguments to registers or stack location                  */
4477
4478                         for (; --s3 >= 0; src = src->prev) {
4479                                 if (src->varkind == ARGVAR) {
4480                                         continue;
4481                                 }
4482
4483                                 if (IS_INT_LNG_TYPE(src->type)) {
4484                                         if (s3 < intreg_argnum) {
4485                                                 panic("No integer argument registers available!");
4486
4487                                         } else {
4488                                                 if (src->flags & INMEMORY) {
4489                                                         i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
4490                                                         i386_mov_reg_membase(REG_ITMP1, REG_SP, s3 * 8);
4491
4492                                                 } else {
4493                                                         i386_mov_reg_membase(src->regoff, REG_SP, s3 * 4);
4494                                                 }
4495                                         }
4496
4497                                 } else {
4498                                         if (s3 < fltreg_argnum) {
4499                                                 panic("No float argument registers available!");
4500
4501                                         } else {
4502                                                 var_to_reg_flt(d, src, REG_FTMP1);
4503                                                 M_DST(d, REG_SP, 8 * (s3 - FLT_ARG_CNT));
4504                                         }
4505                                 }
4506                         } /* end of for */
4507
4508                         m = iptr->val.a;
4509                         switch (iptr->opc) {
4510                                 case ICMD_BUILTIN3:
4511                                 case ICMD_BUILTIN2:
4512                                 case ICMD_BUILTIN1:
4513
4514                                         a = (s4) m;
4515                                         d = iptr->op1;
4516                                         i386_mov_imm_reg(a, REG_ITMP1);
4517                                         i386_call_reg(REG_ITMP1);
4518                                         break;
4519
4520                                 case ICMD_INVOKESTATIC:
4521                                 case ICMD_INVOKESPECIAL:
4522
4523                                         a = (s4) m->stubroutine;
4524                                         d = m->returntype;
4525                                         i386_mov_imm_reg(a, REG_ITMP2);
4526                                         i386_call_reg(REG_ITMP2);
4527                                         break;
4528
4529                                 case ICMD_INVOKEVIRTUAL:
4530
4531                                         i386_mov_membase_reg(REG_SP, 0, REG_ITMP2);
4532                                         gen_nullptr_check(REG_ITMP2);
4533                                         i386_mov_membase_reg(REG_ITMP2, OFFSET(java_objectheader, vftbl), REG_ITMP3);
4534                                         i386_mov_membase32_reg(REG_ITMP3, OFFSET(vftbl, table[0]) + sizeof(methodptr) * m->vftblindex, REG_ITMP1);
4535
4536                                         d = m->returntype;
4537                                         i386_call_reg(REG_ITMP1);
4538                                         break;
4539
4540                                 case ICMD_INVOKEINTERFACE:
4541                                         ci = m->class;
4542
4543                                         i386_mov_membase_reg(REG_SP, 0, REG_ITMP2);
4544                                         gen_nullptr_check(REG_ITMP2);
4545                                         i386_mov_membase_reg(REG_ITMP2, OFFSET(java_objectheader, vftbl), REG_ITMP3);
4546                                         i386_mov_membase_reg(REG_ITMP3, OFFSET(vftbl, interfacetable[0]) - sizeof(methodptr) * ci->index, REG_ITMP3);
4547                                         i386_mov_membase32_reg(REG_ITMP3, sizeof(methodptr) * (m - ci->methods), REG_ITMP1);
4548
4549                                         d = m->returntype;
4550                                         i386_call_reg(REG_ITMP1);
4551                                         break;
4552
4553                                 default:
4554                                         d = 0;
4555                                         sprintf (logtext, "Unkown ICMD-Command: %d", iptr->opc);
4556                                         error ();
4557                                 }
4558
4559                         /* d contains return type */
4560
4561                         if (d != TYPE_VOID) {
4562                                 d = reg_of_var(iptr->dst, REG_ITMP3);
4563
4564                                 if (IS_INT_LNG_TYPE(iptr->dst->type)) {
4565                                         if (IS_2_WORD_TYPE(iptr->dst->type)) {
4566                                                 if (iptr->dst->flags & INMEMORY) {
4567                                                         i386_mov_reg_membase(REG_RESULT, REG_SP, iptr->dst->regoff * 8);
4568                                                         i386_mov_reg_membase(REG_RESULT2, REG_SP, iptr->dst->regoff * 8 + 4);
4569
4570                                                 } else {
4571                                                         panic("longs have to be in memory");
4572                                                 }
4573
4574                                         } else {
4575                                                 if (iptr->dst->flags & INMEMORY) {
4576                                                         i386_mov_reg_membase(REG_RESULT, REG_SP, iptr->dst->regoff * 8);
4577
4578                                                 } else {
4579                                                         M_INTMOVE(REG_RESULT, iptr->dst->regoff);
4580                                                 }
4581                                         }
4582
4583                                 } else {
4584                                         /* nothing to do for float/double */
4585                                 }
4586                         }
4587                         }
4588                         break;
4589
4590
4591                 case ICMD_INSTANCEOF: /* ..., objectref ==> ..., intresult            */
4592
4593                                       /* op1:   0 == array, 1 == class                */
4594                                       /* val.a: (classinfo*) superclass               */
4595
4596 /*          superclass is an interface:
4597  *
4598  *          return (sub != NULL) &&
4599  *                 (sub->vftbl->interfacetablelength > super->index) &&
4600  *                 (sub->vftbl->interfacetable[-super->index] != NULL);
4601  *
4602  *          superclass is a class:
4603  *
4604  *          return ((sub != NULL) && (0
4605  *                  <= (sub->vftbl->baseval - super->vftbl->baseval) <=
4606  *                  super->vftbl->diffvall));
4607  */
4608
4609                         {
4610                         classinfo *super = (classinfo*) iptr->val.a;
4611                         
4612                         var_to_reg_int(s1, src, REG_ITMP1);
4613                         d = reg_of_var(iptr->dst, REG_ITMP3);
4614 /*                      if (s1 == d) { */
4615 /*                              M_MOV(s1, REG_ITMP1); */
4616 /*                              s1 = REG_ITMP1; */
4617 /*                      } */
4618                         if (iptr->op1) {                               /* class/interface */
4619                                 if (super->flags & ACC_INTERFACE) {        /* interface       */
4620                                         int offset = 0;
4621                                         i386_alu_imm_reg(I386_CMP, 0, s1);
4622
4623                                         /* TODO: clean up this calculation */
4624                                         offset += 2;
4625                                         CALCOFFSETBYTES(OFFSET(java_objectheader, vftbl));
4626
4627                                         offset += 2;
4628                                         CALCOFFSETBYTES(OFFSET(vftbl, interfacetablelength));
4629                                         
4630                                         offset += 2;
4631                                         CALCOFFSETBYTES(-super->index);
4632                                         
4633                                         offset += 3;
4634                                         offset += 6;
4635
4636                                         offset += 2;
4637                                         CALCOFFSETBYTES(OFFSET(vftbl, interfacetable[0]) - super->index * sizeof(methodptr*));
4638
4639                                         offset += 3;
4640                                         offset += 3;
4641
4642                                         i386_jcc(I386_CC_E, offset);
4643
4644                                         i386_mov_membase_reg(s1, OFFSET(java_objectheader, vftbl), REG_ITMP1);
4645                                         i386_mov_membase_reg(REG_ITMP1, OFFSET(vftbl, interfacetablelength), REG_ITMP2);
4646                                         i386_alu_imm_reg(I386_SUB, super->index, REG_ITMP2);
4647                                         i386_alu_imm_reg(I386_CMP, 0, REG_ITMP2);
4648
4649                                         /* TODO: clean up this calculation */
4650                                         offset = 0;
4651                                         offset += 2;
4652                                         CALCOFFSETBYTES(OFFSET(vftbl, interfacetable[0]) - super->index * sizeof(methodptr*));
4653
4654                                         offset += 3;
4655                                         offset += 3;
4656
4657                                         offset += 6;    /* jcc */
4658                                         offset += 5;
4659
4660                                         i386_jcc(I386_CC_LE, offset);
4661                                         i386_mov_membase_reg(REG_ITMP1, OFFSET(vftbl, interfacetable[0]) - super->index * sizeof(methodptr*), REG_ITMP1);
4662                                         i386_alu_reg_reg(I386_XOR, d, d);
4663                                         i386_alu_imm_reg(I386_CMP, 0, REG_ITMP1);
4664 /*                                      i386_setcc_reg(I386_CC_A, d); */
4665                                         i386_jcc(I386_CC_BE, 5);
4666                                         i386_mov_imm_reg(1, d);
4667                                         
4668
4669                                 } else {                                   /* class           */
4670                                         int offset = 0;
4671                                         i386_alu_imm_reg(I386_CMP, 0, s1);
4672
4673                                         /* TODO: clean up this calculation */
4674                                         offset += 2;
4675                                         CALCOFFSETBYTES(OFFSET(java_objectheader, vftbl));
4676
4677                                         offset += 5;
4678
4679                                         offset += 2;
4680                                         CALCOFFSETBYTES(OFFSET(vftbl, baseval));
4681                                         
4682                                         offset += 2;
4683                                         CALCOFFSETBYTES(OFFSET(vftbl, baseval));
4684                                         
4685                                         offset += 2;
4686                                         CALCOFFSETBYTES(OFFSET(vftbl, diffval));
4687                                         
4688                                         offset += 2;
4689                                         offset += 2;
4690                                         offset += 2;
4691
4692                                         offset += 6;    /* jcc */
4693                                         offset += 5;
4694
4695                                         i386_jcc(I386_CC_E, offset);
4696
4697                                         i386_mov_membase_reg(s1, OFFSET(java_objectheader, vftbl), REG_ITMP1);
4698                                         i386_mov_imm_reg((void *) super->vftbl, REG_ITMP2);
4699                                         i386_mov_membase_reg(REG_ITMP1, OFFSET(vftbl, baseval), REG_ITMP1);
4700                                         i386_mov_membase_reg(REG_ITMP2, OFFSET(vftbl, baseval), REG_ITMP3);
4701                                         i386_mov_membase_reg(REG_ITMP2, OFFSET(vftbl, diffval), REG_ITMP2);
4702                                         i386_alu_reg_reg(I386_SUB, REG_ITMP3, REG_ITMP1);
4703                                         i386_alu_reg_reg(I386_XOR, d, d);
4704                                         i386_alu_reg_reg(I386_CMP, REG_ITMP2, REG_ITMP1);
4705 /*                                      i386_setcc_reg(I386_CC_BE, d); */
4706                                         i386_jcc(I386_CC_A, 5);
4707                                         i386_mov_imm_reg(1, d);
4708                                         
4709                                 }
4710                         }
4711                         else
4712                                 panic ("internal error: no inlined array instanceof");
4713                         }
4714                         store_reg_to_var_int(iptr->dst, d);
4715                         break;
4716
4717                 case ICMD_CHECKCAST:  /* ..., objectref ==> ..., objectref            */
4718
4719                                       /* op1:   0 == array, 1 == class                */
4720                                       /* val.a: (classinfo*) superclass               */
4721
4722 /*          superclass is an interface:
4723  *
4724  *          OK if ((sub == NULL) ||
4725  *                 (sub->vftbl->interfacetablelength > super->index) &&
4726  *                 (sub->vftbl->interfacetable[-super->index] != NULL));
4727  *
4728  *          superclass is a class:
4729  *
4730  *          OK if ((sub == NULL) || (0
4731  *                 <= (sub->vftbl->baseval - super->vftbl->baseval) <=
4732  *                 super->vftbl->diffvall));
4733  */
4734
4735                         {
4736                         classinfo *super = (classinfo*) iptr->val.a;
4737                         
4738                         d = reg_of_var(iptr->dst, REG_ITMP3);
4739                         var_to_reg_int(s1, src, d);
4740                         if (iptr->op1) {                               /* class/interface */
4741                                 if (super->flags & ACC_INTERFACE) {        /* interface       */
4742                                         int offset = 0;
4743                                         i386_alu_imm_reg(I386_CMP, 0, s1);
4744
4745                                         /* TODO: clean up this calculation */
4746                                         offset += 2;
4747                                         CALCOFFSETBYTES(OFFSET(java_objectheader, vftbl));
4748
4749                                         offset += 2;
4750                                         CALCOFFSETBYTES(OFFSET(vftbl, interfacetablelength));
4751
4752                                         offset += 2;
4753                                         CALCOFFSETBYTES(-super->index);
4754
4755                                         offset += 3;
4756                                         offset += 6;
4757
4758                                         offset += 2;
4759                                         CALCOFFSETBYTES(OFFSET(vftbl, interfacetable[0]) - super->index * sizeof(methodptr*));
4760
4761                                         offset += 3;
4762                                         offset += 6;
4763
4764                                         i386_jcc(I386_CC_E, offset);
4765
4766                                         i386_mov_membase_reg(s1, OFFSET(java_objectheader, vftbl), REG_ITMP1);
4767                                         i386_mov_membase_reg(REG_ITMP1, OFFSET(vftbl, interfacetablelength), REG_ITMP2);
4768                                         i386_alu_imm_reg(I386_SUB, super->index, REG_ITMP2);
4769                                         i386_alu_imm_reg(I386_CMP, 0, REG_ITMP2);
4770                                         i386_jcc(I386_CC_LE, 0);
4771                                         mcode_addxcastrefs(mcodeptr);
4772                                         i386_mov_membase_reg(REG_ITMP1, OFFSET(vftbl, interfacetable[0]) - super->index * sizeof(methodptr*), REG_ITMP2);
4773                                         i386_alu_imm_reg(I386_CMP, 0, REG_ITMP2);
4774                                         i386_jcc(I386_CC_E, 0);
4775                                         mcode_addxcastrefs(mcodeptr);
4776
4777                                 } else {                                     /* class           */
4778                                         int offset = 0;
4779                                         i386_alu_imm_reg(I386_CMP, 0, s1);
4780
4781                                         /* TODO: clean up this calculation */
4782                                         offset += 2;
4783                                         CALCOFFSETBYTES(OFFSET(java_objectheader, vftbl));
4784
4785                                         offset += 5;
4786
4787                                         offset += 2;
4788                                         CALCOFFSETBYTES(OFFSET(vftbl, baseval));
4789
4790                                         if (d != REG_ITMP3) {
4791                                                 offset += 2;
4792                                                 CALCOFFSETBYTES(OFFSET(vftbl, baseval));
4793                                                 
4794                                                 offset += 2;
4795                                                 CALCOFFSETBYTES(OFFSET(vftbl, diffval));
4796
4797                                                 offset += 2;
4798                                                 
4799                                         } else {
4800                                                 offset += 2;
4801                                                 CALCOFFSETBYTES(OFFSET(vftbl, baseval));
4802
4803                                                 offset += 2;
4804
4805                                                 offset += 5;
4806
4807                                                 offset += 2;
4808                                                 CALCOFFSETBYTES(OFFSET(vftbl, diffval));
4809                                         }
4810
4811                                         offset += 2;
4812
4813                                         offset += 6;
4814
4815                                         i386_jcc(I386_CC_E, offset);
4816
4817                                         i386_mov_membase_reg(s1, OFFSET(java_objectheader, vftbl), REG_ITMP1);
4818                                         i386_mov_imm_reg((void *) super->vftbl, REG_ITMP2);
4819                                         i386_mov_membase_reg(REG_ITMP1, OFFSET(vftbl, baseval), REG_ITMP1);
4820                                         if (d != REG_ITMP3) {
4821                                                 i386_mov_membase_reg(REG_ITMP2, OFFSET(vftbl, baseval), REG_ITMP3);
4822                                                 i386_mov_membase_reg(REG_ITMP2, OFFSET(vftbl, diffval), REG_ITMP2);
4823                                                 i386_alu_reg_reg(I386_SUB, REG_ITMP3, REG_ITMP1);
4824
4825                                         } else {
4826                                                 i386_mov_membase_reg(REG_ITMP2, OFFSET(vftbl, baseval), REG_ITMP2);
4827                                                 i386_alu_reg_reg(I386_SUB, REG_ITMP2, REG_ITMP1);
4828                                                 i386_mov_imm_reg((void *) super->vftbl, REG_ITMP2);
4829                                                 i386_mov_membase_reg(REG_ITMP2, OFFSET(vftbl, diffval), REG_ITMP2);
4830                                         }
4831                                         i386_alu_reg_reg(I386_CMP, REG_ITMP2, REG_ITMP1);
4832                                         i386_jcc(I386_CC_B, 0);
4833                                         mcode_addxcastrefs(mcodeptr);
4834                                         }
4835                                 }
4836                         else
4837                                 panic ("internal error: no inlined array checkcast");
4838                         }
4839                         M_INTMOVE(s1, d);
4840                         store_reg_to_var_int(iptr->dst, d);
4841                         break;
4842
4843                 case ICMD_CHECKASIZE:  /* ..., size ==> ..., size                     */
4844
4845                         if (src->flags & INMEMORY) {
4846                                 i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4847                                 
4848                         } else {
4849                                 i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4850                         }
4851                         i386_jcc(I386_CC_L, 0);
4852                         mcode_addxcheckarefs(mcodeptr);
4853                         break;
4854
4855                 case ICMD_MULTIANEWARRAY:/* ..., cnt1, [cnt2, ...] ==> ..., arrayref  */
4856                                       /* op1 = dimension, val.a = array descriptor    */
4857
4858                         /* check for negative sizes and copy sizes to stack if necessary  */
4859
4860                         MCODECHECK((iptr->op1 << 1) + 64);
4861
4862                         for (s1 = iptr->op1; --s1 >= 0; src = src->prev) {
4863                                 if (src->flags & INMEMORY) {
4864                                         i386_alu_imm_membase(I386_CMP, 0, REG_SP, src->regoff * 8);
4865
4866                                 } else {
4867                                         i386_alu_imm_reg(I386_CMP, 0, src->regoff);
4868                                 }
4869                                 i386_jcc(I386_CC_LE, 0);
4870                                 mcode_addxcheckarefs(mcodeptr);
4871
4872                                 /* 
4873                                  * copy sizes to new stack location, be cause native function
4874                                  * builtin_nmultianewarray access them as (int *)
4875                                  */
4876                                 i386_mov_membase_reg(REG_SP, src->regoff * 8, REG_ITMP1);
4877                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, -(iptr->op1 - s1) * 4);
4878
4879                                 /* copy sizes to stack (argument numbers >= INT_ARG_CNT)      */
4880
4881                                 if (src->varkind != ARGVAR) {
4882                                         if (src->flags & INMEMORY) {
4883                                                 i386_mov_membase_reg(REG_SP, (src->regoff + intreg_argnum) * 8, REG_ITMP1);
4884                                                 i386_mov_reg_membase(REG_ITMP1, REG_SP, (s1 + intreg_argnum) * 8);
4885
4886                                         } else {
4887                                                 i386_mov_reg_membase(src->regoff, REG_SP, (s1 + intreg_argnum) * 8);
4888                                         }
4889                                 }
4890                         }
4891                         i386_alu_imm_reg(I386_SUB, iptr->op1 * 4, REG_SP);
4892
4893                         /* a0 = dimension count */
4894
4895                         /* save stack pointer */
4896                         M_INTMOVE(REG_SP, REG_ITMP1);
4897
4898                         i386_alu_imm_reg(I386_SUB, 12, REG_SP);
4899                         i386_mov_imm_membase(iptr->op1, REG_SP, 0);
4900
4901                         /* a1 = arraydescriptor */
4902
4903                         i386_mov_imm_membase(iptr->val.a, REG_SP, 4);
4904
4905                         /* a2 = pointer to dimensions = stack pointer */
4906
4907                         i386_mov_reg_membase(REG_ITMP1, REG_SP, 8);
4908
4909                         i386_mov_imm_reg((void*) (builtin_nmultianewarray), REG_ITMP1);
4910                         i386_call_reg(REG_ITMP1);
4911                         i386_alu_imm_reg(I386_ADD, 12 + iptr->op1 * 4, REG_SP);
4912
4913                         s1 = reg_of_var(iptr->dst, REG_RESULT);
4914                         M_INTMOVE(REG_RESULT, s1);
4915                         store_reg_to_var_int(iptr->dst, s1);
4916                         break;
4917
4918
4919                 default: sprintf (logtext, "Unknown pseudo command: %d", iptr->opc);
4920                          error();
4921         
4922    
4923
4924         } /* switch */
4925                 
4926         } /* for instruction */
4927                 
4928         /* copy values to interface registers */
4929
4930         src = bptr->outstack;
4931         len = bptr->outdepth;
4932         MCODECHECK(64+len);
4933         while (src) {
4934                 len--;
4935                 if ((src->varkind != STACKVAR)) {
4936                         s2 = src->type;
4937                         if (IS_FLT_DBL_TYPE(s2)) {
4938                                 var_to_reg_flt(s1, src, REG_FTMP1);
4939                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
4940                                         M_FLTMOVE(s1,interfaces[len][s2].regoff);
4941                                         }
4942                                 else {
4943                                         M_DST(s1, REG_SP, 8 * interfaces[len][s2].regoff);
4944                                         }
4945                                 }
4946                         else {
4947                                 var_to_reg_int(s1, src, REG_ITMP1);
4948                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
4949                                         M_INTMOVE(s1,interfaces[len][s2].regoff);
4950                                         }
4951                                 else {
4952                                         M_LST(s1, REG_SP, 8 * interfaces[len][s2].regoff);
4953                                         }
4954                                 }
4955                         }
4956                 src = src->prev;
4957                 }
4958         } /* if (bptr -> flags >= BBREACHED) */
4959         } /* for basic block */
4960
4961         /* bptr -> mpc = (int)((u1*) mcodeptr - mcodebase); */
4962
4963         {
4964
4965         /* generate bound check stubs */
4966         s4 *xcodeptr = NULL;
4967         
4968         for (; xboundrefs != NULL; xboundrefs = xboundrefs->next) {
4969                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
4970                         gen_resolvebranch((u1*) mcodebase + xboundrefs->branchpos, 
4971                                 xboundrefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - (5 + 3));
4972                         continue;
4973                         }
4974
4975
4976                 gen_resolvebranch((u1*) mcodebase + xboundrefs->branchpos, 
4977                                   xboundrefs->branchpos, (u1*) mcodeptr - mcodebase);
4978
4979                 MCODECHECK(8);
4980
4981                 i386_mov_imm_reg(0, REG_ITMP2_XPC);    /* 5 bytes */
4982                 dseg_adddata(mcodeptr);
4983                 i386_alu_imm_reg(I386_ADD, xboundrefs->branchpos - 4, REG_ITMP2_XPC);    /* 3 bytes */
4984
4985                 if (xcodeptr != NULL) {
4986                         i386_jmp((xcodeptr - mcodeptr) - 1);
4987
4988                 } else {
4989                         xcodeptr = mcodeptr;
4990
4991                         i386_mov_imm_reg(proto_java_lang_ArrayIndexOutOfBoundsException, REG_ITMP1_XPTR);
4992                         i386_mov_imm_reg(asm_handle_exception, REG_ITMP3);
4993                         i386_jmp_reg(REG_ITMP3);
4994                 }
4995         }
4996
4997         /* generate negative array size check stubs */
4998         xcodeptr = NULL;
4999         
5000         for (; xcheckarefs != NULL; xcheckarefs = xcheckarefs->next) {
5001                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
5002                         gen_resolvebranch((u1*) mcodebase + xcheckarefs->branchpos, 
5003                                 xcheckarefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - (5 + 3));
5004                         continue;
5005                         }
5006
5007                 gen_resolvebranch((u1*) mcodebase + xcheckarefs->branchpos, 
5008                                   xcheckarefs->branchpos, (u1*) mcodeptr - mcodebase);
5009
5010                 MCODECHECK(8);
5011
5012                 i386_mov_imm_reg(0, REG_ITMP2_XPC);    /* 5 bytes */
5013                 dseg_adddata(mcodeptr);
5014                 i386_alu_imm_reg(I386_ADD, xcheckarefs->branchpos - 4, REG_ITMP2_XPC);    /* 3 bytes */
5015
5016                 if (xcodeptr != NULL) {
5017                         i386_jmp((xcodeptr - mcodeptr) - 1);
5018
5019                 } else {
5020                         xcodeptr = mcodeptr;
5021
5022                         i386_mov_imm_reg(proto_java_lang_NegativeArraySizeException, REG_ITMP1_XPTR);
5023                         i386_mov_imm_reg(asm_handle_exception, REG_ITMP3);
5024                         i386_jmp_reg(REG_ITMP3);
5025                 }
5026         }
5027
5028         /* generate cast check stubs */
5029         xcodeptr = NULL;
5030         
5031         for (; xcastrefs != NULL; xcastrefs = xcastrefs->next) {
5032                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
5033                         gen_resolvebranch((u1*) mcodebase + xcastrefs->branchpos, 
5034                                 xcastrefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - (5 + 3));
5035                         continue;
5036                 }
5037
5038                 gen_resolvebranch((u1*) mcodebase + xcastrefs->branchpos, 
5039                                   xcastrefs->branchpos, (u1*) mcodeptr - mcodebase);
5040
5041                 MCODECHECK(8);
5042
5043                 i386_mov_imm_reg(0, REG_ITMP2_XPC);    /* 5 bytes */
5044                 dseg_adddata(mcodeptr);
5045                 i386_alu_imm_reg(I386_ADD, xcastrefs->branchpos - 4, REG_ITMP2_XPC);    /* 3 bytes (max. 6 bytes) */
5046
5047                 if (xcodeptr != NULL) {
5048                         i386_jmp(((u1 *) xcodeptr - (u1 *) mcodeptr) - 4);
5049                 
5050                 } else {
5051                         xcodeptr = mcodeptr;
5052
5053                         i386_mov_imm_reg(proto_java_lang_ClassCastException, REG_ITMP1_XPTR);
5054                         i386_mov_imm_reg(asm_handle_exception, REG_ITMP3);
5055                         i386_jmp_reg(REG_ITMP3);
5056                 }
5057         }
5058
5059 #ifdef SOFTNULLPTRCHECK
5060
5061         /* generate cast check stubs */
5062         xcodeptr = NULL;
5063         
5064         for (; xnullrefs != NULL; xnullrefs = xnullrefs->next) {
5065                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
5066                         gen_resolvebranch((u1*) mcodebase + xnullrefs->branchpos, 
5067                                 xnullrefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - 4);
5068                         continue;
5069                 }
5070
5071                 gen_resolvebranch((u1*) mcodebase + xnullrefs->branchpos, 
5072                                   xnullrefs->branchpos, (u1*) mcodeptr - mcodebase);
5073
5074                 MCODECHECK(8);
5075
5076                 i386_mov_imm_reg(0, REG_ITMP2_XPC);    /* 5 bytes */
5077                 dseg_adddata(mcodeptr);
5078                 i386_alu_imm_reg(I386_ADD, xnullrefs->branchpos - 4, REG_ITMP2_XPC);    /* 3 bytes */
5079
5080                 if (xcodeptr != NULL) {
5081                         i386_jmp((xcodeptr - mcodeptr) - 1);
5082                 
5083                 } else {
5084                         xcodeptr = mcodeptr;
5085
5086                         i386_mov_imm_reg(proto_java_lang_NullPointerException, REG_ITMP1_XPTR);
5087                         i386_mov_imm_reg(asm_handle_exception, REG_ITMP3);
5088                         i386_jmp_reg(REG_ITMP3);
5089                 }
5090         }
5091
5092 #endif
5093         }
5094
5095         mcode_finish((int)((u1*) mcodeptr - mcodebase));
5096 }
5097
5098
5099 /* function createcompilerstub *************************************************
5100
5101         creates a stub routine which calls the compiler
5102         
5103 *******************************************************************************/
5104
5105 #define COMPSTUBSIZE 3
5106
5107 u1 *createcompilerstub (methodinfo *m)
5108 {
5109         u8 *s = CNEW (u8, COMPSTUBSIZE);    /* memory to hold the stub            */
5110         s4 *p = (s4*) s;                    /* code generation pointer            */
5111
5112         s4 *mcodeptr = p;                                       /* make macros work                   */
5113         
5114                                             /* code for the stub                  */
5115         i386_mov_imm_reg(m, I386_EAX);      /* pass method pointer to compiler    */
5116         i386_mov_imm_reg(asm_call_jit_compiler, REG_ITMP2);    /* load address    */
5117         i386_jmp_reg(REG_ITMP2);            /* jump to compiler                   */
5118
5119 #ifdef STATISTICS
5120         count_cstub_len += COMPSTUBSIZE * 8;
5121 #endif
5122
5123         return (u1*) s;
5124 }
5125
5126
5127 /* function removecompilerstub *************************************************
5128
5129      deletes a compilerstub from memory  (simply by freeing it)
5130
5131 *******************************************************************************/
5132
5133 void removecompilerstub (u1 *stub) 
5134 {
5135         CFREE (stub, COMPSTUBSIZE * 8);
5136 }
5137
5138 /* function: createnativestub **************************************************
5139
5140         creates a stub routine which calls a native method
5141
5142 *******************************************************************************/
5143
5144 #define NATIVESTUBSIZE 18
5145
5146 u1 *createnativestub (functionptr f, methodinfo *m)
5147 {
5148         u8 *s = CNEW (u8, NATIVESTUBSIZE);  /* memory to hold the stub            */
5149         s4 *p = (s4*) s;                    /* code generation pointer            */
5150
5151         /* TWISTI: get rid of those 2nd defines */
5152         s4 *mcodeptr = p;
5153         
5154         reg_init();
5155
5156         /* TWISTI */
5157 /*      M_MOV  (argintregs[4],argintregs[5]);  */
5158 /*      M_FMOV (argfltregs[4],argfltregs[5]); */
5159
5160 /*      M_MOV  (argintregs[3],argintregs[4]); */
5161 /*      M_FMOV (argfltregs[3],argfltregs[4]); */
5162
5163 /*      M_MOV  (argintregs[2],argintregs[3]); */
5164 /*      M_FMOV (argfltregs[2],argfltregs[3]); */
5165
5166 /*      M_MOV  (argintregs[1],argintregs[2]); */
5167 /*      M_FMOV (argfltregs[1],argfltregs[2]); */
5168
5169 /*      M_MOV  (argintregs[0],argintregs[1]); */
5170 /*      M_FMOV (argfltregs[0],argfltregs[1]); */
5171
5172 /*      M_ALD  (argintregs[0], REG_PV, 17*8); /* load adress of jni_environement  */
5173
5174 /*      M_LDA  (REG_SP, REG_SP, -8);        /* build up stackframe                */
5175 /*      M_AST  (REG_RA, REG_SP, 0);         /* store return address               */
5176
5177 /*      M_ALD  (REG_PV, REG_PV, 14*8);      /* load adress of native method       */
5178 /*      M_JSR  (REG_RA, REG_PV);            /* call native method                 */
5179
5180 /*      utf_fprint(stderr, m->name); */
5181 /*      fprintf(stderr, " paramcount=%d paramtypes=%x\n", m->paramcount, m->paramtypes); */
5182
5183         i386_alu_imm_reg(I386_SUB, 24, REG_SP); /* 20 = 5 * 4 (5 params * 4 bytes)    */
5184
5185         i386_mov_membase_reg(REG_SP, 24 + 4, REG_ITMP1);
5186         i386_mov_reg_membase(REG_ITMP1, REG_SP, 4);
5187
5188         i386_mov_membase_reg(REG_SP, 32 + 4, REG_ITMP1);
5189         i386_mov_reg_membase(REG_ITMP1, REG_SP, 8);
5190
5191         i386_mov_membase_reg(REG_SP, 40 + 4, REG_ITMP1);
5192         i386_mov_reg_membase(REG_ITMP1, REG_SP, 12);
5193
5194         i386_mov_membase_reg(REG_SP, 48 + 4, REG_ITMP1);
5195         i386_mov_reg_membase(REG_ITMP1, REG_SP, 16);
5196
5197         i386_mov_membase_reg(REG_SP, 56 + 4, REG_ITMP1);
5198         i386_mov_reg_membase(REG_ITMP1, REG_SP, 20);
5199
5200         i386_mov_imm_membase(&env, REG_SP, 0);
5201
5202         i386_mov_imm_reg(f, REG_ITMP1);
5203         i386_call_reg(REG_ITMP1);
5204
5205         i386_alu_imm_reg(I386_ADD, 24, REG_SP);
5206
5207 /*      M_LDA  (REG_PV, REG_RA, -15*4);      /* recompute pv from ra               */
5208 /*      M_ALD  (REG_ITMP3, REG_PV, 15*8);    /* get address of exceptionptr        */
5209
5210 /*      M_ALD  (REG_RA, REG_SP, 0);         /* load return address                */
5211 /*      M_ALD  (REG_ITMP1, REG_ITMP3, 0);   /* load exception into reg. itmp1     */
5212
5213 /*      M_LDA  (REG_SP, REG_SP, 8);         /* remove stackframe                  */
5214 /*      M_BNEZ (REG_ITMP1, 1);              /* if no exception then return        */
5215
5216 /*      M_RET  (REG_ZERO, REG_RA);          /* return to caller                   */
5217         i386_ret();
5218
5219 /*      M_AST  (REG_ZERO, REG_ITMP3, 0);    /* store NULL into exceptionptr       */
5220 /*      M_LDA  (REG_ITMP2, REG_RA, -4);     /* move fault address into reg. itmp2 */
5221
5222 /*      M_ALD  (REG_ITMP3, REG_PV,16*8);    /* load asm exception handler address */
5223 /*      M_JMP  (REG_ZERO, REG_ITMP3);       /* jump to asm exception handler      */
5224
5225
5226         /* TWISTI */    
5227 /*      s[14] = (u8) f;                      /* address of native method          */
5228 /*      s[15] = (u8) (&exceptionptr);        /* address of exceptionptr           */
5229 /*      s[16] = (u8) (asm_handle_nat_exception); /* addr of asm exception handler */
5230 /*      s[17] = (u8) (&env);                  /* addr of jni_environement         */
5231         s[14] = (u4) f;                      /* address of native method          */
5232         s[15] = (u8) (&exceptionptr);        /* address of exceptionptr           */
5233         s[16] = (u8) (asm_handle_nat_exception); /* addr of asm exception handler */
5234         s[17] = (u8) (&env);                  /* addr of jni_environement         */
5235
5236 #ifdef STATISTICS
5237         count_nstub_len += NATIVESTUBSIZE * 8;
5238 #endif
5239
5240         return (u1*) s;
5241 }
5242
5243 /* function: removenativestub **************************************************
5244
5245     removes a previously created native-stub from memory
5246     
5247 *******************************************************************************/
5248
5249 void removenativestub (u1 *stub)
5250 {
5251         CFREE (stub, NATIVESTUBSIZE * 8);
5252 }
5253
5254
5255 /*
5256  * These are local overrides for various environment variables in Emacs.
5257  * Please do not remove this and leave it at the end of the file, where
5258  * Emacs will automagically detect them.
5259  * ---------------------------------------------------------------------
5260  * Local variables:
5261  * mode: c
5262  * indent-tabs-mode: t
5263  * c-basic-offset: 4
5264  * tab-width: 4
5265  * End:
5266  */