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