invokevirtual: implement lazy class loading right
[mate.git] / Mate / X86TrapHandling.hs
index 2972cacf9627c541c637b0c0c9edcda028ab8fb3..e41c1adef50975d9a76159cfbec1cd63cfb625cc 100644 (file)
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
 #include "debug.h"
-module Mate.X86TrapHandling where
+module Mate.X86TrapHandling (
+  mateHandler,
+  register_signal
+  ) where
 
+import Numeric
 import qualified Data.Map as M
+import qualified Data.ByteString.Lazy as B
 
 import Foreign
 import Foreign.C.Types
 
 import Mate.Types
-import Mate.MethodPool
+import Mate.NativeSizes
+import {-# SOURCE #-} Mate.MethodPool
 import Mate.ClassPool
 
-
 foreign import ccall "register_signal"
   register_signal :: IO ()
 
-
-getTrapType :: CUInt -> CUInt -> IO CUInt
-getTrapType signal_from from2 = do
+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
-  case M.lookup (fromIntegral signal_from) tmap of
-    (Just (MI _)) -> return 0
-    (Just (SFI _)) -> return 2
-    (Just _) -> error "getTrapMap: doesn't happen"
-    -- maybe we've a hit on the second `from' value
-    Nothing -> case M.lookup (fromIntegral from2) tmap of
-      (Just (VI _)) -> return 1
-      (Just (II _)) -> return 4
-      (Just _) -> error "getTrapType: abort #1 :-("
-      Nothing -> error "getTrapType: abort #2 :-("
-
-foreign export ccall mateHandler :: CUInt -> CUInt -> CUInt -> CUInt -> IO CUInt
-mateHandler :: CUInt -> CUInt -> CUInt -> CUInt -> IO CUInt
-mateHandler eip eax ebx esp = do
-  callerAddr <- callerAddrFromStack esp
-  blah <- getTrapType eip (callerAddr - 3)
-  case blah of
-    0 -> staticCallHandler eip
-    1 -> invokeHandler eax eax esp
-    4 -> invokeHandler eax ebx esp
-    2 -> staticFieldHandler eip
-    x -> error $ "wtf: " ++ (show x)
+  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)
+        _ -> error $ "getTrapType: abort :-(" ++ (showHex eip "") ++ ", " ++ show (M.keys tmap)
 
-staticCallHandler :: CUInt -> IO CUInt
+staticCallHandler :: CPtrdiff -> IO CPtrdiff
 staticCallHandler eip = do
-  -- the actual insn to patch is displaced by two bytes
-  let insn_ptr = intPtrToPtr (fromIntegral (eip - 2)) :: Ptr CUChar
-  -- call offset is displaced by one byte
-  let imm_ptr = intPtrToPtr (fromIntegral (eip - 1)) :: Ptr CUInt
+  -- the actual insn to patch as pointer
+  let insn_ptr = intPtrToPtr (fromIntegral eip) :: Ptr CUChar
+  -- call offset is displaced by one byte (as the first byte is the opcode)
+  let imm_ptr = intPtrToPtr (fromIntegral (eip + 1)) :: Ptr CPtrdiff
   -- in codegen we set the immediate to some magic value
   -- in order to produce a SIGILL signal. we also do a safety
   -- check here, if we're really the "owner" of this signal.
   checkMe <- peek imm_ptr
-  case checkMe == 0x90ffff90 of
-    True -> do
+  if checkMe == 0x909090ff then
+    do
       entryAddr <- getMethodEntry eip 0
-      poke insn_ptr 0xe8 -- call opcode
-      -- it's a relative call, so we have to calculate the offset. why "+ 3"?
+      poke insn_ptr 0xe8 -- `call' opcode
+      -- it's a relative call, so we have to calculate the offset. why "+ 5"?
       -- (1) the whole insn is 5 bytes long
-      -- (2) begin of insn is displaced by 2 bytes
-      -- (3) offset is calculated wrt to the beginning of the next insn
-      poke imm_ptr (entryAddr - (eip + 3))
-      return (eip - 2)
-    False -> error "staticCallHandler: something is wrong here. abort\n"
+      -- (2) offset is calculated wrt to the beginning of the next insn
+      poke imm_ptr (entryAddr - (eip + 5))
+      return eip
+    else error "staticCallHandler: something is wrong here. abort\n"
 
-staticFieldHandler :: CUInt -> IO CUInt
+staticFieldHandler :: CPtrdiff -> IO CPtrdiff
 staticFieldHandler eip = do
   -- patch the offset here, first two bytes are part of the insn (opcode + reg)
-  let imm_ptr = intPtrToPtr (fromIntegral (eip + 2)) :: Ptr CUInt
+  let imm_ptr = intPtrToPtr (fromIntegral (eip + 2)) :: Ptr CPtrdiff
   checkMe <- peek imm_ptr
-  case checkMe == 0x00000000 of
-    True -> do
+  if checkMe == 0x00000000 then
+    do
       getStaticFieldAddr eip >>= poke imm_ptr
       return eip
-    False -> error "staticFieldHandler: something is wrong here. abort.\n"
+    else error "staticFieldHandler: something is wrong here. abort.\n"
 
-invokeHandler :: CUInt -> CUInt -> CUInt -> IO CUInt
-invokeHandler method_table table2patch esp = do
-  -- table2patch: note, that can be a method-table or a interface-table
-  callerAddr <- callerAddrFromStack esp
-  offset <- offsetOfCallInsn esp
-  entryAddr <- getMethodEntry (callerAddr - 3) method_table
-  let call_insn = intPtrToPtr (fromIntegral $ table2patch + (fromIntegral offset))
-  poke call_insn entryAddr
-  return entryAddr
+instanceOfMissHandler :: CPtrdiff -> B.ByteString -> IO CPtrdiff
+instanceOfMissHandler eip classname = do
+  -- first byte is going to be the opcode
+  let insn_ptr = intPtrToPtr (fromIntegral eip) :: Ptr CUChar
+  -- the next four bytes are the immediate
+  let imm_ptr = intPtrToPtr (fromIntegral (eip + 1)) :: Ptr CPtrdiff
+  checkMe <- peek imm_ptr
+  if checkMe == 0x909090ff then -- safety check...
+    do
+      mtable <- getMethodTable classname
+      poke imm_ptr (fromIntegral mtable)
+      poke insn_ptr 0xba -- `mov edx' opcode
+      return eip
+    else error "instanceOfMissHandler: something is wrong here. abort.\n"
 
+newObjectHandler :: CPtrdiff -> B.ByteString -> IO CPtrdiff
+newObjectHandler eip classname = do
+  let push_insn_ptr = intPtrToPtr (fromIntegral eip) :: Ptr CUChar
+  let push_imm_ptr = intPtrToPtr (fromIntegral (eip + 1)) :: Ptr CPtrdiff
+  let mov_imm_ptr = intPtrToPtr (fromIntegral (eip + 16)) :: Ptr CPtrdiff
+  checkMe <- peek mov_imm_ptr
+  if checkMe == 0x13371337
+    then do
+      objsize <- getObjectSize classname
+      mtable <- getMethodTable classname
+      poke push_insn_ptr 0x68 -- push_imm insn
+      poke push_imm_ptr (fromIntegral objsize)
+      poke mov_imm_ptr (fromIntegral mtable)
+      return eip
+    else error "newObjectHandler: something is wrong here. abort.\n"
 
-callerAddrFromStack :: CUInt -> IO CUInt
-callerAddrFromStack = peek . intPtrToPtr . fromIntegral
+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
 
-offsetOfCallInsn :: CUInt -> IO CUChar
-offsetOfCallInsn esp = do
-  let ret_ptr = intPtrToPtr (fromIntegral esp) :: Ptr CUInt
-  ret <- peek ret_ptr
-  peek (intPtrToPtr $ fromIntegral (ret - 1))
+  -- patch table
+  let call_insn = intPtrToPtr . fromIntegral $ table2patch + fromIntegral offset
+  poke call_insn entryAddr
+
+  -- 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"