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