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