codegen: handle exceptions of a method
[mate.git] / Mate / X86TrapHandling.hs
index e41c1adef50975d9a76159cfbec1cd63cfb625cc..82ed7ca0d738ca3ad52b1a0f23562ac8ae0e9597 100644 (file)
@@ -1,7 +1,5 @@
-{-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
-#include "debug.h"
 module Mate.X86TrapHandling (
   mateHandler,
   register_signal
@@ -9,116 +7,96 @@ module Mate.X86TrapHandling (
 
 import Numeric
 import qualified Data.Map as M
-import qualified Data.ByteString.Lazy as B
+import Control.Monad
 
 import Foreign
 import Foreign.C.Types
 
+import Harpy hiding (fst)
+
 import Mate.Types
 import Mate.NativeSizes
 import {-# SOURCE #-} Mate.MethodPool
 import Mate.ClassPool
+import Mate.X86CodeGen
+
+import Mate.Debug
+import Harpy.X86Disassembler
 
 foreign import ccall "register_signal"
   register_signal :: IO ()
 
-foreign export ccall mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
-mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
-mateHandler eip eax ebx esi = do
+foreign export ccall mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
+mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
+mateHandler reip reax rebx resi resp = do
   tmap <- getTrapMap
-  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)
+  let reipw32 = fromIntegral reip
+  (deleteMe, ret_nreip) <- case M.lookup reipw32 tmap of
+    (Just (StaticMethod patcher)) ->
+        patchWithHarpy patcher reip >>= delFalse
+    (Just (StaticField _))  ->
+        staticFieldHandler reip >>= delTrue
+    (Just (ObjectField patcher)) ->
+        patchWithHarpy patcher reip >>= delTrue
+    (Just (InstanceOf patcher))  ->
+        patchWithHarpy (patcher reax) reip >>= delFalse
+    (Just (ThrowException patcher)) ->
+        patchWithHarpy (patcher reax resp) reip >>= delFalse
+    (Just (NewObject patcher))   ->
+        patchWithHarpy patcher reip >>= delTrue
+    (Just (VirtualCall False mi io_offset)) ->
+        patchWithHarpy (patchInvoke mi reax reax io_offset) reip
+        >>= delFalse
+    (Just (VirtualCall True  mi io_offset)) ->
+        patchWithHarpy (patchInvoke mi rebx reax io_offset) reip
+        >>= delFalse
+    Nothing -> case resi of
+        0x13371234 -> delFalse (-1)
+        _ -> error $ "getTrapType: abort :-( eip: "
+             ++ showHex reip ". " ++ concatMap (`showHex` ", ") (M.keys tmap)
+  when deleteMe $ setTrapMap $ M.delete reipw32 tmap
+  return ret_nreip
+    where
+      delTrue x = return (True,x)
+      delFalse x = return (False,x)
 
-staticCallHandler :: CPtrdiff -> IO CPtrdiff
-staticCallHandler eip = do
-  -- 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
-  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 "+ 5"?
-      -- (1) the whole insn is 5 bytes long
-      -- (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"
+
+patchWithHarpy :: (CPtrdiff -> CodeGen () () CPtrdiff) -> CPtrdiff -> IO CPtrdiff
+patchWithHarpy patcher reip = do
+  -- this is just an upperbound. if the value is to low, patching fails. find
+  -- something better?
+  let fixme = 1024
+  let entry = Just (intPtrToPtr (fromIntegral reip), fixme)
+  let cgconfig = defaultCodeGenConfig { customCodeBuffer = entry }
+  (_, Right right) <- runCodeGenWithConfig (withDisasm $ patcher reip) () () cgconfig
+  when mateDEBUG $ mapM_ (printfJit . printf "patched: %s\n" . showIntel) $ snd right
+  return $ fst right
+
+withDisasm :: CodeGen e s CPtrdiff -> CodeGen e s (CPtrdiff, [Instruction])
+withDisasm patcher = do
+  reip <- patcher
+  d <- disassemble
+  return (reip, d)
 
 staticFieldHandler :: CPtrdiff -> IO CPtrdiff
-staticFieldHandler eip = do
+staticFieldHandler reip = do
   -- patch the offset here, first two bytes are part of the insn (opcode + reg)
-  let imm_ptr = intPtrToPtr (fromIntegral (eip + 2)) :: Ptr CPtrdiff
+  let imm_ptr = intPtrToPtr (fromIntegral (reip + 2)) :: Ptr CPtrdiff
   checkMe <- peek imm_ptr
   if checkMe == 0x00000000 then
     do
-      getStaticFieldAddr eip >>= poke imm_ptr
-      return eip
+      getStaticFieldAddr reip >>= poke imm_ptr
+      return reip
     else error "staticFieldHandler: something is wrong here. abort.\n"
 
-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"
-
-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
+patchInvoke :: MethodInfo -> CPtrdiff -> CPtrdiff -> IO NativeWord -> CPtrdiff -> CodeGen e s CPtrdiff
+patchInvoke (MethodInfo methname _ msig)  method_table table2patch io_offset reip = do
+  vmap <- liftIO getVirtualMap
+  let newmi = MethodInfo methname (vmap M.! fromIntegral method_table) msig
+  offset <- liftIO io_offset
+  (entryAddr, _) <- liftIO $ getMethodEntry newmi
+  call32Eax (Disp offset)
+  -- patch entry in 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"
+  liftIO $ poke call_insn entryAddr
+  return reip