invokevirtual: implement lazy class loading right
authorBernhard Urban <lewurm@gmail.com>
Fri, 17 Aug 2012 22:21:12 +0000 (00:21 +0200)
committerBernhard Urban <lewurm@gmail.com>
Fri, 17 Aug 2012 22:21:12 +0000 (00:21 +0200)
also use a different trap strategy, namely SIGILL instead of SIGSEGV, which
makes handling a lot easier and simplifies code imho.

Mate/MethodPool.hs
Mate/Types.hs
Mate/X86CodeGen.hs
Mate/X86TrapHandling.hs
doc/TODO
ffi/trap.c
tests/Generics1.java
tests/Instance6.java [new file with mode: 0644]

index 5a0f70e73605fa0e256cfcea9b925cbddd2d1520..5330ade2e6a5b8d1eac3b3878fd08622a9f91a25 100644 (file)
@@ -48,8 +48,7 @@ getMethodEntry signal_from methodtable = do
   let mi'@(MethodInfo method cm sig) =
        case mi of
          (StaticMethod x) -> x
   let mi'@(MethodInfo method cm sig) =
        case mi of
          (StaticMethod x) -> x
-         (VirtualMethod   _ (MethodInfo methname _ msig)) -> newMi methname msig
-         (InterfaceMethod _ (MethodInfo methname _ msig)) -> newMi methname msig
+         (VirtualCall _ (MethodInfo methname _ msig) _) -> newMi methname msig
          _ -> error "getMethodEntry: no TrapCause found. abort."
        where newMi mn = MethodInfo mn (vmap M.! fromIntegral methodtable)
   -- bernhard (TODO): doesn't work with gnu classpath at some point. didn't
          _ -> error "getMethodEntry: no TrapCause found. abort."
        where newMi mn = MethodInfo mn (vmap M.! fromIntegral methodtable)
   -- bernhard (TODO): doesn't work with gnu classpath at some point. didn't
index 0fe838e0edd9524f62fc186659ce75757402d296..5e5bf221e0ba26420943967d2b77e2cdcedb7ab6 100644 (file)
@@ -40,11 +40,10 @@ type TrapMap = M.Map NativeWord TrapCause
 
 data TrapCause =
   StaticMethod MethodInfo | -- for static calls
 
 data TrapCause =
   StaticMethod MethodInfo | -- for static calls
-  VirtualMethod Bool MethodInfo | -- for virtual calls
-  InterfaceMethod Bool MethodInfo | -- for interface calls
+  VirtualCall Bool MethodInfo (IO NativeWord) | -- for invoke{interface,virtual}
   InstanceOf B.ByteString | -- class name
   NewObject B.ByteString | -- class name
   InstanceOf B.ByteString | -- class name
   NewObject B.ByteString | -- class name
-  StaticField StaticFieldInfo deriving Show
+  StaticField StaticFieldInfo
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
index ffdc83d8b2021d6f7e8639c38fc6257feb9b4072..fb62c905d3332d67c3188e5b81cba239e809a676 100644 (file)
@@ -9,6 +9,7 @@ import Data.Binary
 import Data.BinaryState
 import Data.Int
 import Data.Maybe
 import Data.BinaryState
 import Data.Int
 import Data.Maybe
+import Data.List (genericLength)
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
 import Control.Monad
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
 import Control.Monad
@@ -112,7 +113,7 @@ emitFromBB cls method = do
       newNamedLabel (show l) >>= defineLabel
       -- causes SIGILL. in the signal handler we patch it to the acutal call.
       -- place two nop's at the end, therefore the disasm doesn't screw up
       newNamedLabel (show l) >>= defineLabel
       -- causes SIGILL. in the signal handler we patch it to the acutal call.
       -- place two nop's at the end, therefore the disasm doesn't screw up
-      emit32 (0x9090ffff :: Word32) >> emit8 (0x90 :: Word8)
+      emit32 (0x9090ffff :: Word32); nop
       -- discard arguments on stack
       let argcnt = ((if hasThis then 1 else 0) + methodGetArgsCount (methodNameTypeByIdx cls cpidx)) * ptrSize
       when (argcnt > 0) (add esp argcnt)
       -- discard arguments on stack
       let argcnt = ((if hasThis then 1 else 0) + methodGetArgsCount (methodNameTypeByIdx cls cpidx)) * ptrSize
       when (argcnt > 0) (add esp argcnt)
@@ -120,18 +121,35 @@ emitFromBB cls method = do
       when (methodHaveReturnValue cls cpidx) (push eax)
       return $ Just (calladdr, StaticMethod l)
 
       when (methodHaveReturnValue cls cpidx) (push eax)
       return $ Just (calladdr, StaticMethod l)
 
-    invokeEpilog :: Word16 -> Word32 -> (Bool -> TrapCause) -> CodeGen e s (Maybe (Word32, TrapCause))
-    invokeEpilog cpidx offset trapcause = do
+    virtualCall :: Word16 -> Bool -> CodeGen e s (Maybe (Word32, TrapCause))
+    virtualCall cpidx isInterface = do
+      let mi@(MethodInfo methodname objname msig@(MethodSignature args _))  = buildMethodID cls cpidx
+      newNamedLabel (show mi) >>= defineLabel
+      -- get method offset for call @ runtime
+      let offset = if isInterface
+          then getInterfaceMethodOffset objname methodname (encode msig)
+          else getMethodOffset objname (methodname `B.append` encode msig)
+      let argsLen = genericLength args
+      -- objref lives somewhere on the argument stack
+      mov ebx (Disp (argsLen * ptrSize), esp)
+      if isInterface
+        then mov ebx (Disp 0, ebx) -- get method-table-ptr, keep it in ebx
+        else return () -- invokevirtual
+      -- get method-table-ptr (or interface-table-ptr)
+      mov eax (Disp 0, ebx)
       -- make actual (indirect) call
       calladdr <- getCurrentOffset
       -- make actual (indirect) call
       calladdr <- getCurrentOffset
-      call (Disp offset, eax)
+      -- will be patched to this: call (Disp 0xXXXXXXXX, eax)
+      emit32 (0x9090ffff :: Word32); nop; nop
       -- discard arguments on stack (`+1' for "this")
       let argcnt = ptrSize * (1 + methodGetArgsCount (methodNameTypeByIdx cls cpidx))
       when (argcnt > 0) (add esp argcnt)
       -- push result on stack if method has a return value
       when (methodHaveReturnValue cls cpidx) (push eax)
       -- discard arguments on stack (`+1' for "this")
       let argcnt = ptrSize * (1 + methodGetArgsCount (methodNameTypeByIdx cls cpidx))
       when (argcnt > 0) (add esp argcnt)
       -- push result on stack if method has a return value
       when (methodHaveReturnValue cls cpidx) (push eax)
-      let imm8 = is8BitOffset offset
-      return $ Just (calladdr + (if imm8 then 3 else 6), trapcause imm8)
+      -- note, that "mi" has the wrong class reference here.
+      -- we figure that out at run-time, in the methodpool,
+      -- depending on the method-table-ptr
+      return $ Just (calladdr, VirtualCall isInterface mi offset)
 
     emit'' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause))
     emit'' insn = newNamedLabel ("jvm_insn: " ++ show insn) >>= defineLabel >> emit' insn
 
     emit'' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause))
     emit'' insn = newNamedLabel ("jvm_insn: " ++ show insn) >>= defineLabel >> emit' insn
@@ -139,37 +157,8 @@ emitFromBB cls method = do
     emit' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause))
     emit' (INVOKESPECIAL cpidx) = emitInvoke cpidx True
     emit' (INVOKESTATIC cpidx) = emitInvoke cpidx False
     emit' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause))
     emit' (INVOKESPECIAL cpidx) = emitInvoke cpidx True
     emit' (INVOKESTATIC cpidx) = emitInvoke cpidx False
-    emit' (INVOKEINTERFACE cpidx _) = do
-      -- get methodInfo entry
-      let mi@(MethodInfo methodname ifacename msig@(MethodSignature args _)) = buildMethodID cls cpidx
-      newNamedLabel (show mi) >>= defineLabel
-      -- objref lives somewhere on the argument stack
-      mov eax (Disp ((* ptrSize) $ fromIntegral $ length args), esp)
-      -- get method-table-ptr, keep it in eax (for trap handling)
-      mov eax (Disp 0, eax)
-      -- get interface-table-ptr
-      mov ebx (Disp 0, eax)
-      -- get method offset
-      offset <- liftIO $ getInterfaceMethodOffset ifacename methodname (encode msig)
-      -- note, that "mi" has the wrong class reference here.
-      -- we figure that out at run-time, in the methodpool,
-      -- depending on the method-table-ptr
-      invokeEpilog cpidx offset (`InterfaceMethod` mi)
-    emit' (INVOKEVIRTUAL cpidx) = do
-      -- get methodInfo entry
-      let mi@(MethodInfo methodname objname msig@(MethodSignature args _))  = buildMethodID cls cpidx
-      newNamedLabel (show mi) >>= defineLabel
-      -- objref lives somewhere on the argument stack
-      mov eax (Disp ((* ptrSize) $ fromIntegral $ length args), esp)
-      -- get method-table-ptr
-      mov eax (Disp 0, eax)
-      -- get method offset
-      let nameAndSig = methodname `B.append` encode msig
-      offset <- liftIO $ getMethodOffset objname nameAndSig
-      -- note, that "mi" has the wrong class reference here.
-      -- we figure that out at run-time, in the methodpool,
-      -- depending on the method-table-ptr
-      invokeEpilog cpidx offset (`VirtualMethod` mi)
+    emit' (INVOKEINTERFACE cpidx _) = virtualCall cpidx True
+    emit' (INVOKEVIRTUAL cpidx) = virtualCall cpidx False
     emit' (PUTSTATIC cpidx) = do
       pop eax
       trapaddr <- getCurrentOffset
     emit' (PUTSTATIC cpidx) = do
       pop eax
       trapaddr <- getCurrentOffset
@@ -185,7 +174,7 @@ emitFromBB cls method = do
       mov eax (Disp 0, eax) -- mtable of objectref
       trapaddr <- getCurrentOffset
       -- place something like `mov edx $mtable_of_objref' instead
       mov eax (Disp 0, eax) -- mtable of objectref
       trapaddr <- getCurrentOffset
       -- place something like `mov edx $mtable_of_objref' instead
-      emit32 (0x9090ffff :: Word32) >> emit8 (0x90 :: Word8)
+      emit32 (0x9090ffff :: Word32); nop
       cmp eax edx
       sete al
       movzxb eax al
       cmp eax edx
       sete al
       movzxb eax al
@@ -196,7 +185,7 @@ emitFromBB cls method = do
       let objname = buildClassID cls objidx
       trapaddr <- getCurrentOffset
       -- place something like `push $objsize' instead
       let objname = buildClassID cls objidx
       trapaddr <- getCurrentOffset
       -- place something like `push $objsize' instead
-      emit32 (0x9090ffff :: Word32) >> emit8 (0x90 :: Word8)
+      emit32 (0x9090ffff :: Word32); nop
       callMalloc
       -- 0x13371337 is just a placeholder; will be replaced with mtable ptr
       mov (Disp 0, eax) (0x13371337 :: Word32)
       callMalloc
       -- 0x13371337 is just a placeholder; will be replaced with mtable ptr
       mov (Disp 0, eax) (0x13371337 :: Word32)
@@ -381,7 +370,3 @@ emitFromBB cls method = do
   s8_w32 :: Word8 -> Word32
   s8_w32 w8 = fromIntegral s8
     where s8 = fromIntegral w8 :: Int8
   s8_w32 :: Word8 -> Word32
   s8_w32 w8 = fromIntegral s8
     where s8 = fromIntegral w8 :: Int8
-
-  is8BitOffset :: Word32 -> Bool
-  is8BitOffset w32 = s32 < 128 && s32 > (-127)
-    where s32 = fromIntegral w32 :: Int32
index 493a3ceaf1b1a3a4a45c2d29bcacbeb6034a7a2e..e41c1adef50975d9a76159cfbec1cd63cfb625cc 100644 (file)
@@ -7,6 +7,7 @@ module Mate.X86TrapHandling (
   register_signal
   ) where
 
   register_signal
   ) where
 
+import Numeric
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
 
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
 
@@ -14,52 +15,27 @@ import Foreign
 import Foreign.C.Types
 
 import Mate.Types
 import Foreign.C.Types
 
 import Mate.Types
+import Mate.NativeSizes
 import {-# SOURCE #-} Mate.MethodPool
 import Mate.ClassPool
 
 foreign import ccall "register_signal"
   register_signal :: IO ()
 
 import {-# SOURCE #-} Mate.MethodPool
 import Mate.ClassPool
 
 foreign import ccall "register_signal"
   register_signal :: IO ()
 
-data TrapType =
-    StaticMethodCall
-  | StaticFieldAccess
-  | VirtualMethodCall Bool
-  | InterfaceMethodCall Bool
-  | InstanceOfMiss B.ByteString
-  | NewObjectTrap B.ByteString
-  | NoKnownTrap String
-
-getTrapType :: TrapMap -> CPtrdiff -> CPtrdiff -> TrapType
-getTrapType tmap signal_from from2 =
-  case M.lookup (fromIntegral signal_from) tmap of
-    (Just (StaticMethod _)) -> StaticMethodCall
-    (Just (StaticField _)) -> StaticFieldAccess
-    (Just (InstanceOf cn)) -> InstanceOfMiss cn
-    (Just (NewObject cn)) -> NewObjectTrap cn
-    (Just _) -> NoKnownTrap "getTrapMap: doesn't happen"
-    -- maybe we've a hit on the second `from' value
-    Nothing -> case M.lookup (fromIntegral from2) tmap of
-      (Just (VirtualMethod imm8 _)) -> VirtualMethodCall imm8
-      (Just (InterfaceMethod imm8 _)) -> InterfaceMethodCall imm8
-      (Just _) -> NoKnownTrap "getTrapType: abort #1 :-("
-      Nothing -> NoKnownTrap $ "getTrapType: abort #2 :-(" ++ show signal_from ++ ", " ++ show from2 ++ ", " ++ show tmap
-
-foreign export ccall mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
-mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
-mateHandler eip eax ebx esp esi = do
-  callerAddr <- callerAddrFromStack esp
+foreign export ccall mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
+mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
+mateHandler eip eax ebx esi = do
   tmap <- getTrapMap
   tmap <- getTrapMap
-  case getTrapType tmap eip callerAddr of
-    StaticMethodCall  -> staticCallHandler eip
-    StaticFieldAccess -> staticFieldHandler eip
-    (InstanceOfMiss cn) -> instanceOfMissHandler eip cn
-    (NewObjectTrap cn) -> newObjectHandler eip cn
-    VirtualMethodCall imm8   -> invokeHandler eax eax esp imm8
-    InterfaceMethodCall imm8 -> invokeHandler eax ebx esp imm8
-    NoKnownTrap err ->
-      case esi of
+  case M.lookup (fromIntegral eip) tmap of
+    (Just (StaticMethod _)) -> staticCallHandler eip
+    (Just (StaticField _))  -> staticFieldHandler eip
+    (Just (InstanceOf cn))  -> instanceOfMissHandler eip cn
+    (Just (NewObject cn))   -> newObjectHandler eip cn
+    (Just (VirtualCall False _ io_offset)) -> invokeHandler eax eax eip io_offset
+    (Just (VirtualCall True  _ io_offset)) -> invokeHandler ebx eax eip io_offset
+    Nothing -> case esi of
         0x13371234 -> return (-1)
         0x13371234 -> return (-1)
-        _ -> error err
+        _ -> error $ "getTrapType: abort :-(" ++ (showHex eip "") ++ ", " ++ show (M.keys tmap)
 
 staticCallHandler :: CPtrdiff -> IO CPtrdiff
 staticCallHandler eip = do
 
 staticCallHandler :: CPtrdiff -> IO CPtrdiff
 staticCallHandler eip = do
@@ -124,29 +100,25 @@ newObjectHandler eip classname = do
       return eip
     else error "newObjectHandler: something is wrong here. abort.\n"
 
       return eip
     else error "newObjectHandler: something is wrong here. abort.\n"
 
-invokeHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> Bool -> IO CPtrdiff
-invokeHandler method_table table2patch esp imm8 = do
-  -- table2patch: note, that can be a method-table or a interface-table
-  callerAddr <- callerAddrFromStack esp
-  offset <- if imm8 then offsetOfCallInsn8 esp else offsetOfCallInsn32 esp
-  entryAddr <- getMethodEntry callerAddr method_table
-  let call_insn = intPtrToPtr (fromIntegral $ table2patch + fromIntegral offset)
+invokeHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> IO NativeWord -> IO CPtrdiff
+invokeHandler method_table table2patch eip io_offset = do
+  let call0_insn_ptr = intPtrToPtr (fromIntegral eip) :: Ptr CUChar
+  let call1_insn_ptr = intPtrToPtr (fromIntegral (eip + 1)) :: Ptr CUChar
+  let call_imm_ptr = intPtrToPtr (fromIntegral (eip + 2)) :: Ptr CPtrdiff
+  offset <- io_offset
+  -- @table2patch: note, that can be a method-table or a interface-table
+  entryAddr <- getMethodEntry eip method_table
+
+  -- patch table
+  let call_insn = intPtrToPtr . fromIntegral $ table2patch + fromIntegral offset
   poke call_insn entryAddr
   poke call_insn entryAddr
-  return entryAddr
-
-
-callerAddrFromStack :: CPtrdiff -> IO CPtrdiff
-callerAddrFromStack = peek . intPtrToPtr . fromIntegral
 
 
-offsetOfCallInsn8 :: CPtrdiff -> IO CPtrdiff
-offsetOfCallInsn8 esp = do
-  let ret_ptr = intPtrToPtr (fromIntegral esp) :: Ptr CPtrdiff
-  ret <- peek ret_ptr
-  retval <- peek (intPtrToPtr (fromIntegral (ret - 1)) :: Ptr CUChar)
-  return $ fromIntegral retval
-
-offsetOfCallInsn32 :: CPtrdiff -> IO CPtrdiff
-offsetOfCallInsn32 esp = do
-  let ret_ptr = intPtrToPtr (fromIntegral esp) :: Ptr CPtrdiff
-  ret <- peek ret_ptr
-  peek (intPtrToPtr $ fromIntegral (ret - 4))
+  -- patch insn
+  checkMe <- peek call_imm_ptr
+  if checkMe == 0x90909090
+    then do
+      poke call0_insn_ptr 0xff -- indirect call op[0]
+      poke call1_insn_ptr 0x90 -- indirect call op[1]
+      poke call_imm_ptr (fromIntegral offset)
+      return eip
+    else error "invokeHandler: something is wrong here. abort\n"
index f65d294d46cf90aa4fc9fd664c3307602d2845db..15f7cb7190f159e260aeaf7eeb246e1308306413 100644 (file)
--- a/doc/TODO
+++ b/doc/TODO
@@ -81,6 +81,9 @@
        -> seperate analysis, jit, execution, ...
        -> maybe use ghc profiling? (it doesn't measure native execution, but well)
 
        -> seperate analysis, jit, execution, ...
        -> maybe use ghc profiling? (it doesn't measure native execution, but well)
 
+(h) patching also possible with harpy?
+       -> we can use a own buffer @ codegeneration...
+
 
 (l) ... low priority
 (m) ... medium priority
 
 (l) ... low priority
 (m) ... medium priority
index 4c291cf70d8c7e1dfd90f324d3da55e32269b846..4e526f23275d8967c9d05ed03899a7c29181aee1 100644 (file)
@@ -22,7 +22,7 @@
 
 #include <sys/ucontext.h>
 
 
 #include <sys/ucontext.h>
 
-ptrdiff_t mateHandler(ptrdiff_t, ptrdiff_t, ptrdiff_t, ptrdiff_t, ptrdiff_t);
+ptrdiff_t mateHandler(ptrdiff_t, ptrdiff_t, ptrdiff_t, ptrdiff_t);
 
 #ifdef DBG_TRAP
 #define dprintf(args...) do { printf (args); } while (0);
 
 #ifdef DBG_TRAP
 #define dprintf(args...) do { printf (args); } while (0);
@@ -45,7 +45,7 @@ void chandler(int nSignal, siginfo_t *info, void *ctx)
                        "esp 0x%08x, *esp 0x%08x, *(ebp+8) 0x%08x\n", nSignal, eip,
                        eax, ebx, esp, *(ptrdiff_t*) esp, *(ptrdiff_t *) (ebp + 8));
 
                        "esp 0x%08x, *esp 0x%08x, *(ebp+8) 0x%08x\n", nSignal, eip,
                        eax, ebx, esp, *(ptrdiff_t*) esp, *(ptrdiff_t *) (ebp + 8));
 
-       ptrdiff_t ret = mateHandler(eip, eax, ebx, esp, esi);
+       ptrdiff_t ret = mateHandler(eip, eax, ebx, esi);
        if (ret == -1) {
                dprintf("regdump @ EIP: 0x%08x\n", regs[REG_EIP]);
                dprintf("\tEAX: 0x%08lx EBX: 0x%08lx ECX: 0x%08lx EDX: 0x%08lx\n",
        if (ret == -1) {
                dprintf("regdump @ EIP: 0x%08x\n", regs[REG_EIP]);
                dprintf("\tEAX: 0x%08lx EBX: 0x%08lx ECX: 0x%08lx EDX: 0x%08lx\n",
index fa093ca2611da4f32ec1042de1cb9067e2663ee0..6a708fbd116c66d7f47e0142378745c27a8725f9 100644 (file)
@@ -11,8 +11,10 @@ public class Generics1 implements Cmp<Integer> {
 
        public static void main(String []args) {
                Generics1 foo = new Generics1();
 
        public static void main(String []args) {
                Generics1 foo = new Generics1();
-               System.out.printf("0x%08x\n", foo.cmpto(0x666));
-               System.out.printf("0x%08x\n", sb.cmpto(0x666));
+               for (int i = 0; i < 0x10; i++) {
+                       System.out.printf("0x%08x\n", foo.cmpto(0x666));
+                       System.out.printf("0x%08x\n", sb.cmpto(0x666));
+               }
        }
 }
 
        }
 }
 
diff --git a/tests/Instance6.java b/tests/Instance6.java
new file mode 100644 (file)
index 0000000..c1ed367
--- /dev/null
@@ -0,0 +1,24 @@
+package tests;
+
+public class Instance6 {
+       public static void main(String []args) {
+               int i_am_null = 0;
+               System.out.printf("before\n");
+               if (i_am_null > 0) {
+                       Instance6_notload a = new Instance6_notload();
+                       a.lol();
+                       System.out.printf("loaded notload stuff o_O\n");
+               } else {
+                       System.out.printf("Nothing to do here\n");
+               }
+       }
+}
+
+class Instance6_notload {
+       static {
+               System.out.printf("sup, I'm Instance6_notload\n");
+       }
+       void lol() {
+               System.out.printf("lolololololo\n");
+       }
+}