Major file restructuring.
[cacao.git] / src / vm / jit / alpha / codegen.c
1 /* jit/alpha/codegen.c - machine code generator for alpha
2
3    Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003
4    Institut f. Computersprachen, TU Wien
5    R. Grafl, A. Krall, C. Kruegel, C. Oates, R. Obermaisser, M. Probst,
6    S. Ring, E. Steiner, C. Thalinger, D. Thuernbeck, P. Tomsich,
7    J. Wenninger
8
9    This file is part of CACAO.
10
11    This program is free software; you can redistribute it and/or
12    modify it under the terms of the GNU General Public License as
13    published by the Free Software Foundation; either version 2, or (at
14    your option) any later version.
15
16    This program is distributed in the hope that it will be useful, but
17    WITHOUT ANY WARRANTY; without even the implied warranty of
18    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19    General Public License for more details.
20
21    You should have received a copy of the GNU General Public License
22    along with this program; if not, write to the Free Software
23    Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA
24    02111-1307, USA.
25
26    Contact: cacao@complang.tuwien.ac.at
27
28    Authors: Andreas Krall
29             Reinhard Grafl
30
31    $Id: codegen.c 557 2003-11-02 22:51:59Z twisti $
32
33 */
34
35
36 #include <stdio.h>
37 #include <signal.h>
38 #include "types.h"
39 #include "codegen.h"
40 #include "jit.h"
41 #include "reg.h"
42 #include "builtin.h"
43 #include "asmpart.h"
44 #include "jni.h"
45 #include "loader.h"
46 #include "tables.h"
47 #include "native.h"
48
49 /* include independent code generation stuff */
50 #include "codegen.inc"
51 #include "reg.inc"
52
53
54 /* *****************************************************************************
55
56 Datatypes and Register Allocations:
57 ----------------------------------- 
58
59 On 64-bit-machines (like the Alpha) all operands are stored in the
60 registers in a 64-bit form, even when the correspondig JavaVM  operands
61 only need 32 bits. This is done by a canonical representation:
62
63 32-bit integers are allways stored as sign-extended 64-bit values (this
64 approach is directly supported by the Alpha architecture and is very easy
65 to implement).
66
67 32-bit-floats are stored in a 64-bit doubleprecision register by simply
68 expanding the exponent and mantissa with zeroes. (also supported by the
69 architecture)
70
71
72 Stackframes:
73
74 The calling conventions and the layout of the stack is  explained in detail
75 in the documention file: calling.doc
76
77 *******************************************************************************/
78
79
80 /* additional functions and macros to generate code ***************************/
81
82 /* #define BlockPtrOfPC(pc)        block+block_index[pc] */
83 #define BlockPtrOfPC(pc)  ((basicblock *) iptr->target)
84
85
86 #ifdef STATISTICS
87 #define COUNT_SPILLS count_spills++
88 #else
89 #define COUNT_SPILLS
90 #endif
91
92
93 /* gen_nullptr_check(objreg) */
94
95 #ifdef SOFTNULLPTRCHECK
96 #define gen_nullptr_check(objreg) \
97         if (checknull) {\
98         M_BEQZ((objreg), 0);\
99         mcode_addxnullrefs(mcodeptr);\
100         }
101 #else
102 #define gen_nullptr_check(objreg)
103 #endif
104
105
106 /* MCODECHECK(icnt) */
107
108 #define MCODECHECK(icnt) \
109         if((mcodeptr+(icnt))>mcodeend)mcodeptr=mcode_increase((u1*)mcodeptr)
110
111 /* M_INTMOVE:
112      generates an integer-move from register a to b.
113      if a and b are the same int-register, no code will be generated.
114 */ 
115
116 #define M_INTMOVE(a,b) if(a!=b){M_MOV(a,b);}
117
118
119 /* M_FLTMOVE:
120     generates a floating-point-move from register a to b.
121     if a and b are the same float-register, no code will be generated
122 */ 
123
124 #define M_FLTMOVE(a,b) if(a!=b){M_FMOV(a,b);}
125
126
127 /* var_to_reg_xxx:
128     this function generates code to fetch data from a pseudo-register
129     into a real register. 
130     If the pseudo-register has actually been assigned to a real 
131     register, no code will be emitted, since following operations
132     can use this register directly.
133     
134     v: pseudoregister to be fetched from
135     tempregnum: temporary register to be used if v is actually spilled to ram
136
137     return: the register number, where the operand can be found after 
138             fetching (this wil be either tempregnum or the register
139             number allready given to v)
140 */
141
142 #define var_to_reg_int(regnr,v,tempnr) { \
143         if ((v)->flags & INMEMORY) \
144                 {COUNT_SPILLS;M_LLD(tempnr,REG_SP,8*(v)->regoff);regnr=tempnr;} \
145         else regnr=(v)->regoff; \
146 }
147
148
149 #define var_to_reg_flt(regnr,v,tempnr) { \
150         if ((v)->flags & INMEMORY) \
151                 {COUNT_SPILLS;M_DLD(tempnr,REG_SP,8*(v)->regoff);regnr=tempnr;} \
152         else regnr=(v)->regoff; \
153 }
154
155
156 /* reg_of_var:
157     This function determines a register, to which the result of an operation
158     should go, when it is ultimatively intended to store the result in
159     pseudoregister v.
160     If v is assigned to an actual register, this register will be returned.
161     Otherwise (when v is spilled) this function returns tempregnum.
162     If not already done, regoff and flags are set in the stack location.
163 */        
164
165 static int reg_of_var(stackptr v, int tempregnum)
166 {
167         varinfo      *var;
168
169         switch (v->varkind) {
170                 case TEMPVAR:
171                         if (!(v->flags & INMEMORY))
172                                 return(v->regoff);
173                         break;
174                 case STACKVAR:
175                         var = &(interfaces[v->varnum][v->type]);
176                         v->regoff = var->regoff;
177                         if (!(var->flags & INMEMORY))
178                                 return(var->regoff);
179                         break;
180                 case LOCALVAR:
181                         var = &(locals[v->varnum][v->type]);
182                         v->regoff = var->regoff;
183                         if (!(var->flags & INMEMORY))
184                                 return(var->regoff);
185                         break;
186                 case ARGVAR:
187                         v->regoff = v->varnum;
188                         if (IS_FLT_DBL_TYPE(v->type)) {
189                                 if (v->varnum < fltreg_argnum) {
190                                         v->regoff = argfltregs[v->varnum];
191                                         return(argfltregs[v->varnum]);
192                                         }
193                                 }
194                         else
195                                 if (v->varnum < intreg_argnum) {
196                                         v->regoff = argintregs[v->varnum];
197                                         return(argintregs[v->varnum]);
198                                         }
199                         v->regoff -= intreg_argnum;
200                         break;
201                 }
202         v->flags |= INMEMORY;
203         return tempregnum;
204 }
205
206
207 /* store_reg_to_var_xxx:
208     This function generates the code to store the result of an operation
209     back into a spilled pseudo-variable.
210     If the pseudo-variable has not been spilled in the first place, this 
211     function will generate nothing.
212     
213     v ............ Pseudovariable
214     tempregnum ... Number of the temporary registers as returned by
215                    reg_of_var.
216 */      
217
218 #define store_reg_to_var_int(sptr, tempregnum) {       \
219         if ((sptr)->flags & INMEMORY) {                    \
220                 COUNT_SPILLS;                                  \
221                 M_LST(tempregnum, REG_SP, 8 * (sptr)->regoff); \
222                 }                                              \
223         }
224
225 #define store_reg_to_var_flt(sptr, tempregnum) {       \
226         if ((sptr)->flags & INMEMORY) {                    \
227                 COUNT_SPILLS;                                  \
228                 M_DST(tempregnum, REG_SP, 8 * (sptr)->regoff); \
229                 }                                              \
230         }
231
232
233 /* NullPointerException handlers and exception handling initialisation        */
234
235 typedef struct sigctx_struct {
236
237         long          sc_onstack;           /* sigstack state to restore          */
238         long          sc_mask;              /* signal mask to restore             */
239         long          sc_pc;                /* pc at time of signal               */
240         long          sc_ps;                /* psl to retore                      */
241         long          sc_regs[32];          /* processor regs 0 to 31             */
242         long          sc_ownedfp;           /* fp has been used                   */
243         long          sc_fpregs[32];        /* fp regs 0 to 31                    */
244         unsigned long sc_fpcr;              /* floating point control register    */
245         unsigned long sc_fp_control;        /* software fpcr                      */
246                                             /* rest is unused                     */
247         unsigned long sc_reserved1, sc_reserved2;
248         unsigned long sc_ssize;
249         char          *sc_sbase;
250         unsigned long sc_traparg_a0;
251         unsigned long sc_traparg_a1;
252         unsigned long sc_traparg_a2;
253         unsigned long sc_fp_trap_pc;
254         unsigned long sc_fp_trigger_sum;
255         unsigned long sc_fp_trigger_inst;
256         unsigned long sc_retcode[2];
257 } sigctx_struct;
258
259
260 /* NullPointerException signal handler for hardware null pointer check */
261
262 void catch_NullPointerException(int sig, int code, sigctx_struct *sigctx)
263 {
264         sigset_t nsig;
265         int      instr;
266         long     faultaddr;
267
268         /* Reset signal handler - necessary for SysV, does no harm for BSD */
269
270         instr = *((int*)(sigctx->sc_pc));
271         faultaddr = sigctx->sc_regs[(instr >> 16) & 0x1f];
272
273         if (faultaddr == 0) {
274                 signal(sig, (void*) catch_NullPointerException); /* reinstall handler */
275                 sigemptyset(&nsig);
276                 sigaddset(&nsig, sig);
277                 sigprocmask(SIG_UNBLOCK, &nsig, NULL);           /* unblock signal    */
278                 sigctx->sc_regs[REG_ITMP1_XPTR] =
279                                             (long) proto_java_lang_NullPointerException;
280                 sigctx->sc_regs[REG_ITMP2_XPC] = sigctx->sc_pc;
281                 sigctx->sc_pc = (long) asm_handle_exception;
282                 return;
283                 }
284         else {
285                 faultaddr += (long) ((instr << 16) >> 16);
286                 fprintf(stderr, "faulting address: 0x%16lx\n", faultaddr);
287                 panic("Stack overflow");
288                 }
289 }
290
291
292 #ifdef __osf__
293
294 void init_exceptions(void)
295 {
296
297 #else /* Linux */
298
299 /* Linux on Digital Alpha needs an initialisation of the ieee floating point
300         control for IEEE compliant arithmetic (option -mieee of GCC). Under
301         Digital Unix this is done automatically.
302 */
303
304 #include <asm/fpu.h>
305
306 extern unsigned long ieee_get_fp_control();
307 extern void ieee_set_fp_control(unsigned long fp_control);
308
309 void init_exceptions(void)
310 {
311 /* initialize floating point control */
312
313 ieee_set_fp_control(ieee_get_fp_control()
314                     & ~IEEE_TRAP_ENABLE_INV
315                     & ~IEEE_TRAP_ENABLE_DZE
316 /*                  & ~IEEE_TRAP_ENABLE_UNF   we dont want underflow */
317                     & ~IEEE_TRAP_ENABLE_OVF);
318 #endif
319
320         /* install signal handlers we need to convert to exceptions */
321
322         if (!checknull) {
323
324 #if defined(SIGSEGV)
325                 signal(SIGSEGV, (void*) catch_NullPointerException);
326 #endif
327
328 #if defined(SIGBUS)
329                 signal(SIGBUS, (void*) catch_NullPointerException);
330 #endif
331                 }
332 }
333
334
335 /* function gen_mcode **********************************************************
336
337         generates machine code
338
339 *******************************************************************************/
340
341 #define         MethodPointer   -8
342 #define         FrameSize       -12
343 #define     IsSync          -16
344 #define     IsLeaf          -20
345 #define     IntSave         -24
346 #define     FltSave         -28
347 #define     ExTableSize     -32
348 #define     ExTableStart    -32
349
350 #define     ExEntrySize     -32
351 #define     ExStartPC       -8
352 #define     ExEndPC         -16
353 #define     ExHandlerPC     -24
354 #define     ExCatchType     -32
355
356 void codegen()
357 {
358         int  len, s1, s2, s3, d, bbs;
359         s4   a;
360         s4          *mcodeptr;
361         stackptr    src;
362         varinfo     *var;
363         basicblock  *bptr;
364         instruction *iptr;
365         xtable *ex;
366
367         {
368         int p, pa, t, l, r;
369
370         savedregs_num = (isleafmethod) ? 0 : 1;           /* space to save the RA */
371
372         /* space to save used callee saved registers */
373
374         savedregs_num += (savintregcnt - maxsavintreguse);
375         savedregs_num += (savfltregcnt - maxsavfltreguse);
376
377         parentargs_base = maxmemuse + savedregs_num;
378
379 #ifdef USE_THREADS                 /* space to save argument of monitor_enter */
380
381         if (checksync && (method->flags & ACC_SYNCHRONIZED))
382                 parentargs_base++;
383
384 #endif
385
386         /* create method header */
387
388         (void) dseg_addaddress(method);                         /* MethodPointer  */
389         (void) dseg_adds4(parentargs_base * 8);                 /* FrameSize      */
390
391 #ifdef USE_THREADS
392
393         /* IsSync contains the offset relative to the stack pointer for the
394            argument of monitor_exit used in the exception handler. Since the
395            offset could be zero and give a wrong meaning of the flag it is
396            offset by one.
397         */
398
399         if (checksync && (method->flags & ACC_SYNCHRONIZED))
400                 (void) dseg_adds4((maxmemuse + 1) * 8);             /* IsSync         */
401         else
402
403 #endif
404
405         (void) dseg_adds4(0);                                   /* IsSync         */
406                                                
407         (void) dseg_adds4(isleafmethod);                        /* IsLeaf         */
408         (void) dseg_adds4(savintregcnt - maxsavintreguse);      /* IntSave        */
409         (void) dseg_adds4(savfltregcnt - maxsavfltreguse);      /* FltSave        */
410         (void) dseg_adds4(exceptiontablelength);                /* ExTableSize    */
411
412         /* create exception table */
413
414         for (ex = extable; ex != NULL; ex = ex->down) {
415
416 #ifdef LOOP_DEBUG       
417                 if (ex->start != NULL)
418                         printf("adding start - %d - ", ex->start->debug_nr);
419                 else {
420                         printf("PANIC - start is NULL");
421                         exit(-1);
422                 }
423 #endif
424
425                 dseg_addtarget(ex->start);
426
427 #ifdef LOOP_DEBUG                       
428                 if (ex->end != NULL)
429                         printf("adding end - %d - ", ex->end->debug_nr);
430                 else {
431                         printf("PANIC - end is NULL");
432                         exit(-1);
433                 }
434 #endif
435
436                 dseg_addtarget(ex->end);
437
438 #ifdef LOOP_DEBUG               
439                 if (ex->handler != NULL)
440                         printf("adding handler - %d\n", ex->handler->debug_nr);
441                 else {
442                         printf("PANIC - handler is NULL");
443                         exit(-1);
444                 }
445 #endif
446
447                 dseg_addtarget(ex->handler);
448            
449                 (void) dseg_addaddress(ex->catchtype);
450                 }
451         
452         /* initialize mcode variables */
453         
454         mcodeptr = (s4*) mcodebase;
455         mcodeend = (s4*) (mcodebase + mcodesize);
456         MCODECHECK(128 + mparamcount);
457
458         /* create stack frame (if necessary) */
459
460         if (parentargs_base)
461                 {M_LDA (REG_SP, REG_SP, -parentargs_base * 8);}
462
463         /* save return address and used callee saved registers */
464
465         p = parentargs_base;
466         if (!isleafmethod)
467                 {p--;  M_AST (REG_RA, REG_SP, 8*p);}
468         for (r = savintregcnt - 1; r >= maxsavintreguse; r--)
469                 {p--; M_LST (savintregs[r], REG_SP, 8 * p);}
470         for (r = savfltregcnt - 1; r >= maxsavfltreguse; r--)
471                 {p--; M_DST (savfltregs[r], REG_SP, 8 * p);}
472
473         /* save monitorenter argument */
474
475 #ifdef USE_THREADS
476         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
477                 if (method->flags & ACC_STATIC) {
478                         p = dseg_addaddress (class);
479                         M_ALD(REG_ITMP1, REG_PV, p);
480                         M_AST(REG_ITMP1, REG_SP, 8 * maxmemuse);
481                         } 
482                 else {
483                         M_AST (argintregs[0], REG_SP, 8 * maxmemuse);
484                         }
485                 }                       
486 #endif
487
488         /* copy argument registers to stack and call trace function with pointer
489            to arguments on stack. ToDo: save floating point registers !!!!!!!!!
490         */
491
492         if (runverbose) {
493                 M_LDA (REG_SP, REG_SP, -(14*8));
494                 M_AST(REG_RA, REG_SP, 1*8);
495
496                 M_LST(argintregs[0], REG_SP,  2*8);
497                 M_LST(argintregs[1], REG_SP,  3*8);
498                 M_LST(argintregs[2], REG_SP,  4*8);
499                 M_LST(argintregs[3], REG_SP,  5*8);
500                 M_LST(argintregs[4], REG_SP,  6*8);
501                 M_LST(argintregs[5], REG_SP,  7*8);
502
503                 M_DST(argfltregs[0], REG_SP,  8*8);
504                 M_DST(argfltregs[1], REG_SP,  9*8);
505                 M_DST(argfltregs[2], REG_SP, 10*8);
506                 M_DST(argfltregs[3], REG_SP, 11*8);
507                 M_DST(argfltregs[4], REG_SP, 12*8);
508                 M_DST(argfltregs[5], REG_SP, 13*8);
509
510                 p = dseg_addaddress (method);
511                 M_ALD(REG_ITMP1, REG_PV, p);
512                 M_AST(REG_ITMP1, REG_SP, 0);
513                 p = dseg_addaddress ((void*) (builtin_trace_args));
514                 M_ALD(REG_PV, REG_PV, p);
515                 M_JSR(REG_RA, REG_PV);
516                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
517                 M_ALD(REG_RA, REG_SP, 1*8);
518
519                 M_LLD(argintregs[0], REG_SP,  2*8);
520                 M_LLD(argintregs[1], REG_SP,  3*8);
521                 M_LLD(argintregs[2], REG_SP,  4*8);
522                 M_LLD(argintregs[3], REG_SP,  5*8);
523                 M_LLD(argintregs[4], REG_SP,  6*8);
524                 M_LLD(argintregs[5], REG_SP,  7*8);
525
526                 M_DLD(argfltregs[0], REG_SP,  8*8);
527                 M_DLD(argfltregs[1], REG_SP,  9*8);
528                 M_DLD(argfltregs[2], REG_SP, 10*8);
529                 M_DLD(argfltregs[3], REG_SP, 11*8);
530                 M_DLD(argfltregs[4], REG_SP, 12*8);
531                 M_DLD(argfltregs[5], REG_SP, 13*8);
532
533                 M_LDA (REG_SP, REG_SP, 14*8);
534                 }
535
536         /* take arguments out of register or stack frame */
537
538         for (p = 0, l = 0; p < mparamcount; p++) {
539                 t = mparamtypes[p];
540                 var = &(locals[l][t]);
541                 l++;
542                 if (IS_2_WORD_TYPE(t))    /* increment local counter for 2 word types */
543                         l++;
544                 if (var->type < 0)
545                         continue;
546                 r = var->regoff; 
547                 if (IS_INT_LNG_TYPE(t)) {                    /* integer args          */
548                         if (p < INT_ARG_CNT) {                   /* register arguments    */
549                                 if (!(var->flags & INMEMORY))        /* reg arg -> register   */
550                                         {M_INTMOVE (argintregs[p], r);}
551                                 else                                 /* reg arg -> spilled    */
552                                         M_LST (argintregs[p], REG_SP, 8 * r);
553                                 }
554                         else {                                   /* stack arguments       */
555                                 pa = p - INT_ARG_CNT;
556                                 if (!(var->flags & INMEMORY))        /* stack arg -> register */ 
557                                         M_LLD (r, REG_SP, 8 * (parentargs_base + pa));
558                                 else {                               /* stack arg -> spilled  */
559                                         M_LLD (REG_ITMP1, REG_SP, 8 * (parentargs_base + pa));
560                                         M_LST (REG_ITMP1, REG_SP, 8 * r);
561                                         }
562                                 }
563                         }
564                 else {                                       /* floating args         */   
565                         if (p < FLT_ARG_CNT) {                   /* register arguments    */
566                                 if (!(var->flags & INMEMORY))        /* reg arg -> register   */
567                                         {M_FLTMOVE (argfltregs[p], r);}
568                                 else                                             /* reg arg -> spilled    */
569                                         M_DST (argfltregs[p], REG_SP, 8 * r);
570                                 }
571                         else {                                   /* stack arguments       */
572                                 pa = p - FLT_ARG_CNT;
573                                 if (!(var->flags & INMEMORY))        /* stack-arg -> register */
574                                         M_DLD (r, REG_SP, 8 * (parentargs_base + pa) );
575                                 else {                               /* stack-arg -> spilled  */
576                                         M_DLD (REG_FTMP1, REG_SP, 8 * (parentargs_base + pa));
577                                         M_DST (REG_FTMP1, REG_SP, 8 * r);
578                                         }
579                                 }
580                         }
581                 }  /* end for */
582
583         /* call trace function */
584
585 #if 0
586         if (runverbose && !isleafmethod) {
587                 M_LDA (REG_SP, REG_SP, -8);
588                 p = dseg_addaddress (method);
589                 M_ALD(REG_ITMP1, REG_PV, p);
590                 M_AST(REG_ITMP1, REG_SP, 0);
591                 p = dseg_addaddress ((void*) (builtin_trace_args));
592                 M_ALD(REG_PV, REG_PV, p);
593                 M_JSR(REG_RA, REG_PV);
594                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
595                 M_LDA(REG_SP, REG_SP, 8);
596                 }
597 #endif
598
599         /* call monitorenter function */
600
601 #ifdef USE_THREADS
602         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
603                 p = dseg_addaddress ((void*) (builtin_monitorenter));
604                 M_ALD(REG_PV, REG_PV, p);
605                 M_ALD(argintregs[0], REG_SP, 8 * maxmemuse);
606                 M_JSR(REG_RA, REG_PV);
607                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
608                 }                       
609 #endif
610         }
611
612         /* end of header generation */
613
614         /* walk through all basic blocks */
615         for (/* bbs = block_count, */ bptr = block; /* --bbs >= 0 */ bptr != NULL; bptr = bptr->next) {
616
617                 bptr -> mpc = (int)((u1*) mcodeptr - mcodebase);
618
619                 if (bptr->flags >= BBREACHED) {
620
621                 /* branch resolving */
622
623                 {
624                 branchref *brefs;
625                 for (brefs = bptr->branchrefs; brefs != NULL; brefs = brefs->next) {
626                         gen_resolvebranch((u1*) mcodebase + brefs->branchpos, 
627                                           brefs->branchpos, bptr->mpc);
628                         }
629                 }
630
631                 /* copy interface registers to their destination */
632
633                 src = bptr->instack;
634                 len = bptr->indepth;
635                 MCODECHECK(64+len);
636                 while (src != NULL) {
637                         len--;
638                         if ((len == 0) && (bptr->type != BBTYPE_STD)) {
639                                 d = reg_of_var(src, REG_ITMP1);
640                                 M_INTMOVE(REG_ITMP1, d);
641                                 store_reg_to_var_int(src, d);
642                                 }
643                         else {
644                                 d = reg_of_var(src, REG_IFTMP);
645                                 if ((src->varkind != STACKVAR)) {
646                                         s2 = src->type;
647                                         if (IS_FLT_DBL_TYPE(s2)) {
648                                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
649                                                         s1 = interfaces[len][s2].regoff;
650                                                         M_FLTMOVE(s1,d);
651                                                         }
652                                                 else {
653                                                         M_DLD(d, REG_SP, 8 * interfaces[len][s2].regoff);
654                                                         }
655                                                 store_reg_to_var_flt(src, d);
656                                                 }
657                                         else {
658                                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
659                                                         s1 = interfaces[len][s2].regoff;
660                                                         M_INTMOVE(s1,d);
661                                                         }
662                                                 else {
663                                                         M_LLD(d, REG_SP, 8 * interfaces[len][s2].regoff);
664                                                         }
665                                                 store_reg_to_var_int(src, d);
666                                                 }
667                                         }
668                                 }
669                         src = src->prev;
670                         }
671
672                 /* walk through all instructions */
673                 
674                 src = bptr->instack;
675                 len = bptr->icount;
676                 for (iptr = bptr->iinstr;
677                     len > 0;
678                     src = iptr->dst, len--, iptr++) {
679
680         MCODECHECK(64);           /* an instruction usually needs < 64 words      */
681         switch (iptr->opc) {
682
683                 case ICMD_NOP:        /* ...  ==> ...                                 */
684                         break;
685
686                 case ICMD_NULLCHECKPOP: /* ..., objectref  ==> ...                    */
687
688                         var_to_reg_int(s1, src, REG_ITMP1);
689                         M_BEQZ(s1, 0);
690                         codegen_addxnullrefs(mcodeptr);
691                         break;
692
693                 /* constant operations ************************************************/
694
695 #define ICONST(r,c) if(((c)>=-32768)&&((c)<= 32767)){M_LDA(r,REG_ZERO,c);} \
696                     else{a=dseg_adds4(c);M_ILD(r,REG_PV,a);}
697
698 #define LCONST(r,c) if(((c)>=-32768)&&((c)<= 32767)){M_LDA(r,REG_ZERO,c);} \
699                     else{a=dseg_adds8(c);M_LLD(r,REG_PV,a);}
700
701                 case ICMD_ICONST:     /* ...  ==> ..., constant                       */
702                                       /* op1 = 0, val.i = constant                    */
703
704                         d = reg_of_var(iptr->dst, REG_ITMP1);
705                         ICONST(d, iptr->val.i);
706                         store_reg_to_var_int(iptr->dst, d);
707                         break;
708
709                 case ICMD_LCONST:     /* ...  ==> ..., constant                       */
710                                       /* op1 = 0, val.l = constant                    */
711
712                         d = reg_of_var(iptr->dst, REG_ITMP1);
713                         LCONST(d, iptr->val.l);
714                         store_reg_to_var_int(iptr->dst, d);
715                         break;
716
717                 case ICMD_FCONST:     /* ...  ==> ..., constant                       */
718                                       /* op1 = 0, val.f = constant                    */
719
720                         d = reg_of_var (iptr->dst, REG_FTMP1);
721                         a = dseg_addfloat (iptr->val.f);
722                         M_FLD(d, REG_PV, a);
723                         store_reg_to_var_flt (iptr->dst, d);
724                         break;
725                         
726                 case ICMD_DCONST:     /* ...  ==> ..., constant                       */
727                                       /* op1 = 0, val.d = constant                    */
728
729                         d = reg_of_var (iptr->dst, REG_FTMP1);
730                         a = dseg_adddouble (iptr->val.d);
731                         M_DLD(d, REG_PV, a);
732                         store_reg_to_var_flt (iptr->dst, d);
733                         break;
734
735                 case ICMD_ACONST:     /* ...  ==> ..., constant                       */
736                                       /* op1 = 0, val.a = constant                    */
737
738                         d = reg_of_var(iptr->dst, REG_ITMP1);
739                         if (iptr->val.a) {
740                                 a = dseg_addaddress (iptr->val.a);
741                                 M_ALD(d, REG_PV, a);
742                                 }
743                         else {
744                                 M_INTMOVE(REG_ZERO, d);
745                                 }
746                         store_reg_to_var_int(iptr->dst, d);
747                         break;
748
749
750                 /* load/store operations **********************************************/
751
752                 case ICMD_ILOAD:      /* ...  ==> ..., content of local variable      */
753                 case ICMD_LLOAD:      /* op1 = local variable                         */
754                 case ICMD_ALOAD:
755
756                         d = reg_of_var(iptr->dst, REG_ITMP1);
757                         if ((iptr->dst->varkind == LOCALVAR) &&
758                             (iptr->dst->varnum == iptr->op1))
759                                 break;
760                         var = &(locals[iptr->op1][iptr->opc - ICMD_ILOAD]);
761                         if (var->flags & INMEMORY)
762                                 M_LLD(d, REG_SP, 8 * var->regoff);
763                         else
764                                 {M_INTMOVE(var->regoff,d);}
765                         store_reg_to_var_int(iptr->dst, d);
766                         break;
767
768                 case ICMD_FLOAD:      /* ...  ==> ..., content of local variable      */
769                 case ICMD_DLOAD:      /* op1 = local variable                         */
770
771                         d = reg_of_var(iptr->dst, REG_FTMP1);
772                         if ((iptr->dst->varkind == LOCALVAR) &&
773                             (iptr->dst->varnum == iptr->op1))
774                                 break;
775                         var = &(locals[iptr->op1][iptr->opc - ICMD_ILOAD]);
776                         if (var->flags & INMEMORY)
777                                 M_DLD(d, REG_SP, 8 * var->regoff);
778                         else
779                                 {M_FLTMOVE(var->regoff,d);}
780                         store_reg_to_var_flt(iptr->dst, d);
781                         break;
782
783
784                 case ICMD_ISTORE:     /* ..., value  ==> ...                          */
785                 case ICMD_LSTORE:     /* op1 = local variable                         */
786                 case ICMD_ASTORE:
787
788                         if ((src->varkind == LOCALVAR) &&
789                             (src->varnum == iptr->op1))
790                                 break;
791                         var = &(locals[iptr->op1][iptr->opc - ICMD_ISTORE]);
792                         if (var->flags & INMEMORY) {
793                                 var_to_reg_int(s1, src, REG_ITMP1);
794                                 M_LST(s1, REG_SP, 8 * var->regoff);
795                                 }
796                         else {
797                                 var_to_reg_int(s1, src, var->regoff);
798                                 M_INTMOVE(s1, var->regoff);
799                                 }
800                         break;
801
802                 case ICMD_FSTORE:     /* ..., value  ==> ...                          */
803                 case ICMD_DSTORE:     /* op1 = local variable                         */
804
805                         if ((src->varkind == LOCALVAR) &&
806                             (src->varnum == iptr->op1))
807                                 break;
808                         var = &(locals[iptr->op1][iptr->opc - ICMD_ISTORE]);
809                         if (var->flags & INMEMORY) {
810                                 var_to_reg_flt(s1, src, REG_FTMP1);
811                                 M_DST(s1, REG_SP, 8 * var->regoff);
812                                 }
813                         else {
814                                 var_to_reg_flt(s1, src, var->regoff);
815                                 M_FLTMOVE(s1, var->regoff);
816                                 }
817                         break;
818
819
820                 /* pop/dup/swap operations ********************************************/
821
822                 /* attention: double and longs are only one entry in CACAO ICMDs      */
823
824                 case ICMD_POP:        /* ..., value  ==> ...                          */
825                 case ICMD_POP2:       /* ..., value, value  ==> ...                   */
826                         break;
827
828 #define M_COPY(from,to) \
829                         d = reg_of_var(to, REG_IFTMP); \
830                         if ((from->regoff != to->regoff) || \
831                             ((from->flags ^ to->flags) & INMEMORY)) { \
832                                 if (IS_FLT_DBL_TYPE(from->type)) { \
833                                         var_to_reg_flt(s1, from, d); \
834                                         M_FLTMOVE(s1,d); \
835                                         store_reg_to_var_flt(to, d); \
836                                         }\
837                                 else { \
838                                         var_to_reg_int(s1, from, d); \
839                                         M_INTMOVE(s1,d); \
840                                         store_reg_to_var_int(to, d); \
841                                         }\
842                                 }
843
844                 case ICMD_DUP:        /* ..., a ==> ..., a, a                         */
845                         M_COPY(src, iptr->dst);
846                         break;
847
848                 case ICMD_DUP_X1:     /* ..., a, b ==> ..., b, a, b                   */
849
850                         M_COPY(src,       iptr->dst->prev->prev);
851
852                 case ICMD_DUP2:       /* ..., a, b ==> ..., a, b, a, b                */
853
854                         M_COPY(src,       iptr->dst);
855                         M_COPY(src->prev, iptr->dst->prev);
856                         break;
857
858                 case ICMD_DUP2_X1:    /* ..., a, b, c ==> ..., b, c, a, b, c          */
859
860                         M_COPY(src->prev,       iptr->dst->prev->prev->prev);
861
862                 case ICMD_DUP_X2:     /* ..., a, b, c ==> ..., c, a, b, c             */
863
864                         M_COPY(src,             iptr->dst);
865                         M_COPY(src->prev,       iptr->dst->prev);
866                         M_COPY(src->prev->prev, iptr->dst->prev->prev);
867                         M_COPY(src, iptr->dst->prev->prev->prev);
868                         break;
869
870                 case ICMD_DUP2_X2:    /* ..., a, b, c, d ==> ..., c, d, a, b, c, d    */
871
872                         M_COPY(src,                   iptr->dst);
873                         M_COPY(src->prev,             iptr->dst->prev);
874                         M_COPY(src->prev->prev,       iptr->dst->prev->prev);
875                         M_COPY(src->prev->prev->prev, iptr->dst->prev->prev->prev);
876                         M_COPY(src,       iptr->dst->prev->prev->prev->prev);
877                         M_COPY(src->prev, iptr->dst->prev->prev->prev->prev->prev);
878                         break;
879
880                 case ICMD_SWAP:       /* ..., a, b ==> ..., b, a                      */
881
882                         M_COPY(src, iptr->dst->prev);
883                         M_COPY(src->prev, iptr->dst);
884                         break;
885
886
887                 /* integer operations *************************************************/
888
889                 case ICMD_INEG:       /* ..., value  ==> ..., - value                 */
890
891                         var_to_reg_int(s1, src, REG_ITMP1); 
892                         d = reg_of_var(iptr->dst, REG_ITMP3);
893                         M_ISUB(REG_ZERO, s1, d);
894                         store_reg_to_var_int(iptr->dst, d);
895                         break;
896
897                 case ICMD_LNEG:       /* ..., value  ==> ..., - value                 */
898
899                         var_to_reg_int(s1, src, REG_ITMP1);
900                         d = reg_of_var(iptr->dst, REG_ITMP3);
901                         M_LSUB(REG_ZERO, s1, d);
902                         store_reg_to_var_int(iptr->dst, d);
903                         break;
904
905                 case ICMD_I2L:        /* ..., value  ==> ..., value                   */
906
907                         var_to_reg_int(s1, src, REG_ITMP1);
908                         d = reg_of_var(iptr->dst, REG_ITMP3);
909                         M_INTMOVE(s1, d);
910                         store_reg_to_var_int(iptr->dst, d);
911                         break;
912
913                 case ICMD_L2I:        /* ..., value  ==> ..., value                   */
914
915                         var_to_reg_int(s1, src, REG_ITMP1);
916                         d = reg_of_var(iptr->dst, REG_ITMP3);
917                         M_IADD(s1, REG_ZERO, d );
918                         store_reg_to_var_int(iptr->dst, d);
919                         break;
920
921                 case ICMD_INT2BYTE:   /* ..., value  ==> ..., value                   */
922
923                         var_to_reg_int(s1, src, REG_ITMP1);
924                         d = reg_of_var(iptr->dst, REG_ITMP3);
925                         if (has_ext_instr_set) {
926                                 M_BSEXT(s1, d);
927                                 }
928                         else {
929                                 M_SLL_IMM(s1, 56, d);
930                                 M_SRA_IMM( d, 56, d);
931                                 }
932                         store_reg_to_var_int(iptr->dst, d);
933                         break;
934
935                 case ICMD_INT2CHAR:   /* ..., value  ==> ..., value                   */
936
937                         var_to_reg_int(s1, src, REG_ITMP1);
938                         d = reg_of_var(iptr->dst, REG_ITMP3);
939             M_CZEXT(s1, d);
940                         store_reg_to_var_int(iptr->dst, d);
941                         break;
942
943                 case ICMD_INT2SHORT:  /* ..., value  ==> ..., value                   */
944
945                         var_to_reg_int(s1, src, REG_ITMP1);
946                         d = reg_of_var(iptr->dst, REG_ITMP3);
947                         if (has_ext_instr_set) {
948                                 M_SSEXT(s1, d);
949                                 }
950                         else {
951                                 M_SLL_IMM(s1, 48, d);
952                                 M_SRA_IMM( d, 48, d);
953                                 }
954                         store_reg_to_var_int(iptr->dst, d);
955                         break;
956
957
958                 case ICMD_IADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
959
960                         var_to_reg_int(s1, src->prev, REG_ITMP1);
961                         var_to_reg_int(s2, src, REG_ITMP2);
962                         d = reg_of_var(iptr->dst, REG_ITMP3);
963                         M_IADD(s1, s2, d);
964                         store_reg_to_var_int(iptr->dst, d);
965                         break;
966
967                 case ICMD_IADDCONST:  /* ..., value  ==> ..., value + constant        */
968                                       /* val.i = constant                             */
969
970                         var_to_reg_int(s1, src, REG_ITMP1);
971                         d = reg_of_var(iptr->dst, REG_ITMP3);
972                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
973                                 M_IADD_IMM(s1, iptr->val.i, d);
974                                 }
975                         else {
976                                 ICONST(REG_ITMP2, iptr->val.i);
977                                 M_IADD(s1, REG_ITMP2, d);
978                                 }
979                         store_reg_to_var_int(iptr->dst, d);
980                         break;
981
982                 case ICMD_LADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
983
984                         var_to_reg_int(s1, src->prev, REG_ITMP1);
985                         var_to_reg_int(s2, src, REG_ITMP2);
986                         d = reg_of_var(iptr->dst, REG_ITMP3);
987                         M_LADD(s1, s2, d);
988                         store_reg_to_var_int(iptr->dst, d);
989                         break;
990
991                 case ICMD_LADDCONST:  /* ..., value  ==> ..., value + constant        */
992                                       /* val.l = constant                             */
993
994                         var_to_reg_int(s1, src, REG_ITMP1);
995                         d = reg_of_var(iptr->dst, REG_ITMP3);
996                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
997                                 M_LADD_IMM(s1, iptr->val.l, d);
998                                 }
999                         else {
1000                                 LCONST(REG_ITMP2, iptr->val.l);
1001                                 M_LADD(s1, REG_ITMP2, d);
1002                                 }
1003                         store_reg_to_var_int(iptr->dst, d);
1004                         break;
1005
1006                 case ICMD_ISUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
1007
1008                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1009                         var_to_reg_int(s2, src, REG_ITMP2);
1010                         d = reg_of_var(iptr->dst, REG_ITMP3);
1011                         M_ISUB(s1, s2, d);
1012                         store_reg_to_var_int(iptr->dst, d);
1013                         break;
1014
1015                 case ICMD_ISUBCONST:  /* ..., value  ==> ..., value + constant        */
1016                                       /* val.i = constant                             */
1017
1018                         var_to_reg_int(s1, src, REG_ITMP1);
1019                         d = reg_of_var(iptr->dst, REG_ITMP3);
1020                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
1021                                 M_ISUB_IMM(s1, iptr->val.i, d);
1022                                 }
1023                         else {
1024                                 ICONST(REG_ITMP2, iptr->val.i);
1025                                 M_ISUB(s1, REG_ITMP2, d);
1026                                 }
1027                         store_reg_to_var_int(iptr->dst, d);
1028                         break;
1029
1030                 case ICMD_LSUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
1031
1032                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1033                         var_to_reg_int(s2, src, REG_ITMP2);
1034                         d = reg_of_var(iptr->dst, REG_ITMP3);
1035                         M_LSUB(s1, s2, d);
1036                         store_reg_to_var_int(iptr->dst, d);
1037                         break;
1038
1039                 case ICMD_LSUBCONST:  /* ..., value  ==> ..., value - constant        */
1040                                       /* val.l = constant                             */
1041
1042                         var_to_reg_int(s1, src, REG_ITMP1);
1043                         d = reg_of_var(iptr->dst, REG_ITMP3);
1044                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
1045                                 M_LSUB_IMM(s1, iptr->val.l, d);
1046                                 }
1047                         else {
1048                                 LCONST(REG_ITMP2, iptr->val.l);
1049                                 M_LSUB(s1, REG_ITMP2, d);
1050                                 }
1051                         store_reg_to_var_int(iptr->dst, d);
1052                         break;
1053
1054                 case ICMD_IMUL:       /* ..., val1, val2  ==> ..., val1 * val2        */
1055
1056                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1057                         var_to_reg_int(s2, src, REG_ITMP2);
1058                         d = reg_of_var(iptr->dst, REG_ITMP3);
1059                         M_IMUL(s1, s2, d);
1060                         store_reg_to_var_int(iptr->dst, d);
1061                         break;
1062
1063                 case ICMD_IMULCONST:  /* ..., value  ==> ..., value * constant        */
1064                                       /* val.i = constant                             */
1065
1066                         var_to_reg_int(s1, src, REG_ITMP1);
1067                         d = reg_of_var(iptr->dst, REG_ITMP3);
1068                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
1069                                 M_IMUL_IMM(s1, iptr->val.i, d);
1070                                 }
1071                         else {
1072                                 ICONST(REG_ITMP2, iptr->val.i);
1073                                 M_IMUL(s1, REG_ITMP2, d);
1074                                 }
1075                         store_reg_to_var_int(iptr->dst, d);
1076                         break;
1077
1078                 case ICMD_LMUL:       /* ..., val1, val2  ==> ..., val1 * val2        */
1079
1080                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1081                         var_to_reg_int(s2, src, REG_ITMP2);
1082                         d = reg_of_var(iptr->dst, REG_ITMP3);
1083                         M_LMUL (s1, s2, d);
1084                         store_reg_to_var_int(iptr->dst, d);
1085                         break;
1086
1087                 case ICMD_LMULCONST:  /* ..., value  ==> ..., value * constant        */
1088                                       /* val.l = constant                             */
1089
1090                         var_to_reg_int(s1, src, REG_ITMP1);
1091                         d = reg_of_var(iptr->dst, REG_ITMP3);
1092                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
1093                                 M_LMUL_IMM(s1, iptr->val.l, d);
1094                                 }
1095                         else {
1096                                 LCONST(REG_ITMP2, iptr->val.l);
1097                                 M_LMUL(s1, REG_ITMP2, d);
1098                                 }
1099                         store_reg_to_var_int(iptr->dst, d);
1100                         break;
1101
1102                 case ICMD_IDIVPOW2:   /* ..., value  ==> ..., value << constant       */
1103                 case ICMD_LDIVPOW2:   /* val.i = constant                             */
1104                                       
1105                         var_to_reg_int(s1, src, REG_ITMP1);
1106                         d = reg_of_var(iptr->dst, REG_ITMP3);
1107                         if (iptr->val.i <= 15) {
1108                                 M_LDA(REG_ITMP2, s1, (1 << iptr->val.i) -1);
1109                                 M_CMOVGE(s1, s1, REG_ITMP2);
1110                                 }
1111                         else {
1112                                 M_SRA_IMM(s1, 63, REG_ITMP2);
1113                                 M_SRL_IMM(REG_ITMP2, 64 - iptr->val.i, REG_ITMP2);
1114                                 M_LADD(s1, REG_ITMP2, REG_ITMP2);
1115                                 }
1116                         M_SRA_IMM(REG_ITMP2, iptr->val.i, d);
1117                         store_reg_to_var_int(iptr->dst, d);
1118                         break;
1119
1120                 case ICMD_ISHL:       /* ..., val1, val2  ==> ..., val1 << val2       */
1121
1122                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1123                         var_to_reg_int(s2, src, REG_ITMP2);
1124                         d = reg_of_var(iptr->dst, REG_ITMP3);
1125                         M_AND_IMM(s2, 0x1f, REG_ITMP3);
1126                         M_SLL(s1, REG_ITMP3, d);
1127                         M_IADD(d, REG_ZERO, d);
1128                         store_reg_to_var_int(iptr->dst, d);
1129                         break;
1130
1131                 case ICMD_ISHLCONST:  /* ..., value  ==> ..., value << constant       */
1132                                       /* val.i = constant                             */
1133
1134                         var_to_reg_int(s1, src, REG_ITMP1);
1135                         d = reg_of_var(iptr->dst, REG_ITMP3);
1136                         M_SLL_IMM(s1, iptr->val.i & 0x1f, d);
1137                         M_IADD(d, REG_ZERO, d);
1138                         store_reg_to_var_int(iptr->dst, d);
1139                         break;
1140
1141                 case ICMD_ISHR:       /* ..., val1, val2  ==> ..., val1 >> val2       */
1142
1143                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1144                         var_to_reg_int(s2, src, REG_ITMP2);
1145                         d = reg_of_var(iptr->dst, REG_ITMP3);
1146                         M_AND_IMM(s2, 0x1f, REG_ITMP3);
1147                         M_SRA(s1, REG_ITMP3, d);
1148                         store_reg_to_var_int(iptr->dst, d);
1149                         break;
1150
1151                 case ICMD_ISHRCONST:  /* ..., value  ==> ..., value >> constant       */
1152                                       /* val.i = constant                             */
1153
1154                         var_to_reg_int(s1, src, REG_ITMP1);
1155                         d = reg_of_var(iptr->dst, REG_ITMP3);
1156                         M_SRA_IMM(s1, iptr->val.i & 0x1f, d);
1157                         store_reg_to_var_int(iptr->dst, d);
1158                         break;
1159
1160                 case ICMD_IUSHR:      /* ..., val1, val2  ==> ..., val1 >>> val2      */
1161
1162                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1163                         var_to_reg_int(s2, src, REG_ITMP2);
1164                         d = reg_of_var(iptr->dst, REG_ITMP3);
1165                         M_AND_IMM(s2, 0x1f, REG_ITMP2);
1166             M_IZEXT(s1, d);
1167                         M_SRL(d, REG_ITMP2, d);
1168                         M_IADD(d, REG_ZERO, d);
1169                         store_reg_to_var_int(iptr->dst, d);
1170                         break;
1171
1172                 case ICMD_IUSHRCONST: /* ..., value  ==> ..., value >>> constant      */
1173                                       /* val.i = constant                             */
1174
1175                         var_to_reg_int(s1, src, REG_ITMP1);
1176                         d = reg_of_var(iptr->dst, REG_ITMP3);
1177             M_IZEXT(s1, d);
1178                         M_SRL_IMM(d, iptr->val.i & 0x1f, d);
1179                         M_IADD(d, REG_ZERO, d);
1180                         store_reg_to_var_int(iptr->dst, d);
1181                         break;
1182
1183                 case ICMD_LSHL:       /* ..., val1, val2  ==> ..., val1 << val2       */
1184
1185                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1186                         var_to_reg_int(s2, src, REG_ITMP2);
1187                         d = reg_of_var(iptr->dst, REG_ITMP3);
1188                         M_SLL(s1, s2, d);
1189                         store_reg_to_var_int(iptr->dst, d);
1190                         break;
1191
1192                 case ICMD_LSHLCONST:  /* ..., value  ==> ..., value << constant       */
1193                                       /* val.i = constant                             */
1194
1195                         var_to_reg_int(s1, src, REG_ITMP1);
1196                         d = reg_of_var(iptr->dst, REG_ITMP3);
1197                         M_SLL_IMM(s1, iptr->val.i & 0x3f, d);
1198                         store_reg_to_var_int(iptr->dst, d);
1199                         break;
1200
1201                 case ICMD_LSHR:       /* ..., val1, val2  ==> ..., val1 >> val2       */
1202
1203                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1204                         var_to_reg_int(s2, src, REG_ITMP2);
1205                         d = reg_of_var(iptr->dst, REG_ITMP3);
1206                         M_SRA(s1, s2, d);
1207                         store_reg_to_var_int(iptr->dst, d);
1208                         break;
1209
1210                 case ICMD_LSHRCONST:  /* ..., value  ==> ..., value >> constant       */
1211                                       /* val.i = constant                             */
1212
1213                         var_to_reg_int(s1, src, REG_ITMP1);
1214                         d = reg_of_var(iptr->dst, REG_ITMP3);
1215                         M_SRA_IMM(s1, iptr->val.i & 0x3f, d);
1216                         store_reg_to_var_int(iptr->dst, d);
1217                         break;
1218
1219                 case ICMD_LUSHR:      /* ..., val1, val2  ==> ..., val1 >>> val2      */
1220
1221                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1222                         var_to_reg_int(s2, src, REG_ITMP2);
1223                         d = reg_of_var(iptr->dst, REG_ITMP3);
1224                         M_SRL(s1, s2, d);
1225                         store_reg_to_var_int(iptr->dst, d);
1226                         break;
1227
1228                 case ICMD_LUSHRCONST: /* ..., value  ==> ..., value >>> constant      */
1229                                       /* val.i = constant                             */
1230
1231                         var_to_reg_int(s1, src, REG_ITMP1);
1232                         d = reg_of_var(iptr->dst, REG_ITMP3);
1233                         M_SRL_IMM(s1, iptr->val.i & 0x3f, d);
1234                         store_reg_to_var_int(iptr->dst, d);
1235                         break;
1236
1237                 case ICMD_IAND:       /* ..., val1, val2  ==> ..., val1 & val2        */
1238                 case ICMD_LAND:
1239
1240                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1241                         var_to_reg_int(s2, src, REG_ITMP2);
1242                         d = reg_of_var(iptr->dst, REG_ITMP3);
1243                         M_AND(s1, s2, d);
1244                         store_reg_to_var_int(iptr->dst, d);
1245                         break;
1246
1247                 case ICMD_IANDCONST:  /* ..., value  ==> ..., value & constant        */
1248                                       /* val.i = constant                             */
1249
1250                         var_to_reg_int(s1, src, REG_ITMP1);
1251                         d = reg_of_var(iptr->dst, REG_ITMP3);
1252                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
1253                                 M_AND_IMM(s1, iptr->val.i, d);
1254                                 }
1255                         else if (iptr->val.i == 0xffff) {
1256                                 M_CZEXT(s1, d);
1257                                 }
1258                         else if (iptr->val.i == 0xffffff) {
1259                                 M_ZAPNOT_IMM(s1, 0x07, d);
1260                                 }
1261                         else {
1262                                 ICONST(REG_ITMP2, iptr->val.i);
1263                                 M_AND(s1, REG_ITMP2, d);
1264                                 }
1265                         store_reg_to_var_int(iptr->dst, d);
1266                         break;
1267
1268                 case ICMD_IREMPOW2:   /* ..., value  ==> ..., value % constant        */
1269                                       /* val.i = constant                             */
1270
1271                         var_to_reg_int(s1, src, REG_ITMP1);
1272                         d = reg_of_var(iptr->dst, REG_ITMP3);
1273                         if (s1 == d) {
1274                                 M_MOV(s1, REG_ITMP1);
1275                                 s1 = REG_ITMP1;
1276                                 }
1277                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
1278                                 M_AND_IMM(s1, iptr->val.i, d);
1279                                 M_BGEZ(s1, 3);
1280                                 M_ISUB(REG_ZERO, s1, d);
1281                                 M_AND_IMM(d, iptr->val.i, d);
1282                                 }
1283                         else if (iptr->val.i == 0xffff) {
1284                                 M_CZEXT(s1, d);
1285                                 M_BGEZ(s1, 3);
1286                                 M_ISUB(REG_ZERO, s1, d);
1287                                 M_CZEXT(d, d);
1288                                 }
1289                         else if (iptr->val.i == 0xffffff) {
1290                                 M_ZAPNOT_IMM(s1, 0x07, d);
1291                                 M_BGEZ(s1, 3);
1292                                 M_ISUB(REG_ZERO, s1, d);
1293                                 M_ZAPNOT_IMM(d, 0x07, d);
1294                                 }
1295                         else {
1296                                 ICONST(REG_ITMP2, iptr->val.i);
1297                                 M_AND(s1, REG_ITMP2, d);
1298                                 M_BGEZ(s1, 3);
1299                                 M_ISUB(REG_ZERO, s1, d);
1300                                 M_AND(d, REG_ITMP2, d);
1301                                 }
1302                         M_ISUB(REG_ZERO, d, d);
1303                         store_reg_to_var_int(iptr->dst, d);
1304                         break;
1305
1306                 case ICMD_IREM0X10001:  /* ..., value  ==> ..., value % 0x100001      */
1307                 
1308 /*          b = value & 0xffff;
1309                         a = value >> 16;
1310                         a = ((b - a) & 0xffff) + (b < a);
1311 */
1312                         var_to_reg_int(s1, src, REG_ITMP1);
1313                         d = reg_of_var(iptr->dst, REG_ITMP3);
1314                         if (s1 == d) {
1315                                 M_MOV(s1, REG_ITMP3);
1316                                 s1 = REG_ITMP3;
1317                                 }
1318                         M_BLTZ(s1, 7);
1319             M_CZEXT(s1, REG_ITMP2);
1320                         M_SRA_IMM(s1, 16, d);
1321                         M_CMPLT(REG_ITMP2, d, REG_ITMP1);
1322                         M_ISUB(REG_ITMP2, d, d);
1323             M_CZEXT(d, d);
1324                         M_IADD(d, REG_ITMP1, d);
1325                         M_BR(11 + (s1 == REG_ITMP1));
1326                         M_ISUB(REG_ZERO, s1, REG_ITMP1);
1327             M_CZEXT(REG_ITMP1, REG_ITMP2);
1328                         M_SRA_IMM(REG_ITMP1, 16, d);
1329                         M_CMPLT(REG_ITMP2, d, REG_ITMP1);
1330                         M_ISUB(REG_ITMP2, d, d);
1331             M_CZEXT(d, d);
1332                         M_IADD(d, REG_ITMP1, d);
1333                         M_ISUB(REG_ZERO, d, d);
1334                         if (s1 == REG_ITMP1) {
1335                                 var_to_reg_int(s1, src, REG_ITMP1);
1336                                 }
1337                         M_SLL_IMM(s1, 33, REG_ITMP2);
1338                         M_CMPEQ(REG_ITMP2, REG_ZERO, REG_ITMP2);
1339                         M_ISUB(d, REG_ITMP2, d);
1340                         store_reg_to_var_int(iptr->dst, d);
1341                         break;
1342
1343                 case ICMD_LANDCONST:  /* ..., value  ==> ..., value & constant        */
1344                                       /* val.l = constant                             */
1345
1346                         var_to_reg_int(s1, src, REG_ITMP1);
1347                         d = reg_of_var(iptr->dst, REG_ITMP3);
1348                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
1349                                 M_AND_IMM(s1, iptr->val.l, d);
1350                                 }
1351                         else if (iptr->val.l == 0xffffL) {
1352                                 M_CZEXT(s1, d);
1353                                 }
1354                         else if (iptr->val.l == 0xffffffL) {
1355                                 M_ZAPNOT_IMM(s1, 0x07, d);
1356                                 }
1357                         else if (iptr->val.l == 0xffffffffL) {
1358                                 M_IZEXT(s1, d);
1359                                 }
1360                         else if (iptr->val.l == 0xffffffffffL) {
1361                                 M_ZAPNOT_IMM(s1, 0x1f, d);
1362                                 }
1363                         else if (iptr->val.l == 0xffffffffffffL) {
1364                                 M_ZAPNOT_IMM(s1, 0x3f, d);
1365                                 }
1366                         else if (iptr->val.l == 0xffffffffffffffL) {
1367                                 M_ZAPNOT_IMM(s1, 0x7f, d);
1368                                 }
1369                         else {
1370                                 LCONST(REG_ITMP2, iptr->val.l);
1371                                 M_AND(s1, REG_ITMP2, d);
1372                                 }
1373                         store_reg_to_var_int(iptr->dst, d);
1374                         break;
1375
1376                 case ICMD_LREMPOW2:   /* ..., value  ==> ..., value % constant        */
1377                                       /* val.l = constant                             */
1378
1379                         var_to_reg_int(s1, src, REG_ITMP1);
1380                         d = reg_of_var(iptr->dst, REG_ITMP3);
1381                         if (s1 == d) {
1382                                 M_MOV(s1, REG_ITMP1);
1383                                 s1 = REG_ITMP1;
1384                                 }
1385                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
1386                                 M_AND_IMM(s1, iptr->val.l, d);
1387                                 M_BGEZ(s1, 3);
1388                                 M_LSUB(REG_ZERO, s1, d);
1389                                 M_AND_IMM(d, iptr->val.l, d);
1390                                 }
1391                         else if (iptr->val.l == 0xffffL) {
1392                                 M_CZEXT(s1, d);
1393                                 M_BGEZ(s1, 3);
1394                                 M_LSUB(REG_ZERO, s1, d);
1395                                 M_CZEXT(d, d);
1396                                 }
1397                         else if (iptr->val.l == 0xffffffL) {
1398                                 M_ZAPNOT_IMM(s1, 0x07, d);
1399                                 M_BGEZ(s1, 3);
1400                                 M_LSUB(REG_ZERO, s1, d);
1401                                 M_ZAPNOT_IMM(d, 0x07, d);
1402                                 }
1403                         else if (iptr->val.l == 0xffffffffL) {
1404                                 M_IZEXT(s1, d);
1405                                 M_BGEZ(s1, 3);
1406                                 M_LSUB(REG_ZERO, s1, d);
1407                                 M_IZEXT(d, d);
1408                                 }
1409                         else if (iptr->val.l == 0xffffffffffL) {
1410                                 M_ZAPNOT_IMM(s1, 0x1f, d);
1411                                 M_BGEZ(s1, 3);
1412                                 M_LSUB(REG_ZERO, s1, d);
1413                                 M_ZAPNOT_IMM(d, 0x1f, d);
1414                                 }
1415                         else if (iptr->val.l == 0xffffffffffffL) {
1416                                 M_ZAPNOT_IMM(s1, 0x3f, d);
1417                                 M_BGEZ(s1, 3);
1418                                 M_LSUB(REG_ZERO, s1, d);
1419                                 M_ZAPNOT_IMM(d, 0x3f, d);
1420                                 }
1421                         else if (iptr->val.l == 0xffffffffffffffL) {
1422                                 M_ZAPNOT_IMM(s1, 0x7f, d);
1423                                 M_BGEZ(s1, 3);
1424                                 M_LSUB(REG_ZERO, s1, d);
1425                                 M_ZAPNOT_IMM(d, 0x7f, d);
1426                                 }
1427                         else {
1428                                 LCONST(REG_ITMP2, iptr->val.l);
1429                                 M_AND(s1, REG_ITMP2, d);
1430                                 M_BGEZ(s1, 3);
1431                                 M_LSUB(REG_ZERO, s1, d);
1432                                 M_AND(d, REG_ITMP2, d);
1433                                 }
1434                         M_LSUB(REG_ZERO, d, d);
1435                         store_reg_to_var_int(iptr->dst, d);
1436                         break;
1437
1438                 case ICMD_LREM0X10001:/* ..., value  ==> ..., value % 0x10001         */
1439
1440                         var_to_reg_int(s1, src, REG_ITMP1);
1441                         d = reg_of_var(iptr->dst, REG_ITMP3);
1442                         if (s1 == d) {
1443                                 M_MOV(s1, REG_ITMP3);
1444                                 s1 = REG_ITMP3;
1445                                 }
1446                         M_CZEXT(s1, REG_ITMP2);
1447                         M_SRA_IMM(s1, 16, d);
1448                         M_CMPLT(REG_ITMP2, d, REG_ITMP1);
1449                         M_LSUB(REG_ITMP2, d, d);
1450             M_CZEXT(d, d);
1451                         M_LADD(d, REG_ITMP1, d);
1452                         M_LDA(REG_ITMP2, REG_ZERO, -1);
1453                         M_SRL_IMM(REG_ITMP2, 33, REG_ITMP2);
1454                         if (s1 == REG_ITMP1) {
1455                                 var_to_reg_int(s1, src, REG_ITMP1);
1456                                 }
1457                         M_CMPULT(s1, REG_ITMP2, REG_ITMP2);
1458                         M_BNEZ(REG_ITMP2, 11);
1459                         M_LDA(d, REG_ZERO, -257);
1460                         M_ZAPNOT_IMM(d, 0xcd, d);
1461                         M_LSUB(REG_ZERO, s1, REG_ITMP2);
1462                         M_CMOVGE(s1, s1, REG_ITMP2);
1463                         M_UMULH(REG_ITMP2, d, REG_ITMP2);
1464                         M_SRL_IMM(REG_ITMP2, 16, REG_ITMP2);
1465                         M_LSUB(REG_ZERO, REG_ITMP2, d);
1466                         M_CMOVGE(s1, REG_ITMP2, d);
1467                         M_SLL_IMM(d, 16, REG_ITMP2);
1468                         M_LADD(d, REG_ITMP2, d);
1469                         M_LSUB(s1, d, d);
1470                         store_reg_to_var_int(iptr->dst, d);
1471                         break;
1472
1473                 case ICMD_IOR:        /* ..., val1, val2  ==> ..., val1 | val2        */
1474                 case ICMD_LOR:
1475
1476                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1477                         var_to_reg_int(s2, src, REG_ITMP2);
1478                         d = reg_of_var(iptr->dst, REG_ITMP3);
1479                         M_OR( s1,s2, d);
1480                         store_reg_to_var_int(iptr->dst, d);
1481                         break;
1482
1483                 case ICMD_IORCONST:   /* ..., value  ==> ..., value | constant        */
1484                                       /* val.i = constant                             */
1485
1486                         var_to_reg_int(s1, src, REG_ITMP1);
1487                         d = reg_of_var(iptr->dst, REG_ITMP3);
1488                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
1489                                 M_OR_IMM(s1, iptr->val.i, d);
1490                                 }
1491                         else {
1492                                 ICONST(REG_ITMP2, iptr->val.i);
1493                                 M_OR(s1, REG_ITMP2, d);
1494                                 }
1495                         store_reg_to_var_int(iptr->dst, d);
1496                         break;
1497
1498                 case ICMD_LORCONST:   /* ..., value  ==> ..., value | constant        */
1499                                       /* val.l = constant                             */
1500
1501                         var_to_reg_int(s1, src, REG_ITMP1);
1502                         d = reg_of_var(iptr->dst, REG_ITMP3);
1503                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
1504                                 M_OR_IMM(s1, iptr->val.l, d);
1505                                 }
1506                         else {
1507                                 LCONST(REG_ITMP2, iptr->val.l);
1508                                 M_OR(s1, REG_ITMP2, d);
1509                                 }
1510                         store_reg_to_var_int(iptr->dst, d);
1511                         break;
1512
1513                 case ICMD_IXOR:       /* ..., val1, val2  ==> ..., val1 ^ val2        */
1514                 case ICMD_LXOR:
1515
1516                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1517                         var_to_reg_int(s2, src, REG_ITMP2);
1518                         d = reg_of_var(iptr->dst, REG_ITMP3);
1519                         M_XOR(s1, s2, d);
1520                         store_reg_to_var_int(iptr->dst, d);
1521                         break;
1522
1523                 case ICMD_IXORCONST:  /* ..., value  ==> ..., value ^ constant        */
1524                                       /* val.i = constant                             */
1525
1526                         var_to_reg_int(s1, src, REG_ITMP1);
1527                         d = reg_of_var(iptr->dst, REG_ITMP3);
1528                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
1529                                 M_XOR_IMM(s1, iptr->val.i, d);
1530                                 }
1531                         else {
1532                                 ICONST(REG_ITMP2, iptr->val.i);
1533                                 M_XOR(s1, REG_ITMP2, d);
1534                                 }
1535                         store_reg_to_var_int(iptr->dst, d);
1536                         break;
1537
1538                 case ICMD_LXORCONST:  /* ..., value  ==> ..., value ^ constant        */
1539                                       /* val.l = constant                             */
1540
1541                         var_to_reg_int(s1, src, REG_ITMP1);
1542                         d = reg_of_var(iptr->dst, REG_ITMP3);
1543                         if ((iptr->val.l >= 0) && (iptr->val.l <= 255)) {
1544                                 M_XOR_IMM(s1, iptr->val.l, d);
1545                                 }
1546                         else {
1547                                 LCONST(REG_ITMP2, iptr->val.l);
1548                                 M_XOR(s1, REG_ITMP2, d);
1549                                 }
1550                         store_reg_to_var_int(iptr->dst, d);
1551                         break;
1552
1553
1554                 case ICMD_LCMP:       /* ..., val1, val2  ==> ..., val1 cmp val2      */
1555
1556                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1557                         var_to_reg_int(s2, src, REG_ITMP2);
1558                         d = reg_of_var(iptr->dst, REG_ITMP3);
1559                         M_CMPLT(s1, s2, REG_ITMP3);
1560                         M_CMPLT(s2, s1, REG_ITMP1);
1561                         M_LSUB (REG_ITMP1, REG_ITMP3, d);
1562                         store_reg_to_var_int(iptr->dst, d);
1563                         break;
1564
1565
1566                 case ICMD_IINC:       /* ..., value  ==> ..., value + constant        */
1567                                       /* op1 = variable, val.i = constant             */
1568
1569                         var = &(locals[iptr->op1][TYPE_INT]);
1570                         if (var->flags & INMEMORY) {
1571                                 s1 = REG_ITMP1;
1572                                 M_LLD(s1, REG_SP, 8 * var->regoff);
1573                                 }
1574                         else
1575                                 s1 = var->regoff;
1576                         if ((iptr->val.i >= 0) && (iptr->val.i <= 255)) {
1577                                 M_IADD_IMM(s1, iptr->val.i, s1);
1578                                 }
1579                         else if ((iptr->val.i > -256) && (iptr->val.i < 0)) {
1580                                 M_ISUB_IMM(s1, (-iptr->val.i), s1);
1581                                 }
1582                         else {
1583                                 M_LDA (s1, s1, iptr->val.i);
1584                                 M_IADD(s1, REG_ZERO, s1);
1585                                 }
1586                         if (var->flags & INMEMORY)
1587                                 M_LST(s1, REG_SP, 8 * var->regoff);
1588                         break;
1589
1590
1591                 /* floating operations ************************************************/
1592
1593                 case ICMD_FNEG:       /* ..., value  ==> ..., - value                 */
1594
1595                         var_to_reg_flt(s1, src, REG_FTMP1);
1596                         d = reg_of_var(iptr->dst, REG_FTMP3);
1597                         M_FMOVN(s1, d);
1598                         store_reg_to_var_flt(iptr->dst, d);
1599                         break;
1600
1601                 case ICMD_DNEG:       /* ..., value  ==> ..., - value                 */
1602
1603                         var_to_reg_flt(s1, src, REG_FTMP1);
1604                         d = reg_of_var(iptr->dst, REG_FTMP3);
1605                         M_FMOVN(s1, d);
1606                         store_reg_to_var_flt(iptr->dst, d);
1607                         break;
1608
1609                 case ICMD_FADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
1610
1611                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1612                         var_to_reg_flt(s2, src, REG_FTMP2);
1613                         d = reg_of_var(iptr->dst, REG_FTMP3);
1614                         if (opt_noieee) {
1615                                 M_FADD(s1, s2, d);
1616                                 }
1617                         else {
1618                                 M_FADDS(s1, s2, d);
1619                                 M_TRAPB;
1620                                 }
1621                         store_reg_to_var_flt(iptr->dst, d);
1622                         break;
1623
1624                 case ICMD_DADD:       /* ..., val1, val2  ==> ..., val1 + val2        */
1625
1626                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1627                         var_to_reg_flt(s2, src, REG_FTMP2);
1628                         d = reg_of_var(iptr->dst, REG_FTMP3);
1629                         if (opt_noieee) {
1630                                 M_DADD(s1, s2, d);
1631                                 }
1632                         else {
1633                                 M_DADDS(s1, s2, d);
1634                                 M_TRAPB;
1635                                 }
1636                         store_reg_to_var_flt(iptr->dst, d);
1637                         break;
1638
1639                 case ICMD_FSUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
1640
1641                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1642                         var_to_reg_flt(s2, src, REG_FTMP2);
1643                         d = reg_of_var(iptr->dst, REG_FTMP3);
1644                         if (opt_noieee) {
1645                                 M_FSUB(s1, s2, d);
1646                                 }
1647                         else {
1648                                 M_FSUBS(s1, s2, d);
1649                                 M_TRAPB;
1650                                 }
1651                         store_reg_to_var_flt(iptr->dst, d);
1652                         break;
1653
1654                 case ICMD_DSUB:       /* ..., val1, val2  ==> ..., val1 - val2        */
1655
1656                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1657                         var_to_reg_flt(s2, src, REG_FTMP2);
1658                         d = reg_of_var(iptr->dst, REG_FTMP3);
1659                         if (opt_noieee) {
1660                                 M_DSUB(s1, s2, d);
1661                                 }
1662                         else {
1663                                 M_DSUBS(s1, s2, d);
1664                                 M_TRAPB;
1665                                 }
1666                         store_reg_to_var_flt(iptr->dst, d);
1667                         break;
1668
1669                 case ICMD_FMUL:       /* ..., val1, val2  ==> ..., val1 * val2        */
1670
1671                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1672                         var_to_reg_flt(s2, src, REG_FTMP2);
1673                         d = reg_of_var(iptr->dst, REG_FTMP3);
1674                         if (opt_noieee) {
1675                                 M_FMUL(s1, s2, d);
1676                                 }
1677                         else {
1678                                 M_FMULS(s1, s2, d);
1679                                 M_TRAPB;
1680                                 }
1681                         store_reg_to_var_flt(iptr->dst, d);
1682                         break;
1683
1684                 case ICMD_DMUL:       /* ..., val1, val2  ==> ..., val1 *** val2        */
1685
1686                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1687                         var_to_reg_flt(s2, src, REG_FTMP2);
1688                         d = reg_of_var(iptr->dst, REG_FTMP3);
1689                         if (opt_noieee) {
1690                                 M_DMUL(s1, s2, d);
1691                                 }
1692                         else {
1693                                 M_DMULS(s1, s2, d);
1694                                 M_TRAPB;
1695                                 }
1696                         store_reg_to_var_flt(iptr->dst, d);
1697                         break;
1698
1699                 case ICMD_FDIV:       /* ..., val1, val2  ==> ..., val1 / val2        */
1700
1701                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1702                         var_to_reg_flt(s2, src, REG_FTMP2);
1703                         d = reg_of_var(iptr->dst, REG_FTMP3);
1704                         if (opt_noieee) {
1705                                 M_FDIV(s1, s2, d);
1706                                 }
1707                         else {
1708                                 M_FDIVS(s1, s2, d);
1709                                 M_TRAPB;
1710                                 }
1711                         store_reg_to_var_flt(iptr->dst, d);
1712                         break;
1713
1714                 case ICMD_DDIV:       /* ..., val1, val2  ==> ..., val1 / val2        */
1715
1716                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1717                         var_to_reg_flt(s2, src, REG_FTMP2);
1718                         d = reg_of_var(iptr->dst, REG_FTMP3);
1719                         if (opt_noieee) {
1720                                 M_DDIV(s1, s2, d);
1721                                 }
1722                         else {
1723                                 M_DDIVS(s1, s2, d);
1724                                 M_TRAPB;
1725                                 }
1726                         store_reg_to_var_flt(iptr->dst, d);
1727                         break;
1728                 
1729                 case ICMD_FREM:       /* ..., val1, val2  ==> ..., val1 % val2        */
1730
1731                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1732                         var_to_reg_flt(s2, src, REG_FTMP2);
1733                         d = reg_of_var(iptr->dst, REG_FTMP3);
1734                         if (opt_noieee) {
1735                                 M_FDIV(s1,s2, REG_FTMP3);
1736                                 M_CVTDL_C(REG_FTMP3, REG_FTMP3); /* round to integer */
1737                                 M_CVTLF(REG_FTMP3, REG_FTMP3);
1738                                 M_FMUL(REG_FTMP3, s2, REG_FTMP3);
1739                                 M_FSUB(s1, REG_FTMP3, d);
1740                                 }
1741                         else {
1742                                 M_FDIVS(s1,s2, REG_FTMP3);
1743                                 M_TRAPB;
1744                                 M_CVTDL_CS(REG_FTMP3, REG_FTMP3); /* round to integer */
1745                                 M_TRAPB;
1746                                 M_CVTLF(REG_FTMP3, REG_FTMP3);
1747                                 M_FMULS(REG_FTMP3, s2, REG_FTMP3);
1748                                 M_TRAPB;
1749                                 M_FSUBS(s1, REG_FTMP3, d);
1750                                 M_TRAPB;
1751                                 }
1752                         store_reg_to_var_flt(iptr->dst, d);
1753                     break;
1754
1755                 case ICMD_DREM:       /* ..., val1, val2  ==> ..., val1 % val2        */
1756
1757                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1758                         var_to_reg_flt(s2, src, REG_FTMP2);
1759                         d = reg_of_var(iptr->dst, REG_FTMP3);
1760                         if (opt_noieee) {
1761                                 M_DDIV(s1,s2, REG_FTMP3);
1762                                 M_CVTDL_C(REG_FTMP3, REG_FTMP3); /* round to integer */
1763                                 M_CVTLD(REG_FTMP3, REG_FTMP3);
1764                                 M_DMUL(REG_FTMP3, s2, REG_FTMP3);
1765                                 M_DSUB(s1, REG_FTMP3, d);
1766                                 }
1767                         else {
1768                                 M_DDIVS(s1,s2, REG_FTMP3);
1769                                 M_TRAPB;
1770                                 M_CVTDL_CS(REG_FTMP3, REG_FTMP3); /* round to integer */
1771                                 M_TRAPB;
1772                                 M_CVTLD(REG_FTMP3, REG_FTMP3);
1773                                 M_DMULS(REG_FTMP3, s2, REG_FTMP3);
1774                                 M_TRAPB;
1775                                 M_DSUBS(s1, REG_FTMP3, d);
1776                                 M_TRAPB;
1777                                 }
1778                         store_reg_to_var_flt(iptr->dst, d);
1779                     break;
1780
1781                 case ICMD_I2F:       /* ..., value  ==> ..., (float) value            */
1782                 case ICMD_L2F:
1783                         var_to_reg_int(s1, src, REG_ITMP1);
1784                         d = reg_of_var(iptr->dst, REG_FTMP3);
1785                         a = dseg_adddouble(0.0);
1786                         M_LST (s1, REG_PV, a);
1787                         M_DLD (d, REG_PV, a);
1788                         M_CVTLF(d, d);
1789                         store_reg_to_var_flt(iptr->dst, d);
1790                         break;
1791
1792                 case ICMD_I2D:       /* ..., value  ==> ..., (double) value           */
1793                 case ICMD_L2D:
1794                         var_to_reg_int(s1, src, REG_ITMP1);
1795                         d = reg_of_var(iptr->dst, REG_FTMP3);
1796                         a = dseg_adddouble(0.0);
1797                         M_LST (s1, REG_PV, a);
1798                         M_DLD (d, REG_PV, a);
1799                         M_CVTLD(d, d);
1800                         store_reg_to_var_flt(iptr->dst, d);
1801                         break;
1802                         
1803                 case ICMD_F2I:       /* ..., value  ==> ..., (int) value              */
1804                 case ICMD_D2I:
1805                         var_to_reg_flt(s1, src, REG_FTMP1);
1806                         d = reg_of_var(iptr->dst, REG_ITMP3);
1807                         a = dseg_adddouble(0.0);
1808                         if (opt_noieee) {
1809                                 M_CVTDL_C(s1, REG_FTMP1);
1810                                 M_CVTLI(REG_FTMP1, REG_FTMP2);
1811                                 }
1812                         else {
1813                                 M_CVTDL_CS(s1, REG_FTMP1);
1814                                 M_TRAPB;
1815                                 M_CVTLIS(REG_FTMP1, REG_FTMP2);
1816                                 M_TRAPB;
1817                                 }
1818                         M_DST (REG_FTMP1, REG_PV, a);
1819                         M_ILD (d, REG_PV, a);
1820                         store_reg_to_var_int(iptr->dst, d);
1821                         break;
1822                 
1823                 case ICMD_F2L:       /* ..., value  ==> ..., (long) value             */
1824                 case ICMD_D2L:
1825                         var_to_reg_flt(s1, src, REG_FTMP1);
1826                         d = reg_of_var(iptr->dst, REG_ITMP3);
1827                         a = dseg_adddouble(0.0);
1828                         if (opt_noieee) {
1829                                 M_CVTDL_C(s1, REG_FTMP1);
1830                                 }
1831                         else {
1832                                 M_CVTDL_CS(s1, REG_FTMP1);
1833                                 M_TRAPB;
1834                                 }
1835                         M_DST (REG_FTMP1, REG_PV, a);
1836                         M_LLD (d, REG_PV, a);
1837                         store_reg_to_var_int(iptr->dst, d);
1838                         break;
1839
1840                 case ICMD_F2D:       /* ..., value  ==> ..., (double) value           */
1841
1842                         var_to_reg_flt(s1, src, REG_FTMP1);
1843                         d = reg_of_var(iptr->dst, REG_FTMP3);
1844                         M_FLTMOVE(s1, d);
1845                         store_reg_to_var_flt(iptr->dst, d);
1846                         break;
1847                                         
1848                 case ICMD_D2F:       /* ..., value  ==> ..., (double) value           */
1849
1850                         var_to_reg_flt(s1, src, REG_FTMP1);
1851                         d = reg_of_var(iptr->dst, REG_FTMP3);
1852                         if (opt_noieee) {
1853                                 M_CVTDF(s1, d);
1854                                 }
1855                         else {
1856                                 M_CVTDFS(s1, d);
1857                                 M_TRAPB;
1858                                 }
1859                         store_reg_to_var_flt(iptr->dst, d);
1860                         break;
1861                 
1862                 case ICMD_FCMPL:      /* ..., val1, val2  ==> ..., val1 fcmpl val2    */
1863                 case ICMD_DCMPL:
1864                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1865                         var_to_reg_flt(s2, src, REG_FTMP2);
1866                         d = reg_of_var(iptr->dst, REG_ITMP3);
1867                         if (opt_noieee) {
1868                                 M_LSUB_IMM(REG_ZERO, 1, d);
1869                                 M_FCMPEQ(s1, s2, REG_FTMP3);
1870                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instructions */
1871                                 M_CLR   (d);
1872                                 M_FCMPLT(s2, s1, REG_FTMP3);
1873                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instruction  */
1874                                 M_LADD_IMM(REG_ZERO, 1, d);
1875                                 }
1876                         else {
1877                                 M_LSUB_IMM(REG_ZERO, 1, d);
1878                                 M_FCMPEQS(s1, s2, REG_FTMP3);
1879                                 M_TRAPB;
1880                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instructions */
1881                                 M_CLR   (d);
1882                                 M_FCMPLTS(s2, s1, REG_FTMP3);
1883                                 M_TRAPB;
1884                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instruction  */
1885                                 M_LADD_IMM(REG_ZERO, 1, d);
1886                                 }
1887                         store_reg_to_var_int(iptr->dst, d);
1888                         break;
1889                         
1890                 case ICMD_FCMPG:      /* ..., val1, val2  ==> ..., val1 fcmpg val2    */
1891                 case ICMD_DCMPG:
1892                         var_to_reg_flt(s1, src->prev, REG_FTMP1);
1893                         var_to_reg_flt(s2, src, REG_FTMP2);
1894                         d = reg_of_var(iptr->dst, REG_ITMP3);
1895                         if (opt_noieee) {
1896                                 M_LADD_IMM(REG_ZERO, 1, d);
1897                                 M_FCMPEQ(s1, s2, REG_FTMP3);
1898                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instruction  */
1899                                 M_CLR   (d);
1900                                 M_FCMPLT(s1, s2, REG_FTMP3);
1901                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instruction  */
1902                                 M_LSUB_IMM(REG_ZERO, 1, d);
1903                                 }
1904                         else {
1905                                 M_LADD_IMM(REG_ZERO, 1, d);
1906                                 M_FCMPEQS(s1, s2, REG_FTMP3);
1907                                 M_TRAPB;
1908                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instruction  */
1909                                 M_CLR   (d);
1910                                 M_FCMPLTS(s1, s2, REG_FTMP3);
1911                                 M_TRAPB;
1912                                 M_FBEQZ (REG_FTMP3, 1);        /* jump over next instruction  */
1913                                 M_LSUB_IMM(REG_ZERO, 1, d);
1914                                 }
1915                         store_reg_to_var_int(iptr->dst, d);
1916                         break;
1917
1918
1919                 /* memory operations **************************************************/
1920
1921                         /* #define gen_bound_check \
1922                         if (checkbounds) {\
1923                                 M_ILD(REG_ITMP3, s1, OFFSET(java_arrayheader, size));\
1924                                 M_CMPULT(s2, REG_ITMP3, REG_ITMP3);\
1925                                 M_BEQZ(REG_ITMP3, 0);\
1926                                 codegen_addxboundrefs(mcodeptr);\
1927                                 }
1928                         */
1929
1930 #define gen_bound_check \
1931             if (checkbounds) { \
1932                                 M_ILD(REG_ITMP3, s1, OFFSET(java_arrayheader, size));\
1933                                 M_CMPULT(s2, REG_ITMP3, REG_ITMP3);\
1934                                 M_BEQZ(REG_ITMP3, 0);\
1935                                 codegen_addxboundrefs(mcodeptr); \
1936                 }
1937
1938                 case ICMD_ARRAYLENGTH: /* ..., arrayref  ==> ..., length              */
1939
1940                         var_to_reg_int(s1, src, REG_ITMP1);
1941                         d = reg_of_var(iptr->dst, REG_ITMP3);
1942                         gen_nullptr_check(s1);
1943                         M_ILD(d, s1, OFFSET(java_arrayheader, size));
1944                         store_reg_to_var_int(iptr->dst, d);
1945                         break;
1946
1947                 case ICMD_AALOAD:     /* ..., arrayref, index  ==> ..., value         */
1948
1949                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1950                         var_to_reg_int(s2, src, REG_ITMP2);
1951                         d = reg_of_var(iptr->dst, REG_ITMP3);
1952                         if (iptr->op1 == 0) {
1953                                 gen_nullptr_check(s1);
1954                                 gen_bound_check;
1955                                 }
1956                         M_SAADDQ(s2, s1, REG_ITMP1);
1957                         M_ALD( d, REG_ITMP1, OFFSET(java_objectarray, data[0]));
1958                         store_reg_to_var_int(iptr->dst, d);
1959                         break;
1960
1961                 case ICMD_LALOAD:     /* ..., arrayref, index  ==> ..., value         */
1962
1963                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1964                         var_to_reg_int(s2, src, REG_ITMP2);
1965                         d = reg_of_var(iptr->dst, REG_ITMP3);
1966                         if (iptr->op1 == 0) {
1967                                 gen_nullptr_check(s1);
1968                                 gen_bound_check;
1969                                 }
1970                         M_S8ADDQ(s2, s1, REG_ITMP1);
1971                         M_LLD(d, REG_ITMP1, OFFSET(java_longarray, data[0]));
1972                         store_reg_to_var_int(iptr->dst, d);
1973                         break;
1974
1975                 case ICMD_IALOAD:     /* ..., arrayref, index  ==> ..., value         */
1976
1977                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1978                         var_to_reg_int(s2, src, REG_ITMP2);
1979                         d = reg_of_var(iptr->dst, REG_ITMP3);
1980                         if (iptr->op1 == 0) {
1981                                 gen_nullptr_check(s1);
1982                                 gen_bound_check;
1983                                 }
1984                   
1985                         M_S4ADDQ(s2, s1, REG_ITMP1);
1986                         M_ILD(d, REG_ITMP1, OFFSET(java_intarray, data[0]));
1987                         store_reg_to_var_int(iptr->dst, d);
1988                         break;
1989
1990                 case ICMD_FALOAD:     /* ..., arrayref, index  ==> ..., value         */
1991
1992                         var_to_reg_int(s1, src->prev, REG_ITMP1);
1993                         var_to_reg_int(s2, src, REG_ITMP2);
1994                         d = reg_of_var(iptr->dst, REG_FTMP3);
1995                         if (iptr->op1 == 0) {
1996                                 gen_nullptr_check(s1);
1997                                 gen_bound_check;
1998                                 }
1999                         M_S4ADDQ(s2, s1, REG_ITMP1);
2000                         M_FLD(d, REG_ITMP1, OFFSET(java_floatarray, data[0]));
2001                         store_reg_to_var_flt(iptr->dst, d);
2002                         break;
2003
2004                 case ICMD_DALOAD:     /* ..., arrayref, index  ==> ..., value         */
2005
2006                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2007                         var_to_reg_int(s2, src, REG_ITMP2);
2008                         d = reg_of_var(iptr->dst, REG_FTMP3);
2009                         if (iptr->op1 == 0) {
2010                                 gen_nullptr_check(s1);
2011                                 gen_bound_check;
2012                                 }
2013                         M_S8ADDQ(s2, s1, REG_ITMP1);
2014                         M_DLD(d, REG_ITMP1, OFFSET(java_doublearray, data[0]));
2015                         store_reg_to_var_flt(iptr->dst, d);
2016                         break;
2017
2018                 case ICMD_CALOAD:     /* ..., arrayref, index  ==> ..., value         */
2019
2020                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2021                         var_to_reg_int(s2, src, REG_ITMP2);
2022                         d = reg_of_var(iptr->dst, REG_ITMP3);
2023                         if (iptr->op1 == 0) {
2024                                 gen_nullptr_check(s1);
2025                                 gen_bound_check;
2026                                 }
2027                         if (has_ext_instr_set) {
2028                                 M_LADD(s2, s1, REG_ITMP1);
2029                                 M_LADD(s2, REG_ITMP1, REG_ITMP1);
2030                                 M_SLDU(d, REG_ITMP1, OFFSET(java_chararray, data[0]));
2031                                 }
2032                         else {
2033                                 M_LADD (s2, s1, REG_ITMP1);
2034                                 M_LADD (s2, REG_ITMP1, REG_ITMP1);
2035                                 M_LLD_U(REG_ITMP2, REG_ITMP1, OFFSET(java_chararray, data[0]));
2036                                 M_LDA  (REG_ITMP1, REG_ITMP1, OFFSET(java_chararray, data[0]));
2037                                 M_EXTWL(REG_ITMP2, REG_ITMP1, d);
2038                                 }
2039                         store_reg_to_var_int(iptr->dst, d);
2040                         break;                  
2041
2042                 case ICMD_SALOAD:     /* ..., arrayref, index  ==> ..., value         */
2043
2044                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2045                         var_to_reg_int(s2, src, REG_ITMP2);
2046                         d = reg_of_var(iptr->dst, REG_ITMP3);
2047                         if (iptr->op1 == 0) {
2048                                 gen_nullptr_check(s1);
2049                                 gen_bound_check;
2050                                 }
2051                         if (has_ext_instr_set) {
2052                                 M_LADD(s2, s1, REG_ITMP1);
2053                                 M_LADD(s2, REG_ITMP1, REG_ITMP1);
2054                                 M_SLDU( d, REG_ITMP1, OFFSET (java_shortarray, data[0]));
2055                                 M_SSEXT(d, d);
2056                                 }
2057                         else {
2058                                 M_LADD(s2, s1, REG_ITMP1);
2059                                 M_LADD(s2, REG_ITMP1, REG_ITMP1);
2060                                 M_LLD_U(REG_ITMP2, REG_ITMP1, OFFSET(java_shortarray, data[0]));
2061                                 M_LDA(REG_ITMP1, REG_ITMP1, OFFSET(java_shortarray, data[0])+2);
2062                                 M_EXTQH(REG_ITMP2, REG_ITMP1, d);
2063                                 M_SRA_IMM(d, 48, d);
2064                                 }
2065                         store_reg_to_var_int(iptr->dst, d);
2066                         break;
2067
2068                 case ICMD_BALOAD:     /* ..., arrayref, index  ==> ..., value         */
2069
2070                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2071                         var_to_reg_int(s2, src, REG_ITMP2);
2072                         d = reg_of_var(iptr->dst, REG_ITMP3);
2073                         if (iptr->op1 == 0) {
2074                                 gen_nullptr_check(s1);
2075                                 gen_bound_check;
2076                                 }
2077                         if (has_ext_instr_set) {
2078                                 M_LADD   (s2, s1, REG_ITMP1);
2079                                 M_BLDU   (d, REG_ITMP1, OFFSET (java_bytearray, data[0]));
2080                                 M_BSEXT  (d, d);
2081                                 }
2082                         else {
2083                                 M_LADD(s2, s1, REG_ITMP1);
2084                                 M_LLD_U(REG_ITMP2, REG_ITMP1, OFFSET(java_bytearray, data[0]));
2085                                 M_LDA(REG_ITMP1, REG_ITMP1, OFFSET(java_bytearray, data[0])+1);
2086                                 M_EXTQH(REG_ITMP2, REG_ITMP1, d);
2087                                 M_SRA_IMM(d, 56, d);
2088                                 }
2089                         store_reg_to_var_int(iptr->dst, d);
2090                         break;
2091
2092
2093                 case ICMD_AASTORE:    /* ..., arrayref, index, value  ==> ...         */
2094
2095                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2096                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2097                         if (iptr->op1 == 0) {
2098                                 gen_nullptr_check(s1);
2099                                 gen_bound_check;
2100                                 }
2101                         var_to_reg_int(s3, src, REG_ITMP3);
2102                         M_SAADDQ(s2, s1, REG_ITMP1);
2103                         M_AST   (s3, REG_ITMP1, OFFSET(java_objectarray, data[0]));
2104                         break;
2105
2106                 case ICMD_LASTORE:    /* ..., arrayref, index, value  ==> ...         */
2107
2108                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2109                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2110                         if (iptr->op1 == 0) {
2111                                 gen_nullptr_check(s1);
2112                                 gen_bound_check;
2113                                 }
2114                         var_to_reg_int(s3, src, REG_ITMP3);
2115                         M_S8ADDQ(s2, s1, REG_ITMP1);
2116                         M_LST   (s3, REG_ITMP1, OFFSET(java_longarray, data[0]));
2117                         break;
2118
2119                 case ICMD_IASTORE:    /* ..., arrayref, index, value  ==> ...         */
2120
2121                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2122                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2123                         if (iptr->op1 == 0) {
2124                                 gen_nullptr_check(s1);
2125                                 gen_bound_check;
2126                                 }
2127
2128                         var_to_reg_int(s3, src, REG_ITMP3);
2129                         M_S4ADDQ(s2, s1, REG_ITMP1);
2130                         M_IST   (s3, REG_ITMP1, OFFSET(java_intarray, data[0]));
2131                         break;
2132
2133                 case ICMD_FASTORE:    /* ..., arrayref, index, value  ==> ...         */
2134
2135                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2136                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2137                         if (iptr->op1 == 0) {
2138                                 gen_nullptr_check(s1);
2139                                 gen_bound_check;
2140                                 }
2141                         var_to_reg_flt(s3, src, REG_FTMP3);
2142                         M_S4ADDQ(s2, s1, REG_ITMP1);
2143                         M_FST   (s3, REG_ITMP1, OFFSET(java_floatarray, data[0]));
2144                         break;
2145
2146                 case ICMD_DASTORE:    /* ..., arrayref, index, value  ==> ...         */
2147
2148                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2149                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2150                         if (iptr->op1 == 0) {
2151                                 gen_nullptr_check(s1);
2152                                 gen_bound_check;
2153                                 }
2154                         var_to_reg_flt(s3, src, REG_FTMP3);
2155                         M_S8ADDQ(s2, s1, REG_ITMP1);
2156                         M_DST   (s3, REG_ITMP1, OFFSET(java_doublearray, data[0]));
2157                         break;
2158
2159                 case ICMD_CASTORE:    /* ..., arrayref, index, value  ==> ...         */
2160
2161                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2162                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2163                         if (iptr->op1 == 0) {
2164                                 gen_nullptr_check(s1);
2165                                 gen_bound_check;
2166                                 }
2167                         var_to_reg_int(s3, src, REG_ITMP3);
2168                         if (has_ext_instr_set) {
2169                                 M_LADD(s2, s1, REG_ITMP1);
2170                                 M_LADD(s2, REG_ITMP1, REG_ITMP1);
2171                                 M_SST (s3, REG_ITMP1, OFFSET(java_chararray, data[0]));
2172                                 }
2173                         else {
2174                                 M_LADD (s2, s1, REG_ITMP1);
2175                                 M_LADD (s2, REG_ITMP1, REG_ITMP1);
2176                                 M_LLD_U(REG_ITMP2, REG_ITMP1, OFFSET(java_chararray, data[0]));
2177                                 M_LDA  (REG_ITMP1, REG_ITMP1, OFFSET(java_chararray, data[0]));
2178                                 M_INSWL(s3, REG_ITMP1, REG_ITMP3);
2179                                 M_MSKWL(REG_ITMP2, REG_ITMP1, REG_ITMP2);
2180                                 M_OR   (REG_ITMP2, REG_ITMP3, REG_ITMP2);
2181                                 M_LST_U(REG_ITMP2, REG_ITMP1, 0);
2182                                 }
2183                         break;
2184
2185                 case ICMD_SASTORE:    /* ..., arrayref, index, value  ==> ...         */
2186
2187                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2188                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2189                         if (iptr->op1 == 0) {
2190                                 gen_nullptr_check(s1);
2191                                 gen_bound_check;
2192                                 }
2193                         var_to_reg_int(s3, src, REG_ITMP3);
2194                         if (has_ext_instr_set) {
2195                                 M_LADD(s2, s1, REG_ITMP1);
2196                                 M_LADD(s2, REG_ITMP1, REG_ITMP1);
2197                                 M_SST (s3, REG_ITMP1, OFFSET(java_shortarray, data[0]));
2198                                 }
2199                         else {
2200                                 M_LADD (s2, s1, REG_ITMP1);
2201                                 M_LADD (s2, REG_ITMP1, REG_ITMP1);
2202                                 M_LLD_U(REG_ITMP2, REG_ITMP1, OFFSET(java_shortarray, data[0]));
2203                                 M_LDA  (REG_ITMP1, REG_ITMP1, OFFSET(java_shortarray, data[0]));
2204                                 M_INSWL(s3, REG_ITMP1, REG_ITMP3);
2205                                 M_MSKWL(REG_ITMP2, REG_ITMP1, REG_ITMP2);
2206                                 M_OR   (REG_ITMP2, REG_ITMP3, REG_ITMP2);
2207                                 M_LST_U(REG_ITMP2, REG_ITMP1, 0);
2208                                 }
2209                         break;
2210
2211                 case ICMD_BASTORE:    /* ..., arrayref, index, value  ==> ...         */
2212
2213                         var_to_reg_int(s1, src->prev->prev, REG_ITMP1);
2214                         var_to_reg_int(s2, src->prev, REG_ITMP2);
2215                         if (iptr->op1 == 0) {
2216                                 gen_nullptr_check(s1);
2217                                 gen_bound_check;
2218                                 }
2219                         var_to_reg_int(s3, src, REG_ITMP3);
2220                         if (has_ext_instr_set) {
2221                                 M_LADD(s2, s1, REG_ITMP1);
2222                                 M_BST (s3, REG_ITMP1, OFFSET(java_bytearray, data[0]));
2223                                 }
2224                         else {
2225                                 M_LADD (s2, s1, REG_ITMP1);
2226                                 M_LLD_U(REG_ITMP2, REG_ITMP1, OFFSET(java_bytearray, data[0]));
2227                                 M_LDA  (REG_ITMP1, REG_ITMP1, OFFSET(java_bytearray, data[0]));
2228                                 M_INSBL(s3, REG_ITMP1, REG_ITMP3);
2229                                 M_MSKBL(REG_ITMP2, REG_ITMP1, REG_ITMP2);
2230                                 M_OR   (REG_ITMP2, REG_ITMP3, REG_ITMP2);
2231                                 M_LST_U(REG_ITMP2, REG_ITMP1, 0);
2232                                 }
2233                         break;
2234
2235
2236                 case ICMD_PUTSTATIC:  /* ..., value  ==> ...                          */
2237                                       /* op1 = type, val.a = field address            */
2238
2239                         a = dseg_addaddress (&(((fieldinfo *)(iptr->val.a))->value));
2240                         M_ALD(REG_ITMP1, REG_PV, a);
2241                         switch (iptr->op1) {
2242                                 case TYPE_INT:
2243                                         var_to_reg_int(s2, src, REG_ITMP2);
2244                                         M_IST(s2, REG_ITMP1, 0);
2245                                         break;
2246                                 case TYPE_LNG:
2247                                         var_to_reg_int(s2, src, REG_ITMP2);
2248                                         M_LST(s2, REG_ITMP1, 0);
2249                                         break;
2250                                 case TYPE_ADR:
2251                                         var_to_reg_int(s2, src, REG_ITMP2);
2252                                         M_AST(s2, REG_ITMP1, 0);
2253                                         break;
2254                                 case TYPE_FLT:
2255                                         var_to_reg_flt(s2, src, REG_FTMP2);
2256                                         M_FST(s2, REG_ITMP1, 0);
2257                                         break;
2258                                 case TYPE_DBL:
2259                                         var_to_reg_flt(s2, src, REG_FTMP2);
2260                                         M_DST(s2, REG_ITMP1, 0);
2261                                         break;
2262                                 default: panic ("internal error");
2263                                 }
2264                         break;
2265
2266                 case ICMD_GETSTATIC:  /* ...  ==> ..., value                          */
2267                                       /* op1 = type, val.a = field address            */
2268
2269                         a = dseg_addaddress (&(((fieldinfo *)(iptr->val.a))->value));
2270                         M_ALD(REG_ITMP1, REG_PV, a);
2271                         switch (iptr->op1) {
2272                                 case TYPE_INT:
2273                                         d = reg_of_var(iptr->dst, REG_ITMP3);
2274                                         M_ILD(d, REG_ITMP1, 0);
2275                                         store_reg_to_var_int(iptr->dst, d);
2276                                         break;
2277                                 case TYPE_LNG:
2278                                         d = reg_of_var(iptr->dst, REG_ITMP3);
2279                                         M_LLD(d, REG_ITMP1, 0);
2280                                         store_reg_to_var_int(iptr->dst, d);
2281                                         break;
2282                                 case TYPE_ADR:
2283                                         d = reg_of_var(iptr->dst, REG_ITMP3);
2284                                         M_ALD(d, REG_ITMP1, 0);
2285                                         store_reg_to_var_int(iptr->dst, d);
2286                                         break;
2287                                 case TYPE_FLT:
2288                                         d = reg_of_var(iptr->dst, REG_FTMP1);
2289                                         M_FLD(d, REG_ITMP1, 0);
2290                                         store_reg_to_var_flt(iptr->dst, d);
2291                                         break;
2292                                 case TYPE_DBL:                          
2293                                         d = reg_of_var(iptr->dst, REG_FTMP1);
2294                                         M_DLD(d, REG_ITMP1, 0);
2295                                         store_reg_to_var_flt(iptr->dst, d);
2296                                         break;
2297                                 default: panic ("internal error");
2298                                 }
2299                         break;
2300
2301
2302                 case ICMD_PUTFIELD:   /* ..., value  ==> ...                          */
2303                                       /* op1 = type, val.i = field offset             */
2304
2305                         a = ((fieldinfo *)(iptr->val.a))->offset;
2306                         switch (iptr->op1) {
2307                                 case TYPE_INT:
2308                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2309                                         var_to_reg_int(s2, src, REG_ITMP2);
2310                                         gen_nullptr_check(s1);
2311                                         M_IST(s2, s1, a);
2312                                         break;
2313                                 case TYPE_LNG:
2314                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2315                                         var_to_reg_int(s2, src, REG_ITMP2);
2316                                         gen_nullptr_check(s1);
2317                                         M_LST(s2, s1, a);
2318                                         break;
2319                                 case TYPE_ADR:
2320                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2321                                         var_to_reg_int(s2, src, REG_ITMP2);
2322                                         gen_nullptr_check(s1);
2323                                         M_AST(s2, s1, a);
2324                                         break;
2325                                 case TYPE_FLT:
2326                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2327                                         var_to_reg_flt(s2, src, REG_FTMP2);
2328                                         gen_nullptr_check(s1);
2329                                         M_FST(s2, s1, a);
2330                                         break;
2331                                 case TYPE_DBL:
2332                                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2333                                         var_to_reg_flt(s2, src, REG_FTMP2);
2334                                         gen_nullptr_check(s1);
2335                                         M_DST(s2, s1, a);
2336                                         break;
2337                                 default: panic ("internal error");
2338                                 }
2339                         break;
2340
2341                 case ICMD_GETFIELD:   /* ...  ==> ..., value                          */
2342                                       /* op1 = type, val.i = field offset             */
2343
2344                         a = ((fieldinfo *)(iptr->val.a))->offset;
2345                         switch (iptr->op1) {
2346                                 case TYPE_INT:
2347                                         var_to_reg_int(s1, src, REG_ITMP1);
2348                                         d = reg_of_var(iptr->dst, REG_ITMP3);
2349                                         gen_nullptr_check(s1);
2350                                         M_ILD(d, s1, a);
2351                                         store_reg_to_var_int(iptr->dst, d);
2352                                         break;
2353                                 case TYPE_LNG:
2354                                         var_to_reg_int(s1, src, REG_ITMP1);
2355                                         d = reg_of_var(iptr->dst, REG_ITMP3);
2356                                         gen_nullptr_check(s1);
2357                                         M_LLD(d, s1, a);
2358                                         store_reg_to_var_int(iptr->dst, d);
2359                                         break;
2360                                 case TYPE_ADR:
2361                                         var_to_reg_int(s1, src, REG_ITMP1);
2362                                         d = reg_of_var(iptr->dst, REG_ITMP3);
2363                                         gen_nullptr_check(s1);
2364                                         M_ALD(d, s1, a);
2365                                         store_reg_to_var_int(iptr->dst, d);
2366                                         break;
2367                                 case TYPE_FLT:
2368                                         var_to_reg_int(s1, src, REG_ITMP1);
2369                                         d = reg_of_var(iptr->dst, REG_FTMP1);
2370                                         gen_nullptr_check(s1);
2371                                         M_FLD(d, s1, a);
2372                                         store_reg_to_var_flt(iptr->dst, d);
2373                                         break;
2374                                 case TYPE_DBL:                          
2375                                         var_to_reg_int(s1, src, REG_ITMP1);
2376                                         d = reg_of_var(iptr->dst, REG_FTMP1);
2377                                         gen_nullptr_check(s1);
2378                                         M_DLD(d, s1, a);
2379                                         store_reg_to_var_flt(iptr->dst, d);
2380                                         break;
2381                                 default: panic ("internal error");
2382                                 }
2383                         break;
2384
2385
2386                 /* branch operations **************************************************/
2387
2388 #define ALIGNCODENOP {if((int)((long)mcodeptr&7)){M_NOP;}}
2389
2390                 case ICMD_ATHROW:       /* ..., objectref ==> ... (, objectref)       */
2391
2392                         var_to_reg_int(s1, src, REG_ITMP1);
2393                         M_INTMOVE(s1, REG_ITMP1_XPTR);
2394                         a = dseg_addaddress(asm_handle_exception);
2395                         M_ALD(REG_ITMP2, REG_PV, a);
2396                         M_JMP(REG_ITMP2_XPC, REG_ITMP2);
2397                         M_NOP;              /* nop ensures that XPC is less than the end */
2398                                             /* of basic block                            */
2399                         ALIGNCODENOP;
2400                         break;
2401
2402                 case ICMD_GOTO:         /* ... ==> ...                                */
2403                                         /* op1 = target JavaVM pc                     */
2404                         M_BR(0);
2405                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2406                         ALIGNCODENOP;
2407                         break;
2408
2409                 case ICMD_JSR:          /* ... ==> ...                                */
2410                                         /* op1 = target JavaVM pc                     */
2411
2412                         M_BSR(REG_ITMP1, 0);
2413                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2414                         break;
2415                         
2416                 case ICMD_RET:          /* ... ==> ...                                */
2417                                         /* op1 = local variable                       */
2418
2419                         var = &(locals[iptr->op1][TYPE_ADR]);
2420                         if (var->flags & INMEMORY) {
2421                                 M_ALD(REG_ITMP1, REG_SP, 8 * var->regoff);
2422                                 M_RET(REG_ZERO, REG_ITMP1);
2423                                 }
2424                         else
2425                                 M_RET(REG_ZERO, var->regoff);
2426                         ALIGNCODENOP;
2427                         break;
2428
2429                 case ICMD_IFNULL:       /* ..., value ==> ...                         */
2430                                         /* op1 = target JavaVM pc                     */
2431
2432                         var_to_reg_int(s1, src, REG_ITMP1);
2433                         M_BEQZ(s1, 0);
2434                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2435                         break;
2436
2437                 case ICMD_IFNONNULL:    /* ..., value ==> ...                         */
2438                                         /* op1 = target JavaVM pc                     */
2439
2440                         var_to_reg_int(s1, src, REG_ITMP1);
2441                         M_BNEZ(s1, 0);
2442                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2443                         break;
2444
2445                 case ICMD_IFEQ:         /* ..., value ==> ...                         */
2446                                         /* op1 = target JavaVM pc, val.i = constant   */
2447
2448                         var_to_reg_int(s1, src, REG_ITMP1);
2449                         if (iptr->val.i == 0) {
2450                                 M_BEQZ(s1, 0);
2451                                 }
2452                         else {
2453                                 if ((iptr->val.i > 0) && (iptr->val.i <= 255)) {
2454                                         M_CMPEQ_IMM(s1, iptr->val.i, REG_ITMP1);
2455                                         }
2456                                 else {
2457                                         ICONST(REG_ITMP2, iptr->val.i);
2458                                         M_CMPEQ(s1, REG_ITMP2, REG_ITMP1);
2459                                         }
2460                                 M_BNEZ(REG_ITMP1, 0);
2461                                 }
2462                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2463                         break;
2464
2465                 case ICMD_IFLT:         /* ..., value ==> ...                         */
2466                                         /* op1 = target JavaVM pc, val.i = constant   */
2467
2468                         var_to_reg_int(s1, src, REG_ITMP1);
2469                         if (iptr->val.i == 0) {
2470                                 M_BLTZ(s1, 0);
2471                                 }
2472                         else {
2473                                 if ((iptr->val.i > 0) && (iptr->val.i <= 255)) {
2474                                         M_CMPLT_IMM(s1, iptr->val.i, REG_ITMP1);
2475                                         }
2476                                 else {
2477                                         ICONST(REG_ITMP2, iptr->val.i);
2478                                         M_CMPLT(s1, REG_ITMP2, REG_ITMP1);
2479                                         }
2480                                 M_BNEZ(REG_ITMP1, 0);
2481                                 }
2482                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2483                         break;
2484
2485                 case ICMD_IFLE:         /* ..., value ==> ...                         */
2486                                         /* op1 = target JavaVM pc, val.i = constant   */
2487
2488                         var_to_reg_int(s1, src, REG_ITMP1);
2489                         if (iptr->val.i == 0) {
2490                                 M_BLEZ(s1, 0);
2491                                 }
2492                         else {
2493                                 if ((iptr->val.i > 0) && (iptr->val.i <= 255)) {
2494                                         M_CMPLE_IMM(s1, iptr->val.i, REG_ITMP1);
2495                                         }
2496                                 else {
2497                                         ICONST(REG_ITMP2, iptr->val.i);
2498                                         M_CMPLE(s1, REG_ITMP2, REG_ITMP1);
2499                                         }
2500                                 M_BNEZ(REG_ITMP1, 0);
2501                                 }
2502                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2503                         break;
2504
2505                 case ICMD_IFNE:         /* ..., value ==> ...                         */
2506                                         /* op1 = target JavaVM pc, val.i = constant   */
2507
2508                         var_to_reg_int(s1, src, REG_ITMP1);
2509                         if (iptr->val.i == 0) {
2510                                 M_BNEZ(s1, 0);
2511                                 }
2512                         else {
2513                                 if ((iptr->val.i > 0) && (iptr->val.i <= 255)) {
2514                                         M_CMPEQ_IMM(s1, iptr->val.i, REG_ITMP1);
2515                                         }
2516                                 else {
2517                                         ICONST(REG_ITMP2, iptr->val.i);
2518                                         M_CMPEQ(s1, REG_ITMP2, REG_ITMP1);
2519                                         }
2520                                 M_BEQZ(REG_ITMP1, 0);
2521                                 }
2522                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2523                         break;
2524
2525                 case ICMD_IFGT:         /* ..., value ==> ...                         */
2526                                         /* op1 = target JavaVM pc, val.i = constant   */
2527
2528                         var_to_reg_int(s1, src, REG_ITMP1);
2529                         if (iptr->val.i == 0) {
2530                                 M_BGTZ(s1, 0);
2531                                 }
2532                         else {
2533                                 if ((iptr->val.i > 0) && (iptr->val.i <= 255)) {
2534                                         M_CMPLE_IMM(s1, iptr->val.i, REG_ITMP1);
2535                                         }
2536                                 else {
2537                                         ICONST(REG_ITMP2, iptr->val.i);
2538                                         M_CMPLE(s1, REG_ITMP2, REG_ITMP1);
2539                                         }
2540                                 M_BEQZ(REG_ITMP1, 0);
2541                                 }
2542                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2543                         break;
2544
2545                 case ICMD_IFGE:         /* ..., value ==> ...                         */
2546                                         /* op1 = target JavaVM pc, val.i = constant   */
2547
2548                         var_to_reg_int(s1, src, REG_ITMP1);
2549                         if (iptr->val.i == 0) {
2550                                 M_BGEZ(s1, 0);
2551                                 }
2552                         else {
2553                                 if ((iptr->val.i > 0) && (iptr->val.i <= 255)) {
2554                                         M_CMPLT_IMM(s1, iptr->val.i, REG_ITMP1);
2555                                         }
2556                                 else {
2557                                         ICONST(REG_ITMP2, iptr->val.i);
2558                                         M_CMPLT(s1, REG_ITMP2, REG_ITMP1);
2559                                         }
2560                                 M_BEQZ(REG_ITMP1, 0);
2561                                 }
2562                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2563                         break;
2564
2565                 case ICMD_IF_LEQ:       /* ..., value ==> ...                         */
2566                                         /* op1 = target JavaVM pc, val.l = constant   */
2567
2568                         var_to_reg_int(s1, src, REG_ITMP1);
2569                         if (iptr->val.l == 0) {
2570                                 M_BEQZ(s1, 0);
2571                                 }
2572                         else {
2573                                 if ((iptr->val.l > 0) && (iptr->val.l <= 255)) {
2574                                         M_CMPEQ_IMM(s1, iptr->val.l, REG_ITMP1);
2575                                         }
2576                                 else {
2577                                         LCONST(REG_ITMP2, iptr->val.l);
2578                                         M_CMPEQ(s1, REG_ITMP2, REG_ITMP1);
2579                                         }
2580                                 M_BNEZ(REG_ITMP1, 0);
2581                                 }
2582                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2583                         break;
2584
2585                 case ICMD_IF_LLT:       /* ..., value ==> ...                         */
2586                                         /* op1 = target JavaVM pc, val.l = constant   */
2587
2588                         var_to_reg_int(s1, src, REG_ITMP1);
2589                         if (iptr->val.l == 0) {
2590                                 M_BLTZ(s1, 0);
2591                                 }
2592                         else {
2593                                 if ((iptr->val.l > 0) && (iptr->val.l <= 255)) {
2594                                         M_CMPLT_IMM(s1, iptr->val.l, REG_ITMP1);
2595                                         }
2596                                 else {
2597                                         LCONST(REG_ITMP2, iptr->val.l);
2598                                         M_CMPLT(s1, REG_ITMP2, REG_ITMP1);
2599                                         }
2600                                 M_BNEZ(REG_ITMP1, 0);
2601                                 }
2602                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2603                         break;
2604
2605                 case ICMD_IF_LLE:       /* ..., value ==> ...                         */
2606                                         /* op1 = target JavaVM pc, val.l = constant   */
2607
2608                         var_to_reg_int(s1, src, REG_ITMP1);
2609                         if (iptr->val.l == 0) {
2610                                 M_BLEZ(s1, 0);
2611                                 }
2612                         else {
2613                                 if ((iptr->val.l > 0) && (iptr->val.l <= 255)) {
2614                                         M_CMPLE_IMM(s1, iptr->val.l, REG_ITMP1);
2615                                         }
2616                                 else {
2617                                         LCONST(REG_ITMP2, iptr->val.l);
2618                                         M_CMPLE(s1, REG_ITMP2, REG_ITMP1);
2619                                         }
2620                                 M_BNEZ(REG_ITMP1, 0);
2621                                 }
2622                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2623                         break;
2624
2625                 case ICMD_IF_LNE:       /* ..., value ==> ...                         */
2626                                         /* op1 = target JavaVM pc, val.l = constant   */
2627
2628                         var_to_reg_int(s1, src, REG_ITMP1);
2629                         if (iptr->val.l == 0) {
2630                                 M_BNEZ(s1, 0);
2631                                 }
2632                         else {
2633                                 if ((iptr->val.l > 0) && (iptr->val.l <= 255)) {
2634                                         M_CMPEQ_IMM(s1, iptr->val.l, REG_ITMP1);
2635                                         }
2636                                 else {
2637                                         LCONST(REG_ITMP2, iptr->val.l);
2638                                         M_CMPEQ(s1, REG_ITMP2, REG_ITMP1);
2639                                         }
2640                                 M_BEQZ(REG_ITMP1, 0);
2641                                 }
2642                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2643                         break;
2644
2645                 case ICMD_IF_LGT:       /* ..., value ==> ...                         */
2646                                         /* op1 = target JavaVM pc, val.l = constant   */
2647
2648                         var_to_reg_int(s1, src, REG_ITMP1);
2649                         if (iptr->val.l == 0) {
2650                                 M_BGTZ(s1, 0);
2651                                 }
2652                         else {
2653                                 if ((iptr->val.l > 0) && (iptr->val.l <= 255)) {
2654                                         M_CMPLE_IMM(s1, iptr->val.l, REG_ITMP1);
2655                                         }
2656                                 else {
2657                                         LCONST(REG_ITMP2, iptr->val.l);
2658                                         M_CMPLE(s1, REG_ITMP2, REG_ITMP1);
2659                                         }
2660                                 M_BEQZ(REG_ITMP1, 0);
2661                                 }
2662                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2663                         break;
2664
2665                 case ICMD_IF_LGE:       /* ..., value ==> ...                         */
2666                                         /* op1 = target JavaVM pc, val.l = constant   */
2667
2668                         var_to_reg_int(s1, src, REG_ITMP1);
2669                         if (iptr->val.l == 0) {
2670                                 M_BGEZ(s1, 0);
2671                                 }
2672                         else {
2673                                 if ((iptr->val.l > 0) && (iptr->val.l <= 255)) {
2674                                         M_CMPLT_IMM(s1, iptr->val.l, REG_ITMP1);
2675                                         }
2676                                 else {
2677                                         LCONST(REG_ITMP2, iptr->val.l);
2678                                         M_CMPLT(s1, REG_ITMP2, REG_ITMP1);
2679                                         }
2680                                 M_BEQZ(REG_ITMP1, 0);
2681                                 }
2682                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2683                         break;
2684
2685                 case ICMD_IF_ICMPEQ:    /* ..., value, value ==> ...                  */
2686                 case ICMD_IF_LCMPEQ:    /* op1 = target JavaVM pc                     */
2687                 case ICMD_IF_ACMPEQ:
2688
2689                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2690                         var_to_reg_int(s2, src, REG_ITMP2);
2691                         M_CMPEQ(s1, s2, REG_ITMP1);
2692                         M_BNEZ(REG_ITMP1, 0);
2693                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2694                         break;
2695
2696                 case ICMD_IF_ICMPNE:    /* ..., value, value ==> ...                  */
2697                 case ICMD_IF_LCMPNE:    /* op1 = target JavaVM pc                     */
2698                 case ICMD_IF_ACMPNE:
2699
2700                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2701                         var_to_reg_int(s2, src, REG_ITMP2);
2702                         M_CMPEQ(s1, s2, REG_ITMP1);
2703                         M_BEQZ(REG_ITMP1, 0);
2704                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2705                         break;
2706
2707                 case ICMD_IF_ICMPLT:    /* ..., value, value ==> ...                  */
2708                 case ICMD_IF_LCMPLT:    /* op1 = target JavaVM pc                     */
2709
2710                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2711                         var_to_reg_int(s2, src, REG_ITMP2);
2712                         M_CMPLT(s1, s2, REG_ITMP1);
2713                         M_BNEZ(REG_ITMP1, 0);
2714                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2715                         break;
2716
2717                 case ICMD_IF_ICMPGT:    /* ..., value, value ==> ...                  */
2718                 case ICMD_IF_LCMPGT:    /* op1 = target JavaVM pc                     */
2719
2720                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2721                         var_to_reg_int(s2, src, REG_ITMP2);
2722                         M_CMPLE(s1, s2, REG_ITMP1);
2723                         M_BEQZ(REG_ITMP1, 0);
2724                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2725                         break;
2726
2727                 case ICMD_IF_ICMPLE:    /* ..., value, value ==> ...                  */
2728                 case ICMD_IF_LCMPLE:    /* op1 = target JavaVM pc                     */
2729
2730                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2731                         var_to_reg_int(s2, src, REG_ITMP2);
2732                         M_CMPLE(s1, s2, REG_ITMP1);
2733                         M_BNEZ(REG_ITMP1, 0);
2734                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2735                         break;
2736
2737                 case ICMD_IF_ICMPGE:    /* ..., value, value ==> ...                  */
2738                 case ICMD_IF_LCMPGE:    /* op1 = target JavaVM pc                     */
2739
2740                         var_to_reg_int(s1, src->prev, REG_ITMP1);
2741                         var_to_reg_int(s2, src, REG_ITMP2);
2742                         M_CMPLT(s1, s2, REG_ITMP1);
2743                         M_BEQZ(REG_ITMP1, 0);
2744                         codegen_addreference(BlockPtrOfPC(iptr->op1), mcodeptr);
2745                         break;
2746
2747                 /* (value xx 0) ? IFxx_ICONST : ELSE_ICONST                           */
2748
2749                 case ICMD_ELSE_ICONST:  /* handled by IFxx_ICONST                     */
2750                         break;
2751
2752                 case ICMD_IFEQ_ICONST:  /* ..., value ==> ..., constant               */
2753                                         /* val.i = constant                           */
2754
2755                         var_to_reg_int(s1, src, REG_ITMP1);
2756                         d = reg_of_var(iptr->dst, REG_ITMP3);
2757                         s3 = iptr->val.i;
2758                         if (iptr[1].opc == ICMD_ELSE_ICONST) {
2759                                 if ((s3 == 1) && (iptr[1].val.i == 0)) {
2760                                         M_CMPEQ(s1, REG_ZERO, d);
2761                                         store_reg_to_var_int(iptr->dst, d);
2762                                         break;
2763                                         }
2764                                 if ((s3 == 0) && (iptr[1].val.i == 1)) {
2765                                         M_CMPEQ(s1, REG_ZERO, d);
2766                                         M_XOR_IMM(d, 1, d);
2767                                         store_reg_to_var_int(iptr->dst, d);
2768                                         break;
2769                                         }
2770                                 if (s1 == d) {
2771                                         M_MOV(s1, REG_ITMP1);
2772                                         s1 = REG_ITMP1;
2773                                         }
2774                                 ICONST(d, iptr[1].val.i);
2775                                 }
2776                         if ((s3 >= 0) && (s3 <= 255)) {
2777                                 M_CMOVEQ_IMM(s1, s3, d);
2778                                 }
2779                         else {
2780                                 ICONST(REG_ITMP2, s3);
2781                                 M_CMOVEQ(s1, REG_ITMP2, d);
2782                                 }
2783                         store_reg_to_var_int(iptr->dst, d);
2784                         break;
2785
2786                 case ICMD_IFNE_ICONST:  /* ..., value ==> ..., constant               */
2787                                         /* val.i = constant                           */
2788
2789                         var_to_reg_int(s1, src, REG_ITMP1);
2790                         d = reg_of_var(iptr->dst, REG_ITMP3);
2791                         s3 = iptr->val.i;
2792                         if (iptr[1].opc == ICMD_ELSE_ICONST) {
2793                                 if ((s3 == 0) && (iptr[1].val.i == 1)) {
2794                                         M_CMPEQ(s1, REG_ZERO, d);
2795                                         store_reg_to_var_int(iptr->dst, d);
2796                                         break;
2797                                         }
2798                                 if ((s3 == 1) && (iptr[1].val.i == 0)) {
2799                                         M_CMPEQ(s1, REG_ZERO, d);
2800                                         M_XOR_IMM(d, 1, d);
2801                                         store_reg_to_var_int(iptr->dst, d);
2802                                         break;
2803                                         }
2804                                 if (s1 == d) {
2805                                         M_MOV(s1, REG_ITMP1);
2806                                         s1 = REG_ITMP1;
2807                                         }
2808                                 ICONST(d, iptr[1].val.i);
2809                                 }
2810                         if ((s3 >= 0) && (s3 <= 255)) {
2811                                 M_CMOVNE_IMM(s1, s3, d);
2812                                 }
2813                         else {
2814                                 ICONST(REG_ITMP2, s3);
2815                                 M_CMOVNE(s1, REG_ITMP2, d);
2816                                 }
2817                         store_reg_to_var_int(iptr->dst, d);
2818                         break;
2819
2820                 case ICMD_IFLT_ICONST:  /* ..., value ==> ..., constant               */
2821                                         /* val.i = constant                           */
2822
2823                         var_to_reg_int(s1, src, REG_ITMP1);
2824                         d = reg_of_var(iptr->dst, REG_ITMP3);
2825                         s3 = iptr->val.i;
2826                         if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
2827                                 if ((s3 == 1) && (iptr[1].val.i == 0)) {
2828                                         M_CMPLT(s1, REG_ZERO, d);
2829                                         store_reg_to_var_int(iptr->dst, d);
2830                                         break;
2831                                         }
2832                                 if ((s3 == 0) && (iptr[1].val.i == 1)) {
2833                                         M_CMPLE(REG_ZERO, s1, d);
2834                                         store_reg_to_var_int(iptr->dst, d);
2835                                         break;
2836                                         }
2837                                 if (s1 == d) {
2838                                         M_MOV(s1, REG_ITMP1);
2839                                         s1 = REG_ITMP1;
2840                                         }
2841                                 ICONST(d, iptr[1].val.i);
2842                                 }
2843                         if ((s3 >= 0) && (s3 <= 255)) {
2844                                 M_CMOVLT_IMM(s1, s3, d);
2845                                 }
2846                         else {
2847                                 ICONST(REG_ITMP2, s3);
2848                                 M_CMOVLT(s1, REG_ITMP2, d);
2849                                 }
2850                         store_reg_to_var_int(iptr->dst, d);
2851                         break;
2852
2853                 case ICMD_IFGE_ICONST:  /* ..., value ==> ..., constant               */
2854                                         /* val.i = constant                           */
2855
2856                         var_to_reg_int(s1, src, REG_ITMP1);
2857                         d = reg_of_var(iptr->dst, REG_ITMP3);
2858                         s3 = iptr->val.i;
2859                         if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
2860                                 if ((s3 == 1) && (iptr[1].val.i == 0)) {
2861                                         M_CMPLE(REG_ZERO, s1, d);
2862                                         store_reg_to_var_int(iptr->dst, d);
2863                                         break;
2864                                         }
2865                                 if ((s3 == 0) && (iptr[1].val.i == 1)) {
2866                                         M_CMPLT(s1, REG_ZERO, d);
2867                                         store_reg_to_var_int(iptr->dst, d);
2868                                         break;
2869                                         }
2870                                 if (s1 == d) {
2871                                         M_MOV(s1, REG_ITMP1);
2872                                         s1 = REG_ITMP1;
2873                                         }
2874                                 ICONST(d, iptr[1].val.i);
2875                                 }
2876                         if ((s3 >= 0) && (s3 <= 255)) {
2877                                 M_CMOVGE_IMM(s1, s3, d);
2878                                 }
2879                         else {
2880                                 ICONST(REG_ITMP2, s3);
2881                                 M_CMOVGE(s1, REG_ITMP2, d);
2882                                 }
2883                         store_reg_to_var_int(iptr->dst, d);
2884                         break;
2885
2886                 case ICMD_IFGT_ICONST:  /* ..., value ==> ..., constant               */
2887                                         /* val.i = constant                           */
2888
2889                         var_to_reg_int(s1, src, REG_ITMP1);
2890                         d = reg_of_var(iptr->dst, REG_ITMP3);
2891                         s3 = iptr->val.i;
2892                         if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
2893                                 if ((s3 == 1) && (iptr[1].val.i == 0)) {
2894                                         M_CMPLT(REG_ZERO, s1, d);
2895                                         store_reg_to_var_int(iptr->dst, d);
2896                                         break;
2897                                         }
2898                                 if ((s3 == 0) && (iptr[1].val.i == 1)) {
2899                                         M_CMPLE(s1, REG_ZERO, d);
2900                                         store_reg_to_var_int(iptr->dst, d);
2901                                         break;
2902                                         }
2903                                 if (s1 == d) {
2904                                         M_MOV(s1, REG_ITMP1);
2905                                         s1 = REG_ITMP1;
2906                                         }
2907                                 ICONST(d, iptr[1].val.i);
2908                                 }
2909                         if ((s3 >= 0) && (s3 <= 255)) {
2910                                 M_CMOVGT_IMM(s1, s3, d);
2911                                 }
2912                         else {
2913                                 ICONST(REG_ITMP2, s3);
2914                                 M_CMOVGT(s1, REG_ITMP2, d);
2915                                 }
2916                         store_reg_to_var_int(iptr->dst, d);
2917                         break;
2918
2919                 case ICMD_IFLE_ICONST:  /* ..., value ==> ..., constant               */
2920                                         /* val.i = constant                           */
2921
2922                         var_to_reg_int(s1, src, REG_ITMP1);
2923                         d = reg_of_var(iptr->dst, REG_ITMP3);
2924                         s3 = iptr->val.i;
2925                         if ((iptr[1].opc == ICMD_ELSE_ICONST)) {
2926                                 if ((s3 == 1) && (iptr[1].val.i == 0)) {
2927                                         M_CMPLE(s1, REG_ZERO, d);
2928                                         store_reg_to_var_int(iptr->dst, d);
2929                                         break;
2930                                         }
2931                                 if ((s3 == 0) && (iptr[1].val.i == 1)) {
2932                                         M_CMPLT(REG_ZERO, s1, d);
2933                                         store_reg_to_var_int(iptr->dst, d);
2934                                         break;
2935                                         }
2936                                 if (s1 == d) {
2937                                         M_MOV(s1, REG_ITMP1);
2938                                         s1 = REG_ITMP1;
2939                                         }
2940                                 ICONST(d, iptr[1].val.i);
2941                                 }
2942                         if ((s3 >= 0) && (s3 <= 255)) {
2943                                 M_CMOVLE_IMM(s1, s3, d);
2944                                 }
2945                         else {
2946                                 ICONST(REG_ITMP2, s3);
2947                                 M_CMOVLE(s1, REG_ITMP2, d);
2948                                 }
2949                         store_reg_to_var_int(iptr->dst, d);
2950                         break;
2951
2952
2953                 case ICMD_IRETURN:      /* ..., retvalue ==> ...                      */
2954                 case ICMD_LRETURN:
2955                 case ICMD_ARETURN:
2956
2957 #ifdef USE_THREADS
2958                         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
2959                                 a = dseg_addaddress ((void*) (builtin_monitorexit));
2960                                 M_ALD(REG_PV, REG_PV, a);
2961                                 M_ALD(argintregs[0], REG_SP, 8 * maxmemuse);
2962                                 M_JSR(REG_RA, REG_PV);
2963                                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
2964                                 }                       
2965 #endif
2966                         var_to_reg_int(s1, src, REG_RESULT);
2967                         M_INTMOVE(s1, REG_RESULT);
2968                         goto nowperformreturn;
2969
2970                 case ICMD_FRETURN:      /* ..., retvalue ==> ...                      */
2971                 case ICMD_DRETURN:
2972
2973 #ifdef USE_THREADS
2974                         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
2975                                 a = dseg_addaddress ((void*) (builtin_monitorexit));
2976                                 M_ALD(REG_PV, REG_PV, a);
2977                                 M_ALD(argintregs[0], REG_SP, 8 * maxmemuse);
2978                                 M_JSR(REG_RA, REG_PV);
2979                                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
2980                                 }                       
2981 #endif
2982                         var_to_reg_flt(s1, src, REG_FRESULT);
2983                         M_FLTMOVE(s1, REG_FRESULT);
2984                         goto nowperformreturn;
2985
2986                 case ICMD_RETURN:      /* ...  ==> ...                                */
2987
2988 #ifdef USE_THREADS
2989                         if (checksync && (method->flags & ACC_SYNCHRONIZED)) {
2990                                 a = dseg_addaddress ((void*) (builtin_monitorexit));
2991                                 M_ALD(REG_PV, REG_PV, a);
2992                                 M_ALD(argintregs[0], REG_SP, 8 * maxmemuse);
2993                                 M_JSR(REG_RA, REG_PV);
2994                                 M_LDA(REG_PV, REG_RA, -(int)((u1*) mcodeptr - mcodebase));
2995                                 }                       
2996 #endif
2997
2998 nowperformreturn:
2999                         {
3000                         int r, p;
3001                         
3002                         p = parentargs_base;
3003                         
3004                         /* restore return address                                         */
3005
3006                         if (!isleafmethod)
3007                                 {p--;  M_LLD (REG_RA, REG_SP, 8 * p);}
3008
3009                         /* restore saved registers                                        */
3010
3011                         for (r = savintregcnt - 1; r >= maxsavintreguse; r--)
3012                                         {p--; M_LLD(savintregs[r], REG_SP, 8 * p);}
3013                         for (r = savfltregcnt - 1; r >= maxsavfltreguse; r--)
3014                                         {p--; M_DLD(savfltregs[r], REG_SP, 8 * p);}
3015
3016                         /* deallocate stack                                               */
3017
3018                         if (parentargs_base)
3019                                 {M_LDA(REG_SP, REG_SP, parentargs_base*8);}
3020
3021                         /* call trace function */
3022
3023                         if (runverbose) {
3024                                 M_LDA (REG_SP, REG_SP, -24);
3025                                 M_AST(REG_RA, REG_SP, 0);
3026                                 M_LST(REG_RESULT, REG_SP, 8);
3027                                 M_DST(REG_FRESULT, REG_SP,16);
3028                                 a = dseg_addaddress (method);
3029                                 M_ALD(argintregs[0], REG_PV, a);
3030                                 M_MOV(REG_RESULT, argintregs[1]);
3031                                 M_FLTMOVE(REG_FRESULT, argfltregs[2]);
3032                                 M_FLTMOVE(REG_FRESULT, argfltregs[3]);
3033                                 a = dseg_addaddress ((void*) (builtin_displaymethodstop));
3034                                 M_ALD(REG_PV, REG_PV, a);
3035                                 M_JSR (REG_RA, REG_PV);
3036                                 s1 = (int)((u1*) mcodeptr - mcodebase);
3037                                 if (s1<=32768) M_LDA (REG_PV, REG_RA, -s1);
3038                                 else {
3039                                         s4 ml=-s1, mh=0;
3040                                         while (ml<-32768) { ml+=65536; mh--; }
3041                                         M_LDA (REG_PV, REG_RA, ml );
3042                                         M_LDAH (REG_PV, REG_PV, mh );
3043                                         }
3044                                 M_DLD(REG_FRESULT, REG_SP,16);
3045                                 M_LLD(REG_RESULT, REG_SP, 8);
3046                                 M_ALD(REG_RA, REG_SP, 0);
3047                                 M_LDA (REG_SP, REG_SP, 24);
3048                                 }
3049
3050                         M_RET(REG_ZERO, REG_RA);
3051                         ALIGNCODENOP;
3052                         }
3053                         break;
3054
3055
3056                 case ICMD_TABLESWITCH:  /* ..., index ==> ...                         */
3057                         {
3058                         s4 i, l, *s4ptr;
3059                         void **tptr;
3060
3061                         tptr = (void **) iptr->target;
3062
3063                         s4ptr = iptr->val.a;
3064                         l = s4ptr[1];                          /* low     */
3065                         i = s4ptr[2];                          /* high    */
3066                         
3067                         var_to_reg_int(s1, src, REG_ITMP1);
3068                         if (l == 0)
3069                                 {M_INTMOVE(s1, REG_ITMP1);}
3070                         else if (l <= 32768) {
3071                                 M_LDA(REG_ITMP1, s1, -l);
3072                                 }
3073                         else {
3074                                 ICONST(REG_ITMP2, l);
3075                                 M_ISUB(s1, REG_ITMP2, REG_ITMP1);
3076                                 }
3077                         i = i - l + 1;
3078
3079                         /* range check */
3080
3081                         if (i <= 256)
3082                                 M_CMPULE_IMM(REG_ITMP1, i - 1, REG_ITMP2);
3083                         else {
3084                                 M_LDA(REG_ITMP2, REG_ZERO, i - 1);
3085                                 M_CMPULE(REG_ITMP1, REG_ITMP2, REG_ITMP2);
3086                                 }
3087                         M_BEQZ(REG_ITMP2, 0);
3088
3089
3090                         /* codegen_addreference(BlockPtrOfPC(s4ptr[0]), mcodeptr); */
3091                         codegen_addreference((basicblock *) tptr[0], mcodeptr);
3092
3093                         /* build jump table top down and use address of lowest entry */
3094
3095                         /* s4ptr += 3 + i; */
3096                         tptr += i;
3097
3098                         while (--i >= 0) {
3099                                 /* dseg_addtarget(BlockPtrOfPC(*--s4ptr)); */
3100                                 dseg_addtarget((basicblock *) tptr[0]); 
3101                                 --tptr;
3102                                 }
3103                         }
3104
3105                         /* length of dataseg after last dseg_addtarget is used by load */
3106
3107                         M_SAADDQ(REG_ITMP1, REG_PV, REG_ITMP2);
3108                         M_ALD(REG_ITMP2, REG_ITMP2, -dseglen);
3109                         M_JMP(REG_ZERO, REG_ITMP2);
3110                         ALIGNCODENOP;
3111                         break;
3112
3113
3114                 case ICMD_LOOKUPSWITCH: /* ..., key ==> ...                           */
3115                         {
3116                         s4 i, l, val, *s4ptr;
3117                         void **tptr;
3118
3119                         tptr = (void **) iptr->target;
3120
3121                         s4ptr = iptr->val.a;
3122                         l = s4ptr[0];                          /* default  */
3123                         i = s4ptr[1];                          /* count    */
3124                         
3125                         MCODECHECK((i<<2)+8);
3126                         var_to_reg_int(s1, src, REG_ITMP1);
3127                         while (--i >= 0) {
3128                                 s4ptr += 2;
3129                                 ++tptr;
3130
3131                                 val = s4ptr[0];
3132                                 if ((val >= 0) && (val <= 255)) {
3133                                         M_CMPEQ_IMM(s1, val, REG_ITMP2);
3134                                         }
3135                                 else {
3136                                         if ((val >= -32768) && (val <= 32767)) {
3137                                                 M_LDA(REG_ITMP2, REG_ZERO, val);
3138                                                 } 
3139                                         else {
3140                                                 a = dseg_adds4 (val);
3141                                                 M_ILD(REG_ITMP2, REG_PV, a);
3142                                                 }
3143                                         M_CMPEQ(s1, REG_ITMP2, REG_ITMP2);
3144                                         }
3145                                 M_BNEZ(REG_ITMP2, 0);
3146                                 /* codegen_addreference(BlockPtrOfPC(s4ptr[1]), mcodeptr); */
3147                                 codegen_addreference((basicblock *) tptr[0], mcodeptr); 
3148                                 }
3149
3150                         M_BR(0);
3151                         /* codegen_addreference(BlockPtrOfPC(l), mcodeptr); */
3152                         
3153                         tptr = (void **) iptr->target;
3154                         codegen_addreference((basicblock *) tptr[0], mcodeptr);
3155
3156                         ALIGNCODENOP;
3157                         break;
3158                         }
3159
3160
3161                 case ICMD_BUILTIN3:     /* ..., arg1, arg2, arg3 ==> ...              */
3162                                         /* op1 = return type, val.a = function pointer*/
3163                         s3 = 3;
3164                         goto gen_method;
3165
3166                 case ICMD_BUILTIN2:     /* ..., arg1, arg2 ==> ...                    */
3167                                         /* op1 = return type, val.a = function pointer*/
3168                         s3 = 2;
3169                         goto gen_method;
3170
3171                 case ICMD_BUILTIN1:     /* ..., arg1 ==> ...                          */
3172                                         /* op1 = return type, val.a = function pointer*/
3173                         s3 = 1;
3174                         goto gen_method;
3175
3176                 case ICMD_INVOKESTATIC: /* ..., [arg1, [arg2 ...]] ==> ...            */
3177                                         /* op1 = arg count, val.a = method pointer    */
3178
3179                 case ICMD_INVOKESPECIAL:/* ..., objectref, [arg1, [arg2 ...]] ==> ... */
3180                                         /* op1 = arg count, val.a = method pointer    */
3181
3182                 case ICMD_INVOKEVIRTUAL:/* ..., objectref, [arg1, [arg2 ...]] ==> ... */
3183                                         /* op1 = arg count, val.a = method pointer    */
3184
3185                 case ICMD_INVOKEINTERFACE:/*.., objectref, [arg1, [arg2 ...]] ==> ... */
3186                                         /* op1 = arg count, val.a = method pointer    */
3187
3188                         s3 = iptr->op1;
3189
3190 gen_method: {
3191                         methodinfo   *m;
3192                         classinfo    *ci;
3193
3194                         MCODECHECK((s3 << 1) + 64);
3195
3196                         /* copy arguments to registers or stack location                  */
3197
3198                         for (; --s3 >= 0; src = src->prev) {
3199                                 if (src->varkind == ARGVAR)
3200                                         continue;
3201                                 if (IS_INT_LNG_TYPE(src->type)) {
3202                                         if (s3 < INT_ARG_CNT) {
3203                                                 s1 = argintregs[s3];
3204                                                 var_to_reg_int(d, src, s1);
3205                                                 M_INTMOVE(d, s1);
3206                                                 }
3207                                         else  {
3208                                                 var_to_reg_int(d, src, REG_ITMP1);
3209                                                 M_LST(d, REG_SP, 8 * (s3 - INT_ARG_CNT));
3210                                                 }
3211                                         }
3212                                 else
3213                                         if (s3 < FLT_ARG_CNT) {
3214                                                 s1 = argfltregs[s3];
3215                                                 var_to_reg_flt(d, src, s1);
3216                                                 M_FLTMOVE(d, s1);
3217                                                 }
3218                                         else {
3219                                                 var_to_reg_flt(d, src, REG_FTMP1);
3220                                                 M_DST(d, REG_SP, 8 * (s3 - FLT_ARG_CNT));
3221                                                 }
3222                                 } /* end of for */
3223
3224                         m = iptr->val.a;
3225                         switch (iptr->opc) {
3226                                 case ICMD_BUILTIN3:
3227                                 case ICMD_BUILTIN2:
3228                                 case ICMD_BUILTIN1:
3229                                         a = dseg_addaddress ((void*) (m));
3230
3231                                         M_ALD(REG_PV, REG_PV, a); /* Pointer to built-in-function */
3232                                         d = iptr->op1;
3233                                         goto makeactualcall;
3234
3235                                 case ICMD_INVOKESTATIC:
3236                                 case ICMD_INVOKESPECIAL:
3237                                         a = dseg_addaddress (m->stubroutine);
3238
3239                                         M_ALD(REG_PV, REG_PV, a );       /* method pointer in r27 */
3240
3241                                         d = m->returntype;
3242                                         goto makeactualcall;
3243
3244                                 case ICMD_INVOKEVIRTUAL:
3245
3246                                         gen_nullptr_check(argintregs[0]);
3247                                         M_ALD(REG_METHODPTR, argintregs[0],
3248                                                                  OFFSET(java_objectheader, vftbl));
3249                                         M_ALD(REG_PV, REG_METHODPTR, OFFSET(vftbl, table[0]) +
3250                                                                 sizeof(methodptr) * m->vftblindex);
3251
3252                                         d = m->returntype;
3253                                         goto makeactualcall;
3254
3255                                 case ICMD_INVOKEINTERFACE:
3256                                         ci = m->class;
3257                                         
3258                                         gen_nullptr_check(argintregs[0]);
3259                                         M_ALD(REG_METHODPTR, argintregs[0],
3260                                                                  OFFSET(java_objectheader, vftbl));    
3261                                         M_ALD(REG_METHODPTR, REG_METHODPTR,
3262                                               OFFSET(vftbl, interfacetable[0]) -
3263                                               sizeof(methodptr*) * ci->index);
3264                                         M_ALD(REG_PV, REG_METHODPTR,
3265                                                             sizeof(methodptr) * (m - ci->methods));
3266
3267                                         d = m->returntype;
3268                                         goto makeactualcall;
3269
3270                                 default:
3271                                         d = 0;
3272                                         sprintf (logtext, "Unkown ICMD-Command: %d", iptr->opc);
3273                                         error ();
3274                                 }
3275
3276 makeactualcall:
3277
3278                         M_JSR (REG_RA, REG_PV);
3279
3280                         /* recompute pv */
3281
3282                         s1 = (int)((u1*) mcodeptr - mcodebase);
3283                         if (s1<=32768) M_LDA (REG_PV, REG_RA, -s1);
3284                         else {
3285                                 s4 ml=-s1, mh=0;
3286                                 while (ml<-32768) { ml+=65536; mh--; }
3287                                 M_LDA (REG_PV, REG_RA, ml );
3288                                 M_LDAH (REG_PV, REG_PV, mh );
3289                                 }
3290
3291                         /* d contains return type */
3292
3293                         if (d != TYPE_VOID) {
3294                                 if (IS_INT_LNG_TYPE(iptr->dst->type)) {
3295                                         s1 = reg_of_var(iptr->dst, REG_RESULT);
3296                                         M_INTMOVE(REG_RESULT, s1);
3297                                         store_reg_to_var_int(iptr->dst, s1);
3298                                         }
3299                                 else {
3300                                         s1 = reg_of_var(iptr->dst, REG_FRESULT);
3301                                         M_FLTMOVE(REG_FRESULT, s1);
3302                                         store_reg_to_var_flt(iptr->dst, s1);
3303                                         }
3304                                 }
3305                         }
3306                         break;
3307
3308
3309                 case ICMD_INSTANCEOF: /* ..., objectref ==> ..., intresult            */
3310
3311                                       /* op1:   0 == array, 1 == class                */
3312                                       /* val.a: (classinfo*) superclass               */
3313
3314 /*          superclass is an interface:
3315  *
3316  *          return (sub != NULL) &&
3317  *                 (sub->vftbl->interfacetablelength > super->index) &&
3318  *                 (sub->vftbl->interfacetable[-super->index] != NULL);
3319  *
3320  *          superclass is a class:
3321  *
3322  *          return ((sub != NULL) && (0
3323  *                  <= (sub->vftbl->baseval - super->vftbl->baseval) <=
3324  *                  super->vftbl->diffvall));
3325  */
3326
3327                         {
3328                         classinfo *super = (classinfo*) iptr->val.a;
3329                         
3330                         var_to_reg_int(s1, src, REG_ITMP1);
3331                         d = reg_of_var(iptr->dst, REG_ITMP3);
3332                         if (s1 == d) {
3333                                 M_MOV(s1, REG_ITMP1);
3334                                 s1 = REG_ITMP1;
3335                                 }
3336                         M_CLR(d);
3337                         if (iptr->op1) {                               /* class/interface */
3338                                 if (super->flags & ACC_INTERFACE) {        /* interface       */
3339                                         M_BEQZ(s1, 6);
3340                                         M_ALD(REG_ITMP1, s1, OFFSET(java_objectheader, vftbl));
3341                                         M_ILD(REG_ITMP2, REG_ITMP1, OFFSET(vftbl, interfacetablelength));
3342                                         M_LDA(REG_ITMP2, REG_ITMP2, - super->index);
3343                                         M_BLEZ(REG_ITMP2, 2);
3344                                         M_ALD(REG_ITMP1, REG_ITMP1,
3345                                               OFFSET(vftbl, interfacetable[0]) -
3346                                               super->index * sizeof(methodptr*));
3347                                         M_CMPULT(REG_ZERO, REG_ITMP1, d);      /* REG_ITMP1 != 0  */
3348                                         }
3349                                 else {                                     /* class           */
3350 /*
3351                                         s2 = super->vftbl->diffval;
3352                                         M_BEQZ(s1, 4 + (s2 > 255));
3353                                         M_ALD(REG_ITMP1, s1, OFFSET(java_objectheader, vftbl));
3354                                         M_ILD(REG_ITMP1, REG_ITMP1, OFFSET(vftbl, baseval));
3355                                         M_LDA(REG_ITMP1, REG_ITMP1, - super->vftbl->baseval);
3356                                         if (s2 <= 255)
3357                                                 M_CMPULE_IMM(REG_ITMP1, s2, d);
3358                                         else {
3359                                                 M_LDA(REG_ITMP2, REG_ZERO, s2);
3360                                                 M_CMPULE(REG_ITMP1, REG_ITMP2, d);
3361                                                 }
3362 */
3363                                         M_BEQZ(s1, 7);
3364                                         M_ALD(REG_ITMP1, s1, OFFSET(java_objectheader, vftbl));
3365                                         a = dseg_addaddress ((void*) super->vftbl);
3366                                         M_ALD(REG_ITMP2, REG_PV, a);
3367                                         M_ILD(REG_ITMP1, REG_ITMP1, OFFSET(vftbl, baseval));
3368                                         M_ILD(REG_ITMP3, REG_ITMP2, OFFSET(vftbl, baseval));
3369                                         M_ILD(REG_ITMP2, REG_ITMP2, OFFSET(vftbl, diffval));
3370                                         M_ISUB(REG_ITMP1, REG_ITMP3, REG_ITMP1);
3371                                         M_CMPULE(REG_ITMP1, REG_ITMP2, d);
3372                                         }
3373                                 }
3374                         else
3375                                 panic ("internal error: no inlined array instanceof");
3376                         }
3377                         store_reg_to_var_int(iptr->dst, d);
3378                         break;
3379
3380                 case ICMD_CHECKCAST:  /* ..., objectref ==> ..., objectref            */
3381
3382                                       /* op1:   0 == array, 1 == class                */
3383                                       /* val.a: (classinfo*) superclass               */
3384
3385 /*          superclass is an interface:
3386  *
3387  *          OK if ((sub == NULL) ||
3388  *                 (sub->vftbl->interfacetablelength > super->index) &&
3389  *                 (sub->vftbl->interfacetable[-super->index] != NULL));
3390  *
3391  *          superclass is a class:
3392  *
3393  *          OK if ((sub == NULL) || (0
3394  *                 <= (sub->vftbl->baseval - super->vftbl->baseval) <=
3395  *                 super->vftbl->diffvall));
3396  */
3397
3398                         {
3399                         classinfo *super = (classinfo*) iptr->val.a;
3400                         
3401                         d = reg_of_var(iptr->dst, REG_ITMP3);
3402                         var_to_reg_int(s1, src, d);
3403                         if (iptr->op1) {                               /* class/interface */
3404                                 if (super->flags & ACC_INTERFACE) {        /* interface       */
3405                                         M_BEQZ(s1, 6);
3406                                         M_ALD(REG_ITMP1, s1, OFFSET(java_objectheader, vftbl));
3407                                         M_ILD(REG_ITMP2, REG_ITMP1, OFFSET(vftbl, interfacetablelength));
3408                                         M_LDA(REG_ITMP2, REG_ITMP2, - super->index);
3409                                         M_BLEZ(REG_ITMP2, 0);
3410                                         codegen_addxcastrefs(mcodeptr);
3411                                         M_ALD(REG_ITMP2, REG_ITMP1,
3412                                               OFFSET(vftbl, interfacetable[0]) -
3413                                               super->index * sizeof(methodptr*));
3414                                         M_BEQZ(REG_ITMP2, 0);
3415                                         codegen_addxcastrefs(mcodeptr);
3416                                         }
3417                                 else {                                     /* class           */
3418 /*
3419                                         s2 = super->vftbl->diffval;
3420                                         M_BEQZ(s1, 4 + (s2 != 0) + (s2 > 255));
3421                                         M_ALD(REG_ITMP1, s1, OFFSET(java_objectheader, vftbl));
3422                                         M_ILD(REG_ITMP1, REG_ITMP1, OFFSET(vftbl, baseval));
3423                                         M_LDA(REG_ITMP1, REG_ITMP1, - super->vftbl->baseval);
3424                                         if (s2 == 0) {
3425                                                 M_BNEZ(REG_ITMP1, 0);
3426                                                 }
3427                                         else if (s2 <= 255) {
3428                                                 M_CMPULE_IMM(REG_ITMP1, s2, REG_ITMP2);
3429                                                 M_BEQZ(REG_ITMP2, 0);
3430                                                 }
3431                                         else {
3432                                                 M_LDA(REG_ITMP2, REG_ZERO, s2);
3433                                                 M_CMPULE(REG_ITMP1, REG_ITMP2, REG_ITMP2);
3434                                                 M_BEQZ(REG_ITMP2, 0);
3435                                                 }
3436 */
3437                                         M_BEQZ(s1, 8 + (d == REG_ITMP3));
3438                                         M_ALD(REG_ITMP1, s1, OFFSET(java_objectheader, vftbl));
3439                                         a = dseg_addaddress ((void*) super->vftbl);
3440                                         M_ALD(REG_ITMP2, REG_PV, a);
3441                                         M_ILD(REG_ITMP1, REG_ITMP1, OFFSET(vftbl, baseval));
3442                                         if (d != REG_ITMP3) {
3443                                                 M_ILD(REG_ITMP3, REG_ITMP2, OFFSET(vftbl, baseval));
3444                                                 M_ILD(REG_ITMP2, REG_ITMP2, OFFSET(vftbl, diffval));
3445                                                 M_ISUB(REG_ITMP1, REG_ITMP3, REG_ITMP1);
3446                                                 }
3447                                         else {
3448                                                 M_ILD(REG_ITMP2, REG_ITMP2, OFFSET(vftbl, baseval));
3449                                                 M_ISUB(REG_ITMP1, REG_ITMP2, REG_ITMP1);
3450                                                 M_ALD(REG_ITMP2, REG_PV, a);
3451                                                 M_ILD(REG_ITMP2, REG_ITMP2, OFFSET(vftbl, diffval));
3452                                                 }
3453                                         M_CMPULE(REG_ITMP1, REG_ITMP2, REG_ITMP2);
3454                                         M_BEQZ(REG_ITMP2, 0);
3455                                         codegen_addxcastrefs(mcodeptr);
3456                                         }
3457                                 }
3458                         else
3459                                 panic ("internal error: no inlined array checkcast");
3460                         }
3461                         M_INTMOVE(s1, d);
3462                         store_reg_to_var_int(iptr->dst, d);
3463                         break;
3464
3465                 case ICMD_CHECKASIZE:  /* ..., size ==> ..., size                     */
3466
3467                         var_to_reg_int(s1, src, REG_ITMP1);
3468                         M_BLTZ(s1, 0);
3469                         codegen_addxcheckarefs(mcodeptr);
3470                         break;
3471
3472                 case ICMD_MULTIANEWARRAY:/* ..., cnt1, [cnt2, ...] ==> ..., arrayref  */
3473                                       /* op1 = dimension, val.a = array descriptor    */
3474
3475                         /* check for negative sizes and copy sizes to stack if necessary  */
3476
3477                         MCODECHECK((iptr->op1 << 1) + 64);
3478
3479                         for (s1 = iptr->op1; --s1 >= 0; src = src->prev) {
3480                                 var_to_reg_int(s2, src, REG_ITMP1);
3481                                 M_BLTZ(s2, 0);
3482                                 codegen_addxcheckarefs(mcodeptr);
3483
3484                                 /* copy sizes to stack (argument numbers >= INT_ARG_CNT)      */
3485
3486                                 if (src->varkind != ARGVAR) {
3487                                         M_LST(s2, REG_SP, 8 * (s1 + INT_ARG_CNT));
3488                                         }
3489                                 }
3490
3491                         /* a0 = dimension count */
3492
3493                         ICONST(argintregs[0], iptr->op1);
3494
3495                         /* a1 = arraydescriptor */
3496
3497                         a = dseg_addaddress(iptr->val.a);
3498                         M_ALD(argintregs[1], REG_PV, a);
3499
3500                         /* a2 = pointer to dimensions = stack pointer */
3501
3502                         M_INTMOVE(REG_SP, argintregs[2]);
3503
3504                         a = dseg_addaddress((void*) (builtin_nmultianewarray));
3505                         M_ALD(REG_PV, REG_PV, a);
3506                         M_JSR(REG_RA, REG_PV);
3507                         s1 = (int)((u1*) mcodeptr - mcodebase);
3508                         if (s1 <= 32768)
3509                                 M_LDA (REG_PV, REG_RA, -s1);
3510                         else {
3511                                 s4 ml = -s1, mh = 0;
3512                                 while (ml < -32768) {ml += 65536; mh--;}
3513                                 M_LDA(REG_PV, REG_RA, ml);
3514                                 M_LDAH(REG_PV, REG_PV, mh);
3515                             }
3516                         s1 = reg_of_var(iptr->dst, REG_RESULT);
3517                         M_INTMOVE(REG_RESULT, s1);
3518                         store_reg_to_var_int(iptr->dst, s1);
3519                         break;
3520
3521
3522                 default: sprintf (logtext, "Unknown pseudo command: %d", iptr->opc);
3523                          error();
3524         
3525    
3526
3527         } /* switch */
3528                 
3529         } /* for instruction */
3530                 
3531         /* copy values to interface registers */
3532
3533         src = bptr->outstack;
3534         len = bptr->outdepth;
3535         MCODECHECK(64+len);
3536         while (src) {
3537                 len--;
3538                 if ((src->varkind != STACKVAR)) {
3539                         s2 = src->type;
3540                         if (IS_FLT_DBL_TYPE(s2)) {
3541                                 var_to_reg_flt(s1, src, REG_FTMP1);
3542                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
3543                                         M_FLTMOVE(s1,interfaces[len][s2].regoff);
3544                                         }
3545                                 else {
3546                                         M_DST(s1, REG_SP, 8 * interfaces[len][s2].regoff);
3547                                         }
3548                                 }
3549                         else {
3550                                 var_to_reg_int(s1, src, REG_ITMP1);
3551                                 if (!(interfaces[len][s2].flags & INMEMORY)) {
3552                                         M_INTMOVE(s1,interfaces[len][s2].regoff);
3553                                         }
3554                                 else {
3555                                         M_LST(s1, REG_SP, 8 * interfaces[len][s2].regoff);
3556                                         }
3557                                 }
3558                         }
3559                 src = src->prev;
3560                 }
3561         } /* if (bptr -> flags >= BBREACHED) */
3562         } /* for basic block */
3563
3564         /* bptr -> mpc = (int)((u1*) mcodeptr - mcodebase); */
3565
3566         {
3567         /* generate bound check stubs */
3568
3569         s4 *xcodeptr = NULL;
3570         
3571         for (; xboundrefs != NULL; xboundrefs = xboundrefs->next) {
3572                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
3573                         gen_resolvebranch((u1*) mcodebase + xboundrefs->branchpos, 
3574                                 xboundrefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - 4);
3575                         continue;
3576                         }
3577
3578
3579                 gen_resolvebranch((u1*) mcodebase + xboundrefs->branchpos, 
3580                                   xboundrefs->branchpos, (u1*) mcodeptr - mcodebase);
3581
3582                 MCODECHECK(8);
3583
3584                 M_LDA(REG_ITMP2_XPC, REG_PV, xboundrefs->branchpos - 4);
3585
3586                 if (xcodeptr != NULL) {
3587                         M_BR((xcodeptr-mcodeptr)-1);
3588                         }
3589                 else {
3590                         xcodeptr = mcodeptr;
3591
3592                         a = dseg_addaddress(proto_java_lang_ArrayIndexOutOfBoundsException);
3593                         M_ALD(REG_ITMP1_XPTR, REG_PV, a);
3594
3595                         a = dseg_addaddress(asm_handle_exception);
3596                         M_ALD(REG_ITMP3, REG_PV, a);
3597
3598                         M_JMP(REG_ZERO, REG_ITMP3);
3599                         }
3600                 }
3601
3602         /* generate negative array size check stubs */
3603
3604         xcodeptr = NULL;
3605         
3606         for (; xcheckarefs != NULL; xcheckarefs = xcheckarefs->next) {
3607                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
3608                         gen_resolvebranch((u1*) mcodebase + xcheckarefs->branchpos, 
3609                                 xcheckarefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - 4);
3610                         continue;
3611                         }
3612
3613                 gen_resolvebranch((u1*) mcodebase + xcheckarefs->branchpos, 
3614                                   xcheckarefs->branchpos, (u1*) mcodeptr - mcodebase);
3615
3616                 MCODECHECK(8);
3617
3618                 M_LDA(REG_ITMP2_XPC, REG_PV, xcheckarefs->branchpos - 4);
3619
3620                 if (xcodeptr != NULL) {
3621                         M_BR((xcodeptr-mcodeptr)-1);
3622                         }
3623                 else {
3624                         xcodeptr = mcodeptr;
3625
3626                         a = dseg_addaddress(proto_java_lang_NegativeArraySizeException);
3627                         M_ALD(REG_ITMP1_XPTR, REG_PV, a);
3628
3629                         a = dseg_addaddress(asm_handle_exception);
3630                         M_ALD(REG_ITMP3, REG_PV, a);
3631
3632                         M_JMP(REG_ZERO, REG_ITMP3);
3633                         }
3634                 }
3635
3636         /* generate cast check stubs */
3637
3638         xcodeptr = NULL;
3639         
3640         for (; xcastrefs != NULL; xcastrefs = xcastrefs->next) {
3641                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
3642                         gen_resolvebranch((u1*) mcodebase + xcastrefs->branchpos, 
3643                                 xcastrefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - 4);
3644                         continue;
3645                         }
3646
3647                 gen_resolvebranch((u1*) mcodebase + xcastrefs->branchpos, 
3648                                   xcastrefs->branchpos, (u1*) mcodeptr - mcodebase);
3649
3650                 MCODECHECK(8);
3651
3652                 M_LDA(REG_ITMP2_XPC, REG_PV, xcastrefs->branchpos - 4);
3653
3654                 if (xcodeptr != NULL) {
3655                         M_BR((xcodeptr-mcodeptr)-1);
3656                         }
3657                 else {
3658                         xcodeptr = mcodeptr;
3659
3660                         a = dseg_addaddress(proto_java_lang_ClassCastException);
3661                         M_ALD(REG_ITMP1_XPTR, REG_PV, a);
3662
3663                         a = dseg_addaddress(asm_handle_exception);
3664                         M_ALD(REG_ITMP3, REG_PV, a);
3665
3666                         M_JMP(REG_ZERO, REG_ITMP3);
3667                         }
3668                 }
3669
3670
3671 #ifdef SOFTNULLPTRCHECK
3672
3673         /* generate null pointer check stubs */
3674
3675         xcodeptr = NULL;
3676
3677         for (; xnullrefs != NULL; xnullrefs = xnullrefs->next) {
3678                 if ((exceptiontablelength == 0) && (xcodeptr != NULL)) {
3679                         gen_resolvebranch((u1*) mcodebase + xnullrefs->branchpos, 
3680                                 xnullrefs->branchpos, (u1*) xcodeptr - (u1*) mcodebase - 4);
3681                         continue;
3682                         }
3683
3684                 gen_resolvebranch((u1*) mcodebase + xnullrefs->branchpos, 
3685                                   xnullrefs->branchpos, (u1*) mcodeptr - mcodebase);
3686
3687                 MCODECHECK(8);
3688
3689                 M_LDA(REG_ITMP2_XPC, REG_PV, xnullrefs->branchpos - 4);
3690
3691                 if (xcodeptr != NULL) {
3692                         M_BR((xcodeptr-mcodeptr)-1);
3693                         }
3694                 else {
3695                         xcodeptr = mcodeptr;
3696
3697                         a = dseg_addaddress(proto_java_lang_NullPointerException);
3698                         M_ALD(REG_ITMP1_XPTR, REG_PV, a);
3699
3700                         a = dseg_addaddress(asm_handle_exception);
3701                         M_ALD(REG_ITMP3, REG_PV, a);
3702
3703                         M_JMP(REG_ZERO, REG_ITMP3);
3704                         }
3705                 }
3706
3707 #endif
3708         }
3709
3710         codegen_finish((int)((u1*) mcodeptr - mcodebase));
3711 }
3712
3713
3714 /* redefinition of code generation macros (compiling into array) **************/
3715
3716 /* 
3717 These macros are newly defined to allow code generation into an array.
3718 This is necessary, because the original M_.. macros generate code by
3719 calling 'codegen_adds4' that uses an additional data structure to
3720 receive the code.
3721
3722 For a faster (but less flexible) version to generate code, these
3723 macros directly use the (s4* p) - pointer to put the code directly
3724 in a locally defined array.
3725 This makes sense only for the stub-generation-routines below.
3726 */
3727
3728 #undef M_OP3
3729 #define M_OP3(op,fu,a,b,c,const) \
3730         *(p++) = ( (((s4)(op))<<26)|((a)<<21)|((b)<<(16-3*(const)))| \
3731         ((const)<<12)|((fu)<<5)|((c)) )
3732 #undef M_FOP3
3733 #define M_FOP3(op,fu,a,b,c) \
3734         *(p++) = ( (((s4)(op))<<26)|((a)<<21)|((b)<<16)|((fu)<<5)|(c) )
3735 #undef M_BRA
3736 #define M_BRA(op,a,disp) \
3737         *(p++) = ( (((s4)(op))<<26)|((a)<<21)|((disp)&0x1fffff) )
3738 #undef M_MEM
3739 #define M_MEM(op,a,b,disp) \
3740         *(p++) = ( (((s4)(op))<<26)|((a)<<21)|((b)<<16)|((disp)&0xffff) )
3741
3742
3743 /* function createcompilerstub *************************************************
3744
3745         creates a stub routine which calls the compiler
3746         
3747 *******************************************************************************/
3748
3749 #define COMPSTUBSIZE 3
3750
3751 u1 *createcompilerstub (methodinfo *m)
3752 {
3753         u8 *s = CNEW (u8, COMPSTUBSIZE);    /* memory to hold the stub            */
3754         s4 *p = (s4*) s;                    /* code generation pointer            */
3755         
3756                                             /* code for the stub                  */
3757         M_ALD (REG_PV, REG_PV, 16);         /* load pointer to the compiler       */
3758         M_JMP (0, REG_PV);                  /* jump to the compiler, return address
3759                                                in reg 0 is used as method pointer */
3760         s[1] = (u8) m;                      /* literals to be adressed            */  
3761         s[2] = (u8) asm_call_jit_compiler;  /* jump directly via PV from above    */
3762
3763 #ifdef STATISTICS
3764         count_cstub_len += COMPSTUBSIZE * 8;
3765 #endif
3766
3767         return (u1*) s;
3768 }
3769
3770
3771 /* function removecompilerstub *************************************************
3772
3773      deletes a compilerstub from memory  (simply by freeing it)
3774
3775 *******************************************************************************/
3776
3777 void removecompilerstub (u1 *stub) 
3778 {
3779         CFREE (stub, COMPSTUBSIZE * 8);
3780 }
3781
3782 /* function: createnativestub **************************************************
3783
3784         creates a stub routine which calls a native method
3785
3786 *******************************************************************************/
3787
3788 #define NATIVESTUBSIZE 34
3789 #define NATIVESTUBOFFSET 8
3790
3791 int runverbosenat = 0;
3792
3793 u1 *createnativestub (functionptr f, methodinfo *m)
3794 {
3795         int disp;
3796         u8 *s = CNEW (u8, NATIVESTUBSIZE);  /* memory to hold the stub            */
3797         u8 *cs = s + NATIVESTUBOFFSET;
3798         s4 *p = (s4*) (cs);                 /* code generation pointer            */
3799
3800         *(cs-1) = (u8) f;                   /* address of native method           */
3801         *(cs-2) = (u8) (&exceptionptr);     /* address of exceptionptr            */
3802         *(cs-3) = (u8) asm_handle_nat_exception; /* addr of asm exception handler */
3803         *(cs-4) = (u8) (&env);              /* addr of jni_environement           */
3804         *(cs-5) = (u8) asm_builtin_trace;
3805         *(cs-6) = (u8) m;
3806         *(cs-7) = (u8) asm_builtin_exittrace;
3807         *(cs-8) = (u8) builtin_trace_exception;
3808
3809 #if 0
3810         printf("stub: ");
3811         utf_display(m->class->name);
3812         printf(".");
3813         utf_display(m->name);
3814         printf(" 0x%p\n", cs);
3815 #endif
3816
3817         M_LDA  (REG_SP, REG_SP, -8);        /* build up stackframe                */
3818         M_AST  (REG_RA, REG_SP, 0);         /* store return address               */
3819
3820 #if 1
3821         if (runverbosenat) {
3822                 M_ALD(REG_ITMP1, REG_PV, -6*8);
3823                 M_ALD(REG_PV, REG_PV, -5*8);
3824
3825                 M_JSR(REG_RA, REG_PV);
3826                 disp = -(int) (p - (s4*) cs)*4;
3827                 M_LDA(REG_PV, REG_RA, disp);
3828         }
3829 #endif
3830
3831         reg_init();
3832
3833         M_MOV  (argintregs[4],argintregs[5]); 
3834         M_FMOV (argfltregs[4],argfltregs[5]);
3835
3836         M_MOV  (argintregs[3],argintregs[4]);
3837         M_FMOV (argfltregs[3],argfltregs[4]);
3838
3839         M_MOV  (argintregs[2],argintregs[3]);
3840         M_FMOV (argfltregs[2],argfltregs[3]);
3841
3842         M_MOV  (argintregs[1],argintregs[2]);
3843         M_FMOV (argfltregs[1],argfltregs[2]);
3844
3845         M_MOV  (argintregs[0],argintregs[1]);
3846         M_FMOV (argfltregs[0],argfltregs[1]);
3847         
3848         M_ALD  (argintregs[0], REG_PV, -4*8);/* load adress of jni_environement   */
3849
3850         M_ALD  (REG_PV, REG_PV, -1*8);      /* load adress of native method       */
3851         M_JSR  (REG_RA, REG_PV);            /* call native method                 */
3852
3853         disp = -(int) (p - (s4*) cs)*4;
3854         M_LDA  (REG_PV, REG_RA, disp);      /* recompute pv from ra               */
3855         M_ALD  (REG_ITMP3, REG_PV, -2*8);   /* get address of exceptionptr        */
3856
3857         M_ALD  (REG_ITMP1, REG_ITMP3, 0);   /* load exception into reg. itmp1     */
3858         M_BNEZ (REG_ITMP1,
3859                         3 + (runverbosenat ? 6 : 0));  /* if no exception then return        */
3860
3861 #if 1
3862         if (runverbosenat) {
3863                 M_ALD(argintregs[0], REG_PV, -6*8);
3864                 M_MOV(REG_RESULT, argintregs[1]);
3865                 M_FMOV(REG_FRESULT, argfltregs[2]);
3866                 M_FMOV(REG_FRESULT, argfltregs[3]);
3867                 M_ALD(REG_PV, REG_PV, -7*8);
3868                 M_JSR(REG_RA, REG_PV);
3869         }
3870 #endif
3871
3872         M_ALD  (REG_RA, REG_SP, 0);         /* load return address                */
3873         M_LDA  (REG_SP, REG_SP, 8);         /* remove stackframe                  */
3874
3875         M_RET  (REG_ZERO, REG_RA);          /* return to caller                   */
3876         
3877         M_AST  (REG_ZERO, REG_ITMP3, 0);    /* store NULL into exceptionptr       */
3878
3879 #if 1
3880         if (runverbosenat) {
3881                 M_LDA(REG_SP, REG_SP, -8);
3882                 M_AST(REG_ITMP1, REG_SP, 0);
3883                 M_MOV(REG_ITMP1, argintregs[0]);
3884                 M_ALD(argintregs[1], REG_PV, -6*8);
3885                 M_ALD(argintregs[2], REG_SP, 0);
3886                 M_CLR(argintregs[3]);
3887                 M_ALD(REG_PV, REG_PV, -8*8);
3888                 M_JSR(REG_RA, REG_PV);
3889                 disp = -(int) (p - (s4*) cs)*4;
3890                 M_LDA  (REG_PV, REG_RA, disp);
3891                 M_ALD(REG_ITMP1, REG_SP, 0);
3892                 M_LDA(REG_SP, REG_SP, 8);
3893         }
3894 #endif
3895
3896         M_ALD  (REG_RA, REG_SP, 0);         /* load return address                */
3897         M_LDA  (REG_SP, REG_SP, 8);         /* remove stackframe                  */
3898
3899         M_LDA  (REG_ITMP2, REG_RA, -4);     /* move fault address into reg. itmp2 */
3900
3901         M_ALD  (REG_ITMP3, REG_PV, -3*8);   /* load asm exception handler address */
3902         M_JMP  (REG_ZERO, REG_ITMP3);       /* jump to asm exception handler      */
3903         
3904 #if 0
3905         {
3906                 static int stubprinted;
3907                 if (!stubprinted)
3908                         printf("stubsize: %d/2\n", (int) (p - (s4*) s));
3909                 stubprinted = 1;
3910         }
3911 #endif
3912
3913 #ifdef STATISTICS
3914         count_nstub_len += NATIVESTUBSIZE * 8;
3915 #endif
3916
3917         return (u1*) (s + NATIVESTUBOFFSET);
3918 }
3919
3920 /* function: removenativestub **************************************************
3921
3922     removes a previously created native-stub from memory
3923     
3924 *******************************************************************************/
3925
3926 void removenativestub (u1 *stub)
3927 {
3928         CFREE ((u8*) stub - NATIVESTUBOFFSET, NATIVESTUBSIZE * 8);
3929 }
3930
3931
3932 /*
3933  * These are local overrides for various environment variables in Emacs.
3934  * Please do not remove this and leave it at the end of the file, where
3935  * Emacs will automagically detect them.
3936  * ---------------------------------------------------------------------
3937  * Local variables:
3938  * mode: c
3939  * indent-tabs-mode: t
3940  * c-basic-offset: 4
3941  * tab-width: 4
3942  * End:
3943  */