Merged revisions 7642-7664 via svnmerge from
[cacao.git] / src / vm / jit / alpha / asmpart.S
index ae01eff6d565620cbeeb284f2ae51393b59c3450..25ceb1da460d34c07988017cc1f80f030117149d 100644 (file)
@@ -1,6 +1,6 @@
 /* src/vm/jit/alpha/asmpart.S - Java-C interface functions for alpha
 
-   Copyright (C) 1996-2005, 2006 R. Grafl, A. Krall, C. Kruegel,
+   Copyright (C) 1996-2005, 2006, 2007 R. Grafl, A. Krall, C. Kruegel,
    C. Oates, R. Obermaisser, M. Platter, M. Probst, S. Ring,
    E. Steiner, C. Thalinger, D. Thuernbeck, P. Tomsich, C. Ullrich,
    J. Wenninger, Institut f. Computersprachen - TU Wien
    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
    02110-1301, USA.
 
-   Contact: cacao@cacaojvm.org
-
-   Authors: Andreas Krall
-            Reinhard Grafl
-
-   Changes: Joseph Wenninger
-            Christian Thalinger
-
-   $Id: asmpart.S 4555 2006-03-04 18:35:31Z twisti $
+   $Id: asmpart.S 7661 2007-04-03 22:29:59Z twisti $
 
 */
 
@@ -41,7 +33,7 @@
 #include "vm/jit/alpha/md-asm.h"
 #include "vm/jit/alpha/offsets.h"
 
-#include "vm/jit/abi.h"
+#include "vm/jit/abi-asm.h"
 #include "vm/jit/methodheader.h"
 
 
        .set    noreorder
 
 
-/********************* exported functions and variables ***********************/
-
-       .globl asm_md_init
-
-       .globl asm_sync_instruction_cache
-
-       .globl asm_calljavafunction
-       .globl asm_calljavafunction_int
+/* export functions ***********************************************************/
 
-       .globl asm_calljavafunction2
-       .globl asm_calljavafunction2int
-       .globl asm_calljavafunction2long
-       .globl asm_calljavafunction2float
-       .globl asm_calljavafunction2double
+       .globl asm_vm_call_method
+       .globl asm_vm_call_method_int
+       .globl asm_vm_call_method_long
+       .globl asm_vm_call_method_float
+       .globl asm_vm_call_method_double
+       .globl asm_vm_call_method_exception_handler
+       .globl asm_vm_call_method_end
 
        .globl asm_call_jit_compiler
+
        .globl asm_handle_exception
        .globl asm_handle_nat_exception
 
-       .globl asm_wrapper_patcher
-
-       .globl asm_perform_threadswitch
-       .globl asm_initialize_thread_stack
-       .globl asm_switchstackandcall
-       .globl asm_criticalsections
-       .globl asm_getclassvalues_atomic
-
-
-/* asm_sync_instruction_cache **************************************************
-
-   XXX
-
-*******************************************************************************/
-
-       .ent    asm_sync_instruction_cache
-
-asm_sync_instruction_cache:
-       call_pal PAL_imb              /* synchronize instruction cache            */
-       jmp     zero,(ra)
-
-       .end    asm_sync_instruction_cache
-
-
-/* asm_md_init *****************************************************************
-
-   Initialize machine dependent stuff.
+       .globl asm_abstractmethoderror
 
-   Determines if the byte support instruction set (21164a and higher)
-   is available.
+       .globl asm_patcher_wrapper
 
-*******************************************************************************/
-
-       .ent    asm_md_init
+#if defined(ENABLE_REPLACEMENT)
+       .globl asm_replacement_out
+       .globl asm_replacement_in
+#endif
 
-asm_md_init:
+       .globl asm_compare_and_swap
+       .globl asm_memory_barrier
 
-       .long   0x47e03c20                  /* amask   1,v0                       */
-       jmp     zero,(ra)                   /* return                             */
+       .globl asm_criticalsections
+       .globl asm_getclassvalues_atomic
 
-       .end    asm_md_init
+       .globl asm_md_init
+       .globl asm_cacheflush
 
 
-/********************* function asm_calljavafunction ***************************
+/* asm_vm_call_method **********************************************************
 *                                                                              *
 *   This function calls a Java-method (which possibly needs compilation)       *
 *   with up to 4 address parameters.                                           *
@@ -126,75 +90,14 @@ asm_md_init:
 *                                                                              *
 *******************************************************************************/
 
-       .ent    asm_calljavafunction
-
-       .align  2
-
-       .quad   0                           /* catch type all                     */
-       .quad   calljava_xhandler           /* handler pc                         */
-       .quad   calljava_xhandler           /* end pc                             */
-       .quad   asm_calljavafunction        /* start pc                           */
-       .long   1                           /* extable size                       */
-       .long   0                           /* ALIGNMENT PADDING                  */
-       .quad   0                           /* line number table start            */
-       .quad   0                           /* line number table size             */
-       .long   0                           /* ALIGNMENT PADDING                  */
-       .long   0                           /* fltsave                            */
-       .long   0                           /* intsave                            */
-       .long   0                           /* isleaf                             */
-       .long   0                           /* IsSync                             */
-       .long   0                           /* frame size                         */
-       .quad   0                           /* method pointer (pointer to name)   */
-
-asm_calljavafunction:
-asm_calljavafunction_int:
-       ldgp    gp,0(pv)
-       lda     sp,-4*8(sp)                 /* allocate stack space               */
-       stq     ra,0*8(sp)                  /* save return address                */
-       stq     gp,1*8(sp)                  /* save global pointer                */
-
-       mov     a0,itmp1                    /* pass method pointer via tmp1       */
-
-       mov     a1,a0                       /* pass the remaining parameters      */
-       mov     a2,a1
-       mov     a3,a2
-       mov     a4,a3
-
-       lda     mptr,asm_call_jit_compiler  /* fake virtual function call         */
-       stq     mptr,3*8(sp)                /* store function address             */
-       mov     sp,mptr                     /* set method pointer                 */
-
-       ldq     pv,3*8(mptr)                /* method call as in Java             */
-       jmp     ra,(pv)                     /* call JIT compiler                  */
-calljava_jit:
-       lda     pv,(asm_calljavafunction - calljava_jit)(ra)
-
-L_asm_calljavafunction_return:
-       ldq     ra,0*8(sp)                  /* restore return address             */
-       ldq     gp,1*8(sp)                  /* restore global pointer             */
-       lda     sp,4*8(sp)                  /* free stack space                   */
-       jmp     zero,(ra)
-
-calljava_xhandler:
-       ldq     gp,1*8(sp)                  /* restore global pointer             */
-       mov     xptr,a0
-       jsr     ra,builtin_throw_exception
-       mov     zero,v0                     /* return NULL                        */
-       br      L_asm_calljavafunction_return
-
-       .end    asm_calljavafunction
-
-
-
-
-       .ent    asm_calljavafunction2
+       .ent    asm_vm_call_method
 
        .align  3
 
        .quad   0                           /* catch type all                     */
-       .quad   calljava_xhandler2          /* handler pc                         */
-       .quad   calljava_xhandler2          /* end pc                             */
-       .quad   asm_calljavafunction2       /* start pc                           */
+       .quad   0                           /* handler pc                         */
+       .quad   0                           /* end pc                             */
+       .quad   0                           /* start pc                           */
        .long   1                           /* extable size                       */
        .long   0                           /* ALIGNMENT PADDING                  */
        .quad   0                           /* line number table start            */
@@ -205,13 +108,13 @@ calljava_xhandler:
        .long   0                           /* isleaf                             */
        .long   0                           /* IsSync                             */
        .long   0                           /* frame size                         */
-       .quad   0                           /* method pointer (pointer to name)   */
+       .quad   0                           /* codeinfo pointer                   */
 
-asm_calljavafunction2:
-asm_calljavafunction2int:
-asm_calljavafunction2long:
-asm_calljavafunction2float:
-asm_calljavafunction2double:
+asm_vm_call_method:
+asm_vm_call_method_int:
+asm_vm_call_method_long:
+asm_vm_call_method_float:
+asm_vm_call_method_double:
        ldgp    gp,0(pv)
        lda     sp,-5*8(sp)               /* allocate stack space                 */
        stq     ra,0*8(sp)                /* save return address                  */
@@ -277,7 +180,7 @@ calljava_nocopy:
        ldq     pv,1*8(mptr)              /* method call as in Java               */
        jmp     ra,(pv)                   /* call JIT compiler                    */
 calljava_jit2:
-       lda     pv,(asm_calljavafunction2 - calljava_jit2)(ra)
+       lda     pv,(asm_vm_call_method - calljava_jit2)(ra)
 
        s8addq  s6,sp,sp
 calljava_return2:
@@ -289,7 +192,7 @@ calljava_return2:
 calljava_ret2:
        jmp     zero,(ra)
 
-calljava_xhandler2:
+asm_vm_call_method_exception_handler:
        s8addq  s6,sp,sp
        ldq     gp,1*8(sp)                /* restore global pointer               */
        mov     itmp1,a0
@@ -297,98 +200,55 @@ calljava_xhandler2:
        ldq     ra,0*8(sp)                /* restore return address               */
        ldq     s6,3*8(sp)
        lda     sp,5*8(sp)                /* free stack space                     */
-       mov     zero,v0                   /* return NULL                          */
+asm_vm_call_method_end:                                        
        jmp     zero,(ra)
 
-       .end    asm_calljavafunction2
+       .end    asm_vm_call_method
 
 
-/****************** function asm_call_jit_compiler *****************************
-*                                                                              *
-*   invokes the compiler for untranslated JavaVM methods.                      *
-*                                                                              *
-*   Register R0 contains a pointer to the method info structure (prepared      *
-*   by createcompilerstub). Using the return address in R26 and the            *
-*   offset in the LDA instruction or using the value in methodptr R28 the      *
-*   patching address for storing the method address can be computed:           *
-*                                                                              *
-*   method address was either loaded using                                     *
-*   M_LDQ (REG_PV, REG_PV, a)        ; invokestatic/special    ($27)           *
-*   M_LDA (REG_PV, REG_RA, low)                                                *
-*   M_LDAH(REG_PV, REG_RA, high)     ; optional                                *
-*   or                                                                         *
-*   M_LDQ (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($28)           *
-*   in the static case the method pointer can be computed using the            *
-*   return address and the lda function following the jmp instruction          *
-*                                                                              *
+/* asm_call_jit_compiler *******************************************************
+
+   Invokes the compiler for untranslated Java methods.
+
 *******************************************************************************/
 
        .ent    asm_call_jit_compiler
 
 asm_call_jit_compiler:
        ldgp    gp,0(pv)
-       lda     sp,-(15*8+sizestackframeinfo)(sp) /* reserve stack space          */
+       lda     sp,-(ARG_CNT+2)*8(sp) /* +2: keep stack 16-byte aligned           */
 
-       SAVE_ARGUMENT_REGISTERS(0)    /* save 6 int/6 float argument registers    */
+       stq     ra,0*8(sp)            /* save return address                      */
 
-       stq     mptr,12*8(sp)         /* save method pointer                      */
-       stq     ra,13*8(sp)           /* save return address                      */
-       stq     itmp1,14*8(sp)        /* save methodinfo pointer                  */
+       SAVE_ARGUMENT_REGISTERS(1)    /* save 6 int/6 float argument registers    */
 
-       lda     a0,15*8(sp)           /* create stackframe info                   */
-       mov     zero,a1               /* we don't have pv handy                   */
-       lda     a2,15*8+sizestackframeinfo(sp) /* pass java sp                    */
-       mov     ra,a3                 /* pass Java ra                             */
-       mov     a3,a4                 /* xpc is equal to ra                       */
-       jsr     ra,stacktrace_create_extern_stackframeinfo
-       ldgp    gp,0(ra)
+       mov     itmp1,a0              /* pass methodinfo pointer                  */
+       mov     mptr,a1               /* pass method pointer                      */
+       lda     a2,(ARG_CNT+2)*8(sp)  /* pass java sp                             */
+       mov     ra,a3
+       jsr     ra,jit_asm_compile    /* call jit compiler                        */
+       mov     v0,pv
 
-       ldq     a0,14*8(sp)           /* pass methodinfo pointer                  */
-       jsr     ra,jit_compile        /* call jit compiler                        */
-       ldgp    gp,0(ra)
-       stq     v0,14*8(sp)           /* save return value                        */
+       ldq     ra,0*8(sp)            /* load return address                      */
 
-       ldq     a0,13*8(sp)           /* pass return address                      */
-       lda     a1,15*8(sp)           /* pass stackframeinfo (for PV)             */
-       ldq     a2,12*8(sp)           /* pass method pointer                      */
-       jsr     ra,md_assembler_get_patch_address /* get address of patch position*/
-       ldgp    gp,0(ra)
-       stq     v0,12*8(sp)           /* store patch address for later use        */
+       RESTORE_ARGUMENT_REGISTERS(1) /* restore 6 int/6 float argument registers */
 
-       lda     a0,15*8(sp)           /* remove stackframe info                   */
-       jsr     ra,stacktrace_remove_stackframeinfo
-       ldgp    gp,0(ra)
-
-       RESTORE_ARGUMENT_REGISTERS(0) /* restore 6 int/6 float argument registers */
-
-       ldq     t0,12*8(sp)           /* load patch address                       */
-       ldq     ra,13*8(sp)           /* load return address                      */
-       ldq     pv,14*8(sp)           /* restore method entry point               */
-       lda     sp,15*8+sizestackframeinfo(sp) /* deallocate stack area           */
+       lda     sp,(ARG_CNT+2)*8(sp)  /* remove stack frame                       */
 
        beq     pv,L_asm_call_jit_compiler_exception
 
-       stq     pv,0(t0)              /* patch method entry point                 */
-
-       call_pal PAL_imb              /* synchronise instruction cache            */
-
        jmp     zero,(pv)             /* and call method, the method returns      */
                                      /* directly to the caller (ra).             */
 
 L_asm_call_jit_compiler_exception:
-#if defined(USE_THREADS) && defined(NATIVE_THREADS)
-       subq    sp,1*8,sp
+       subq    sp,2*8,sp
        stq     ra,0*8(sp)            /* save return address (xpc)                */
-       jsr     ra,builtin_asm_get_exceptionptrptr
-       ldq     ra,0*8(sp)           /* restore return address (xpc)             */
-       addq    sp,1*8,sp
-#else
-       lda     v0,_exceptionptr
-#endif
-       ldq     xptr,0(v0)            /* get the exception pointer                */
-       stq     zero,0(v0)            /* clear the exception pointer              */
+       jsr     ra,exceptions_get_and_clear_exception
+       ldq     ra,0*8(sp)            /* restore return address (xpc)             */
+       addq    sp,2*8,sp
 
-       subq    ra,4,xpc
+       mov     v0,xptr               /* get exception                            */
+       subq    ra,4,xpc              /* exception address is ra - 4              */
        br      L_asm_handle_nat_exception
 
        .end    asm_call_jit_compiler
@@ -410,18 +270,28 @@ L_asm_call_jit_compiler_exception:
 
 asm_handle_nat_exception:
 L_asm_handle_nat_exception:       /* required for PIC code                    */
-       ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
-       sll     t0,48,t0
-       sra     t0,48,t0              /* isolate offset                           */
-       addq    t0,ra,pv              /* compute update address                   */
-       ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
-       srl     t0,16,t0              /* isolate instruction code                 */
-       lda     t0,-0x177b(t0)        /* test for LDAH                            */
-       bne     t0,L_asm_handle_exception
-       ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
-       sll     t0,16,t0              /* compute high offset                      */
-       addl    t0,0,t0               /* sign extend high offset                  */
-       addq    t0,pv,pv              /* compute update address                   */
+L_asm_handle_exception_stack_loop:
+       lda     sp,-6*8(sp)                 /* keep stack 16-byte aligned         */
+       stq     xptr,0*8(sp)                /* save xptr                          */
+       stq     xpc,1*8(sp)                 /* save xpc                           */
+       stq     ra,3*8(sp)                  /* save RA                            */
+       stq     zero,4*8(sp)                /* save maybe-leaf flag (cleared)     */
+
+       mov     ra,a0                       /* pass RA                            */
+
+       br      ra,L_asm_handle_exception_load_gp
+L_asm_handle_exception_load_gp:
+       ldgp    gp,0(ra)                    /* load gp                            */
+
+       jsr     ra,md_codegen_get_pv_from_pc/* get PV from RA                     */
+       stq     v0,2*8(sp)                  /* save PV                            */
+
+       ldq     a0,0*8(sp)                  /* pass xptr                          */
+       ldq     a1,1*8(sp)                  /* pass xpc                           */
+       mov     v0,a2                       /* pass PV                            */
+       addq    sp,6*8,a3                   /* pass Java SP                       */
+
+       br      L_asm_handle_exception_continue
 
        .aent    asm_handle_exception
 
@@ -432,39 +302,35 @@ L_asm_handle_exception:                 /* required for PIC code              */
        SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
        SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
 
-       lda     a3,(ARG_CNT+TMP_CNT)*8(zero)/* prepare a3 for handle_exception */
-       lda     a4,1(zero)                  /* set maybe-leaf flag                */
+       lda     sp,-6*8(sp)                 /* keep stack 16-byte aligned         */
+       stq     xptr,0*8(sp)                /* save xptr                          */
+       stq     pv,2*8(sp)                  /* save PV                            */
+       stq     ra,3*8(sp)                  /* save RA                            */
+       lda     t0,1(zero)                  /* set maybe-leaf flag                */
+       stq     t0,4*8(sp)                  /* save maybe-leaf flag               */
 
-L_asm_handle_exception_stack_loop:
-       lda     sp,-5*8(sp)                 /* allocate stack                     */
-       stq     xptr,0*8(sp)                /* save exception pointer             */
-       stq     xpc,1*8(sp)                 /* save exception pc                  */
-       stq     pv,2*8(sp)                  /* save data segment pointer          */
-       stq     ra,3*8(sp)                  /* save return address                */
-       addq    a3,sp,a3                    /* calculate Java sp into a3...       */
-       addq    a3,5*8,a3
-       stq     a4,4*8(sp)                  /* save maybe-leaf flag               */
-
-       br      ra,L_asm_handle_exception_load_gp /* set ra for gp loading        */
-L_asm_handle_exception_load_gp:
+       br      ra,L_asm_handle_exception_load_gp_2
+L_asm_handle_exception_load_gp_2:
        ldgp    gp,0(ra)                    /* load gp                            */
 
-       mov     xptr,a0                     /* pass exception pointer             */
-       mov     xpc,a1                      /* pass exception pc                  */
-       mov     pv,a2                       /* pass data segment pointer          */
-                                           /* a3 is still set                    */
+       mov     xptr,a0                     /* pass xptr                          */
+       mov     xpc,a1                      /* pass xpc                           */
+       mov     pv,a2                       /* pass PV                            */
+       lda     a3,(ARG_CNT+TMP_CNT+6)*8(sp)/* pass Java SP                       */
+
+L_asm_handle_exception_continue:
        jsr     ra,exceptions_handle_exception
 
        beq     v0,L_asm_handle_exception_not_catched
 
        mov     v0,xpc                      /* move handlerpc into xpc            */
-       ldq     xptr,0*8(sp)                /* restore exception pointer          */
-       ldq     pv,2*8(sp)                  /* restore data segment pointer       */
-       ldq     ra,3*8(sp)                  /* restore return address             */
-       ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
-       lda     sp,5*8(sp)                  /* free stack frame                   */
+       ldq     xptr,0*8(sp)                /* restore xptr                       */
+       ldq     pv,2*8(sp)                  /* restore PV                         */
+       ldq     ra,3*8(sp)                  /* restore RA                         */
+       ldq     t0,4*8(sp)                  /* get maybe-leaf flag                */
+       lda     sp,6*8(sp)                  /* free stack frame                   */
 
-       beq     a4,L_asm_handle_exception_no_leaf
+       beq     t0,L_asm_handle_exception_no_leaf
 
        RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
        RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
@@ -475,89 +341,98 @@ L_asm_handle_exception_no_leaf:
        jmp     zero,(xpc)                  /* jump to the handler                */
 
 L_asm_handle_exception_not_catched:
-       ldq     xptr,0*8(sp)                /* restore exception pointer          */
-       ldq     pv,2*8(sp)                  /* restore data segment pointer       */
-       ldq     ra,3*8(sp)                  /* restore return address             */
-       ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
-       lda     sp,5*8(sp)
+       ldq     xptr,0*8(sp)                /* restore xptr                       */
+       ldq     pv,2*8(sp)                  /* restore PV                         */
+       ldq     ra,3*8(sp)                  /* restore RA                         */
+       ldq     t0,4*8(sp)                  /* get maybe-leaf flag                */
+       lda     sp,6*8(sp)
 
-       beq     a4,L_asm_handle_exception_no_leaf_stack
+       beq     t0,L_asm_handle_exception_no_leaf_stack
 
        lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
-       mov     zero,a4                     /* clear the maybe-leaf flag          */
+       mov     zero,t0                     /* clear the maybe-leaf flag          */
 
 L_asm_handle_exception_no_leaf_stack:
-       ldl     t0,FrameSize(pv)            /* get frame size                     */
-       addq    t0,sp,t0                    /* pointer to save area               */
+       ldl     t1,FrameSize(pv)            /* get frame size                     */
+       addq    t1,sp,t1                    /* pointer to save area               */
 
-       ldl     t1,IsLeaf(pv)               /* is leaf procedure                  */
-       bne     t1,L_asm_handle_exception_no_ra_restore
+       ldl     t2,IsLeaf(pv)               /* is leaf procedure                  */
+       bne     t2,L_asm_handle_exception_no_ra_restore
 
-       ldq     ra,-1*8(t0)                 /* restore ra                         */
-       subq    t0,8,t0                     /* t0--                               */
+       ldq     ra,-1*8(t1)                 /* restore ra                         */
+       subq    t1,8,t1                     /* t1--                               */
 
 L_asm_handle_exception_no_ra_restore:
        mov     ra,xpc                      /* the new xpc is ra                  */
-       ldl     t1,IntSave(pv)              /* t1 = saved int register count      */
-       br      t2,ex_int1                  /* t2 = current pc                    */
+       ldl     t2,IntSave(pv)              /* t2 = saved int register count      */
+       br      t3,ex_int1                  /* t3 = current pc                    */
 ex_int1:
-       lda     t2,(ex_int2-ex_int1)(t2)
-       negl    t1,t1                       /* negate register count              */
-       s4addq  t1,t2,t2                    /* t2 = IntSave - register count * 4  */
-       jmp     zero,(t2)                   /* jump to save position              */
-
-       ldq     s0,-7*8(t0)
-       ldq     s1,-6*8(t0)
-       ldq     s2,-5*8(t0)
-       ldq     s3,-4*8(t0)
-       ldq     s4,-3*8(t0)
-       ldq     s5,-2*8(t0)
-       ldq     s6,-1*8(t0)
+       lda     t3,(ex_int2 - ex_int1)(t3)
+       negl    t2,t2                       /* negate register count              */
+       s4addq  t2,t3,t3                    /* t2 = IntSave - register count * 4  */
+       jmp     zero,(t3)                   /* jump to save position              */
+
+       ldq     s0,-7*8(t1)
+       ldq     s1,-6*8(t1)
+       ldq     s2,-5*8(t1)
+       ldq     s3,-4*8(t1)
+       ldq     s4,-3*8(t1)
+       ldq     s5,-2*8(t1)
+       ldq     s6,-1*8(t1)
 
 ex_int2:
-       s8addq  t1,t0,t0                    /* t0 = t0 - 8 * register count       */
+       s8addq  t2,t1,t1                    /* t1 = t1 - 8 * register count       */
 
-       ldl     t1,FltSave(pv)              /* t1 = saved flt register count      */
-       br      t2,ex_flt1                  /* t2 = current pc                    */
+       ldl     t2,FltSave(pv)              /* t2 = saved flt register count      */
+       br      t3,ex_flt1                  /* t3 = current pc                    */
 ex_flt1:
-       lda     t2,(ex_flt2-ex_flt1)(t2)
-       negl    t1,t1                       /* negate register count              */
-       s4addq  t1,t2,t2                    /* t2 = FltSave - 4 * register count  */
-       jmp     zero,(t2)                   /* jump to save position              */
-
-       ldt     fs0,-8*8(t0)
-       ldt     fs1,-7*8(t0)
-       ldt     fs2,-6*8(t0)
-       ldt     fs3,-5*8(t0)
-       ldt     fs4,-4*8(t0)
-       ldt     fs5,-3*8(t0)
-       ldt     fs6,-2*8(t0)
-       ldt     fs7,-1*8(t0)
+       lda     t3,(ex_flt2 - ex_flt1)(t3)
+       negl    t2,t2                       /* negate register count              */
+       s4addq  t2,t3,t3                    /* t2 = FltSave - 4 * register count  */
+       jmp     zero,(t3)                   /* jump to save position              */
+
+       ldt     fs0,-8*8(t1)
+       ldt     fs1,-7*8(t1)
+       ldt     fs2,-6*8(t1)
+       ldt     fs3,-5*8(t1)
+       ldt     fs4,-4*8(t1)
+       ldt     fs5,-3*8(t1)
+       ldt     fs6,-2*8(t1)
+       ldt     fs7,-1*8(t1)
 
 ex_flt2:
-       ldl     t0,FrameSize(pv)            /* get frame size                     */
-       addq    sp,t0,sp                    /* unwind stack                       */
-       mov     zero,a3                     /* prepare a3 for handle_exception    */
-
-       ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
-       sll     t0,48,t0
-       sra     t0,48,t0              /* isolate offset                           */
-       addq    t0,ra,pv              /* compute update address                   */
-       ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
-       srl     t0,16,t0              /* isolate instruction code                 */
-       lda     t0,-0x177b(t0)        /* test for LDAH                            */
-       bne     t0,L_asm_handle_exception_stack_loop
-       ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(RA)         */
-       sll     t0,16,t0              /* compute high offset                      */
-       addl    t0,0,t0               /* sign extend high offset                  */
-       addq    t0,pv,pv              /* compute update address                   */
-
+       ldl     t1,FrameSize(pv)            /* get frame size                     */
+       addq    sp,t1,sp                    /* unwind stack                       */
        br      L_asm_handle_exception_stack_loop
 
        .end    asm_handle_nat_exception
 
 
-/* asm_wrapper_patcher *********************************************************
+/* asm_abstractmethoderror *****************************************************
+
+   Creates and throws an AbstractMethodError.
+
+*******************************************************************************/
+
+       .ent    asm_abstractmethoderror
+
+asm_abstractmethoderror:
+       subq    sp,2*8,sp                   /* create stackframe                  */
+       stq     ra,0*8(sp)                  /* save return address                */
+       addq    sp,2*8,a0                   /* pass java sp                       */
+       mov     ra,a1                       /* pass exception address             */
+       jsr     ra,exceptions_asm_new_abstractmethoderror
+       ldq     ra,0*8(sp)                  /* restore return address             */
+       addq    sp,2*8,sp                   /* remove stackframe                  */
+
+       mov     v0,xptr                     /* get exception pointer              */
+       subq    ra,4,xpc                    /* exception address is ra - 4        */
+       br      L_asm_handle_nat_exception
+
+       .end    asm_abstractmethoderror
+
+
+/* asm_patcher_wrapper *********************************************************
 
    XXX
 
@@ -573,10 +448,10 @@ ex_flt2:
 
 *******************************************************************************/
                
-       .ent    asm_wrapper_patcher
+       .ent    asm_patcher_wrapper
 
-asm_wrapper_patcher:
-       lda     sp,-((2+12+27+4)*8+sizestackframeinfo)(sp) /* create stack frame  */
+asm_patcher_wrapper:
+       lda     sp,-((2+12+27+4)*8)(sp) /* create stack frame                     */
 
        SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
        SAVE_ARGUMENT_REGISTERS(2)    /* save 6 int/6 float argument registers    */
@@ -587,29 +462,16 @@ asm_wrapper_patcher:
        stq     ra,(2+12+27+2)*8(sp)  /* save method return address (for leafs)   */
        stq     pv,(2+12+27+3)*8(sp)  /* save pv of calling java function         */
 
-       br      ra,L_asm_wrapper_patcher_load_gp
-L_asm_wrapper_patcher_load_gp:
+       br      ra,L_asm_patcher_wrapper_load_gp
+L_asm_patcher_wrapper_load_gp:
        ldgp    gp,0(ra)              /* load gp (it's not set correctly in jit)  */
 
-       lda     a0,(2+12+27+4)*8(sp)  /* create stackframe info                   */
-       mov     pv,a1                 /* pass java pv                             */
-       lda     a2,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass java sp       */
-       ldq     a3,(2+12+27+2)*8(sp)  /* this is correct for leafs                */
-       ldq     a4,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
-       jsr     ra,stacktrace_create_extern_stackframeinfo
-       ldgp    gp,0(ra)
-
-       lda     a0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass sp            */
-       ldq     pv,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get function       */
-       ldq     itmp1,(2+12+27+3)*8(sp) /* save pv to the position of fp          */
-       stq     itmp1,((0+2+12+27+4)*8+sizestackframeinfo)(sp)
-       jmp     ra,(pv)               /* call the patcher function                */
-       ldgp    gp,0(ra)
-       stq     v0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* save return value  */
-
-       lda     a0,(2+12+27+4)*8(sp)  /* remove stackframe info                   */
-       jsr     ra,stacktrace_remove_stackframeinfo
+       lda     a0,(2+12+27+4)*8(sp)  /* pass SP of patcher stub                  */
+       mov     pv,a1                 /* pass PV                                  */
+       ldq     a2,(2+12+27+2)*8(sp)  /* pass RA (correct for leafs)              */
+       jsr     ra,patcher_wrapper
        ldgp    gp,0(ra)
+       stq     v0,(0+2+12+27+4)*8(sp) /* save return value                       */
 
        RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
        RESTORE_ARGUMENT_REGISTERS(2) /* restore 6 int/6 float argument registers */
@@ -620,161 +482,312 @@ L_asm_wrapper_patcher_load_gp:
        ldq     ra,(2+12+27+2)*8(sp)  /* restore method return address (for leafs)*/
        ldq     pv,(2+12+27+3)*8(sp)  /* restore pv of calling java function      */
 
-       ldq     itmp3,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get return value*/
-       beq     itmp3,L_asm_wrapper_patcher_exception
+       ldq     itmp3,(0+2+12+27+4)*8(sp) /* get return value                     */
+       bne     itmp3,L_asm_patcher_wrapper_exception
 
-       ldq     itmp3,((5+2+12+27+4)*8+sizestackframeinfo)(sp)/* get RA to JIT    */
-       lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
+       ldq     itmp3,(5+2+12+27+4)*8(sp) /* get RA to JIT                        */
+       lda     sp,(6+2+12+27+4)*8(sp) /* remove stack frame                      */
 
        jmp     zero,(itmp3)          /* jump to new patched code                 */
 
-L_asm_wrapper_patcher_exception:
-       ldq     xpc,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* RA is xpc         */
-       lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
-
-       br      itmp1,L_asm_wrapper_patcher_exception_load_gp
-L_asm_wrapper_patcher_exception_load_gp:
-       ldgp    gp,0(itmp1)           /* itmp3 == gp, load the current gp         */
-
-#if defined(USE_THREADS) && defined(NATIVE_THREADS)
-       subq    sp,3*8,sp
-       stq     xpc,0*8(sp)           /* save return address (xpc)                */
-       stq     ra,1*8(sp)
-       stq     pv,2*8(sp)
-       jsr     ra,builtin_asm_get_exceptionptrptr
-       ldq     xpc,0*8(sp)           /* restore return address (xpc)             */
-       ldq     ra,1*8(sp)
-       ldq     pv,2*8(sp)
-       addq    sp,3*8,sp
-#else
-       lda     v0,_exceptionptr
-#endif
-       ldq     xptr,0(v0)            /* get the exception pointer                */
-       stq     zero,0(v0)            /* clear the exception pointer              */
-       br      L_asm_handle_exception/* we have the pv of the calling java func. */
+L_asm_patcher_wrapper_exception:
+       mov     itmp3,xptr            /* get exception                            */
+       ldq     xpc,(5+2+12+27+4)*8(sp) /* RA is xpc                              */
+       lda     sp,(6+2+12+27+4)*8(sp) /* remove stack frame                      */
+       br      L_asm_handle_exception
 
-       .end    asm_wrapper_patcher
+       .end    asm_patcher_wrapper
 
                
-/******************* function asm_initialize_thread_stack **********************
-*                                                                              *
-*   initialized a thread stack                                                 *
-*                                                                              *
-*******************************************************************************/
+#if defined(ENABLE_REPLACEMENT)
 
-       .ent    asm_initialize_thread_stack
-
-asm_initialize_thread_stack:
-       lda     a1,-128(a1)
-       stq     zero, 0(a1)
-       stq     zero, 8(a1)
-       stq     zero, 16(a1)
-       stq     zero, 24(a1)
-       stq     zero, 32(a1)
-       stq     zero, 40(a1)
-       stq     zero, 48(a1)
-       stt     fzero, 56(a1)
-       stt     fzero, 64(a1)
-       stt     fzero, 72(a1)
-       stt     fzero, 80(a1)
-       stt     fzero, 88(a1)
-       stt     fzero, 96(a1)
-       stt     fzero, 104(a1)
-       stt     fzero, 112(a1)
-       stq     a0, 120(a1)
-       mov     a1, v0
-       jmp     zero,(ra)
+/* asm_replacement_out *********************************************************
 
-       .end    asm_initialize_thread_stack
+   This code is jumped to from the replacement-out stubs that are executed
+   when a thread reaches an activated replacement point.
 
+   The purpose of asm_replacement_out is to read out the parts of the
+   execution state that cannot be accessed from C code, store this state,
+   and then call the C function replace_me.
+
+   Stack layout:
+     16                 start of stack inside method to replace
+      0   rplpoint *    info on the replacement point that was reached
+
+   NOTE: itmp3 has been clobbered by the replacement-out stub!
 
-/******************* function asm_perform_threadswitch *************************
-*                                                                              *
-*   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
-*                                                                              *
-*   performs a threadswitch                                                    *
-*                                                                              *
 *******************************************************************************/
 
-       .ent    asm_perform_threadswitch
-
-asm_perform_threadswitch:
-       subq    sp,128,sp
-       stq     s0, 0(sp)
-       stq     s1, 8(sp)
-       stq     s2, 16(sp)
-       stq     s3, 24(sp)
-       stq     s4, 32(sp)
-       stq     s5, 40(sp)
-       stq     s6, 48(sp)
-       stt     fs0, 56(sp)
-       stt     fs1, 64(sp)
-       stt     fs2, 72(sp)
-       stt     fs3, 80(sp)
-       stt     fs4, 88(sp)
-       stt     fs5, 96(sp)
-       stt     fs6, 104(sp)
-       stt     fs7, 112(sp)
-       stq     ra, 120(sp)
-       stq     sp, 0(a0)
-       stq     sp, 0(a2)
-       ldq     sp, 0(a1)
-       ldq     s0, 0(sp)
-       ldq     s1, 8(sp)
-       ldq     s2, 16(sp)
-       ldq     s3, 24(sp)
-       ldq     s4, 32(sp)
-       ldq     s5, 40(sp)
-       ldq     s6, 48(sp)
-       ldt     fs0, 56(sp)
-       ldt     fs1, 64(sp)
-       ldt     fs2, 72(sp)
-       ldt     fs3, 80(sp)
-       ldt     fs4, 88(sp)
-       ldt     fs5, 96(sp)
-       ldt     fs6, 104(sp)
-       ldt     fs7, 112(sp)
-       ldq     ra, 120(sp)
-       mov     ra, pv
-       addq    sp, 128, sp
-       jmp     zero,(ra)
-
-       .end    asm_perform_threadswitch
-
-
-/********************* function asm_switchstackandcall *************************
-*                                                                              *
-*  void *asm_switchstackandcall (void *stack, void *func, void **stacktopsave, *
-*                               void *p);                                      *
-*                                                                              *
-*   Switches to a new stack, calls a function and switches back.               *
-*       a0      new stack pointer                                              *
-*       a1      function pointer                                               *
-*              a2              pointer to variable where stack top should be stored           *
-*              a3      pointer to user data, is passed to the function                *
-*                                                                              *
+/* some room to accomodate changes of the stack frame size during replacement */
+       /* XXX we should find a cleaner solution here */
+#define REPLACEMENT_ROOM  512
+
+#define REPLACEMENT_STACK_OFFSET ((sizeexecutionstate + REPLACEMENT_ROOM + 0xf) & ~0xf)
+
+       .ent asm_replacement_out
+
+asm_replacement_out:
+    /* create stack frame */
+       lda     sp,-(REPLACEMENT_STACK_OFFSET)(sp)
+
+       /* save registers in execution state */
+       stq     $0 ,( 0*8+offes_intregs)(sp)
+       stq     $1 ,( 1*8+offes_intregs)(sp)
+       stq     $2 ,( 2*8+offes_intregs)(sp)
+       stq     $3 ,( 3*8+offes_intregs)(sp)
+       stq     $4 ,( 4*8+offes_intregs)(sp)
+       stq     $5 ,( 5*8+offes_intregs)(sp)
+       stq     $6 ,( 6*8+offes_intregs)(sp)
+       stq     $7 ,( 7*8+offes_intregs)(sp)
+       stq     $8 ,( 8*8+offes_intregs)(sp)
+       stq     $9 ,( 9*8+offes_intregs)(sp)
+       stq     $10,(10*8+offes_intregs)(sp)
+       stq     $11,(11*8+offes_intregs)(sp)
+       stq     $12,(12*8+offes_intregs)(sp)
+       stq     $13,(13*8+offes_intregs)(sp)
+       stq     $14,(14*8+offes_intregs)(sp)
+       stq     $15,(15*8+offes_intregs)(sp)
+       stq     $16,(16*8+offes_intregs)(sp)
+       stq     $17,(17*8+offes_intregs)(sp)
+       stq     $18,(18*8+offes_intregs)(sp)
+       stq     $19,(19*8+offes_intregs)(sp)
+       stq     $20,(20*8+offes_intregs)(sp)
+       stq     $21,(21*8+offes_intregs)(sp)
+       stq     $22,(22*8+offes_intregs)(sp)
+       stq     $23,(23*8+offes_intregs)(sp)
+       stq     $24,(24*8+offes_intregs)(sp)
+       stq     $25,(25*8+offes_intregs)(sp)
+       stq     $26,(26*8+offes_intregs)(sp)
+       stq     $27,(27*8+offes_intregs)(sp)
+       stq     $28,(28*8+offes_intregs)(sp)
+       stq     $29,(29*8+offes_intregs)(sp)
+       stq     $30,(30*8+offes_intregs)(sp)
+       stq     $31,(31*8+offes_intregs)(sp)
+       
+       stt     $f0 ,( 0*8+offes_fltregs)(sp)
+       stt     $f1 ,( 1*8+offes_fltregs)(sp)
+       stt     $f2 ,( 2*8+offes_fltregs)(sp)
+       stt     $f3 ,( 3*8+offes_fltregs)(sp)
+       stt     $f4 ,( 4*8+offes_fltregs)(sp)
+       stt     $f5 ,( 5*8+offes_fltregs)(sp)
+       stt     $f6 ,( 6*8+offes_fltregs)(sp)
+       stt     $f7 ,( 7*8+offes_fltregs)(sp)
+       stt     $f8 ,( 8*8+offes_fltregs)(sp)
+       stt     $f9 ,( 9*8+offes_fltregs)(sp)
+       stt     $f10,(10*8+offes_fltregs)(sp)
+       stt     $f11,(11*8+offes_fltregs)(sp)
+       stt     $f12,(12*8+offes_fltregs)(sp)
+       stt     $f13,(13*8+offes_fltregs)(sp)
+       stt     $f14,(14*8+offes_fltregs)(sp)
+       stt     $f15,(15*8+offes_fltregs)(sp)
+       stt     $f16,(16*8+offes_fltregs)(sp)
+       stt     $f17,(17*8+offes_fltregs)(sp)
+       stt     $f18,(18*8+offes_fltregs)(sp)
+       stt     $f19,(19*8+offes_fltregs)(sp)
+       stt     $f20,(20*8+offes_fltregs)(sp)
+       stt     $f21,(21*8+offes_fltregs)(sp)
+       stt     $f22,(22*8+offes_fltregs)(sp)
+       stt     $f23,(23*8+offes_fltregs)(sp)
+       stt     $f24,(24*8+offes_fltregs)(sp)
+       stt     $f25,(25*8+offes_fltregs)(sp)
+       stt     $f26,(26*8+offes_fltregs)(sp)
+       stt     $f27,(27*8+offes_fltregs)(sp)
+       stt     $f28,(28*8+offes_fltregs)(sp)
+       stt     $f29,(29*8+offes_fltregs)(sp)
+       stt     $f30,(30*8+offes_fltregs)(sp)
+       stt     $f31,(31*8+offes_fltregs)(sp)
+       
+       /* calculate sp of method */
+       lda     itmp1,(REPLACEMENT_STACK_OFFSET + 2*8)(sp)
+       stq     itmp1,(offes_sp)(sp)
+
+       br      ra,L_asm_replacement_out_load_gp
+L_asm_replacement_out_load_gp:
+       ldgp    gp,0(ra)                    /* load gp                            */
+
+       /* store pv */
+       stq     pv,(offes_pv)(sp)
+
+       /* call replace_me */
+       ldq     a0,-(2*8)(itmp1)            /* arg0: rplpoint *                   */
+    mov     sp,a1                       /* arg1: execution state              */
+    jmp     zero,replace_me             /* call C function replace_me         */
+    jmp     zero,abort                  /* NEVER REACHED                      */
+
+       .end asm_replacement_out
+
+/* asm_replacement_in **********************************************************
+
+   This code writes the given execution state and jumps to the replacement
+   code.
+
+   This function never returns!
+
+   NOTE: itmp3 is not restored!
+
+   C prototype:
+      void asm_replacement_in(executionstate *es, replace_safestack_t *st);
+
 *******************************************************************************/
 
+       .ent asm_replacement_in
+       
+asm_replacement_in:
+       /* a0 == executionstate *es */
+
+       /* get arguments */
+       mov     a1,s1                       /* replace_safestack_t *st            */
+       mov     a0,s2                       /* executionstate *es == safe stack   */
+
+       /* switch to the safe stack */
+       mov     s2,sp
+
+       /* call replace_build_execution_state(st) */
+       mov             s1,a0
+       jsr             ra,replace_build_execution_state
+
+       /* set new sp */
+       ldq             sp,(offes_sp)(s2)
 
-       .ent    asm_switchstackandcall
+       /* build stack frame */
+       lda     sp,(-sizeexecutionstate)(sp)
 
-asm_switchstackandcall:
-       lda     a0,-2*8(a0)     /* allocate new stack                                 */
-       stq     ra,0(a0)        /* save return address on new stack                   */
-       stq     sp,1*8(a0)      /* save old stack pointer on new stack                */
-       stq sp,0(a2)        /* save old stack pointer to variable                 */
-       mov     a0,sp           /* switch to new stack                                */
+       /* call replace_free_safestack(st,& of allocated executionstate_t) */
+       mov             sp,a1 /* tmpes */
+       mov             s1,a0 /* st    */
+       jsr             ra,replace_free_safestack
+
+       /* set new pv */
+       ldq     pv,(offes_pv)(sp)
+       
+       /* copy registers from execution state */
+       ldq     $0 ,( 0*8+offes_intregs)(sp)
+       ldq     $1 ,( 1*8+offes_intregs)(sp)
+       ldq     $2 ,( 2*8+offes_intregs)(sp)
+       ldq     $3 ,( 3*8+offes_intregs)(sp)
+       ldq     $4 ,( 4*8+offes_intregs)(sp)
+       ldq     $5 ,( 5*8+offes_intregs)(sp)
+       ldq     $6 ,( 6*8+offes_intregs)(sp)
+       ldq     $7 ,( 7*8+offes_intregs)(sp)
+       ldq     $8 ,( 8*8+offes_intregs)(sp)
+       ldq     $9 ,( 9*8+offes_intregs)(sp)
+       ldq     $10,(10*8+offes_intregs)(sp)
+       ldq     $11,(11*8+offes_intregs)(sp)
+       ldq     $12,(12*8+offes_intregs)(sp)
+       ldq     $13,(13*8+offes_intregs)(sp)
+       ldq     $14,(14*8+offes_intregs)(sp)
+       ldq     $15,(15*8+offes_intregs)(sp)
+       ldq     a0, (16*8+offes_intregs)(sp)
+       ldq     $17,(17*8+offes_intregs)(sp)
+       ldq     $18,(18*8+offes_intregs)(sp)
+       ldq     $19,(19*8+offes_intregs)(sp)
+       ldq     $20,(20*8+offes_intregs)(sp)
+       ldq     $21,(21*8+offes_intregs)(sp)
+       ldq     $22,(22*8+offes_intregs)(sp)
+       ldq     $23,(23*8+offes_intregs)(sp)
+       ldq     $24,(24*8+offes_intregs)(sp)
+       ldq     $25,(25*8+offes_intregs)(sp)
+       ldq     $26,(26*8+offes_intregs)(sp)
+       /* $27 is pv                    */
+       ldq     $28,(28*8+offes_intregs)(sp)
+       ldq     $29,(29*8+offes_intregs)(sp)
+       /* $30 is sp                      */
+       /* $31 is zero                    */
        
-       mov     a1,pv           /* load function pointer                              */
-       mov a3,a0           /* pass pointer */
-       jmp     ra,(pv)         /* and call function                                  */
+       ldt     $f0 ,( 0*8+offes_fltregs)(sp)
+       ldt     $f1 ,( 1*8+offes_fltregs)(sp)
+       ldt     $f2 ,( 2*8+offes_fltregs)(sp)
+       ldt     $f3 ,( 3*8+offes_fltregs)(sp)
+       ldt     $f4 ,( 4*8+offes_fltregs)(sp)
+       ldt     $f5 ,( 5*8+offes_fltregs)(sp)
+       ldt     $f6 ,( 6*8+offes_fltregs)(sp)
+       ldt     $f7 ,( 7*8+offes_fltregs)(sp)
+       ldt     $f8 ,( 8*8+offes_fltregs)(sp)
+       ldt     $f9 ,( 9*8+offes_fltregs)(sp)
+       ldt     $f10,(10*8+offes_fltregs)(sp)
+       ldt     $f11,(11*8+offes_fltregs)(sp)
+       ldt     $f12,(12*8+offes_fltregs)(sp)
+       ldt     $f13,(13*8+offes_fltregs)(sp)
+       ldt     $f14,(14*8+offes_fltregs)(sp)
+       ldt     $f15,(15*8+offes_fltregs)(sp)
+       ldt     $f16,(16*8+offes_fltregs)(sp)
+       ldt     $f17,(17*8+offes_fltregs)(sp)
+       ldt     $f18,(18*8+offes_fltregs)(sp)
+       ldt     $f19,(19*8+offes_fltregs)(sp)
+       ldt     $f20,(20*8+offes_fltregs)(sp)
+       ldt     $f21,(21*8+offes_fltregs)(sp)
+       ldt     $f22,(22*8+offes_fltregs)(sp)
+       ldt     $f23,(23*8+offes_fltregs)(sp)
+       ldt     $f24,(24*8+offes_fltregs)(sp)
+       ldt     $f25,(25*8+offes_fltregs)(sp)
+       ldt     $f26,(26*8+offes_fltregs)(sp)
+       ldt     $f27,(27*8+offes_fltregs)(sp)
+       ldt     $f28,(28*8+offes_fltregs)(sp)
+       ldt     $f29,(29*8+offes_fltregs)(sp)
+       ldt     $f30,(30*8+offes_fltregs)(sp)
+       ldt     $f31,(31*8+offes_fltregs)(sp)
+
+       /* load new pc */
+
+       ldq     itmp3,offes_pc(sp)
+
+       /* remove stack frame */
+
+       lda             sp,(sizeexecutionstate)(sp)
 
-       ldq     ra,0(sp)        /* load return address                                */
-       ldq     sp,1*8(sp)      /* switch to old stack                                */
+       /* jump to new code */
 
-       jmp     zero,(ra)       /* return                                             */
+       jmp     zero,(itmp3)
 
-       .end    asm_switchstackandcall
+       .end asm_replacement_in
+
+#endif /* defined(ENABLE_REPLACEMENT) */
+
+
+/* asm_compare_and_swap ********************************************************
+
+   Does an atomic compare and swap.  Required for the lock
+   implementation.
+
+   Atomically do the following: Check if the location still contains
+   `oldval`. If so, replace it by `newval` and return `oldval`.
+
+   RETURN VALUE:
+       the old value at *p
+
+   long compare_and_swap(volatile long *p, long oldval, long newval);
+
+*******************************************************************************/
+
+       .ent    asm_compare_and_swap
+
+asm_compare_and_swap:
+1:
+       ldq_l   v0,0(a0)
+       cmpeq   v0,a1,t0
+       beq     t0,2f
+       mov     a2,t0
+       stq_c   t0,0(a0)
+       beq     t0,1b
+2:
+       jmp     zero,(ra)
+
+       .end    asm_compare_and_swap
+
+
+/* asm_memory_barrier **********************************************************
+
+   A memory barrier for the Java Memory Model.
+
+*******************************************************************************/
+
+       .ent    asm_memory_barrier
+
+asm_memory_barrier:
+       mb
+       jmp     zero,(ra)
+
+       .end    asm_memory_barrier
 
 
        .ent    asm_getclassvalues_atomic
@@ -797,7 +810,7 @@ _crit_end:
     .data
 
 asm_criticalsections:
-#if defined(USE_THREADS) && defined(NATIVE_THREADS)
+#if defined(ENABLE_THREADS)
     .quad   _crit_begin
     .quad   _crit_end
     .quad   _crit_restart
@@ -805,9 +818,42 @@ asm_criticalsections:
     .quad   0
 
 
-/* Disable exec-stacks, required for Gentoo ***********************************/
+/* asm_md_init *****************************************************************
+
+   Initialize machine dependent stuff.
+
+   Determines if the byte support instruction set (21164a and higher)
+   is available.
+
+*******************************************************************************/
+
+       .ent    asm_md_init
+
+asm_md_init:
+       .long   0x47e03c20                  /* amask   1,v0                       */
+       jmp     zero,(ra)                   /* return                             */
+
+       .end    asm_md_init
+
+
+/* asm_cacheflush **************************************************************
+
+   XXX
+
+*******************************************************************************/
+
+       .ent    asm_cacheflush
+
+asm_cacheflush:
+       call_pal PAL_imb              /* synchronize instruction cache            */
+       jmp     zero,(ra)
+
+       .end    asm_cacheflush
+
+
+/* disable exec-stacks ********************************************************/
 
-#if defined(__GCC__) && defined(__ELF__)
+#if defined(__linux__) && defined(__ELF__)
        .section .note.GNU-stack,"",@progbits
 #endif
 
@@ -823,4 +869,5 @@ asm_criticalsections:
  * c-basic-offset: 4
  * tab-width: 4
  * End:
+ * vim:noexpandtab:sw=4:ts=4:
  */