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