patching: define patcher in X86CodeGen itself where possible
[mate.git] / Mate / X86TrapHandling.hs
index 1a571a39dd2f6eabee17131e99aa16bb231cc8e7..ecf346a2771e7249525ffadfd9d36a1ecd528efb 100644 (file)
@@ -1,7 +1,5 @@
-{-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
-#include "debug.h"
 module Mate.X86TrapHandling (
   mateHandler,
   register_signal
@@ -22,9 +20,6 @@ import {-# SOURCE #-} Mate.MethodPool
 import Mate.ClassPool
 import Mate.X86CodeGen
 
-#ifdef DBG_JIT
-import Text.Printf
-#endif
 import Mate.Debug
 import Harpy.X86Disassembler
 
@@ -35,19 +30,36 @@ foreign export ccall mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff
 mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
 mateHandler reip reax rebx resi = do
   tmap <- getTrapMap
-  case M.lookup (fromIntegral reip) tmap of
-    (Just (StaticMethod _)) -> patchWithHarpy patchStaticCall reip
-    (Just (StaticField _))  -> staticFieldHandler reip
-    (Just (InstanceOf cn))  -> patchWithHarpy (`patchInstanceOf` cn) reip
-    (Just (NewObject cn))   -> patchWithHarpy (`patchNewObject` cn) reip
-    (Just (VirtualCall False _ io_offset)) ->
-          patchWithHarpy (patchInvoke reax reax io_offset) reip
-    (Just (VirtualCall True  _ io_offset)) ->
-          patchWithHarpy (patchInvoke rebx reax io_offset) reip
+  let reipw32 = fromIntegral reip
+  (deleteMe, ret_nreip) <- case M.lookup reipw32 tmap of
+    (Just (StaticMethod patcher)) ->
+        patchWithHarpy patcher reip >>= delTrue
+    (Just (StaticField _))  ->
+        staticFieldHandler reip >>= delTrue
+    (Just (ObjectField patcher)) ->
+        patchWithHarpy patcher reip >>= delTrue
+    (Just (InstanceOf cn))  ->
+        patchWithHarpy (`patchInstanceOf` cn) reip >>= delFalse
+    (Just (NewObject patcher))   ->
+        patchWithHarpy patcher reip >>= delTrue
+    (Just (VirtualCall False mi io_offset)) ->
+        patchWithHarpy (patchInvoke mi reax reax io_offset) reip
+        >>= delTrue
+    (Just (VirtualCall True  mi io_offset)) ->
+        patchWithHarpy (patchInvoke mi rebx reax io_offset) reip
+        >>= delTrue
     Nothing -> case resi of
-        0x13371234 -> return (-1)
+        0x13371234 -> return (-1) >>= delFalse
         _ -> error $ "getTrapType: abort :-( " ++ (showHex reip ". ")
              ++ (concatMap (`showHex` ", ") (M.keys tmap))
+  if deleteMe
+    then setTrapMap $ M.delete reipw32 tmap
+    else return ()
+  return ret_nreip
+  where
+    delTrue = (\nreip -> return (False, nreip)) -- TODO: FIXME
+    delFalse = (\nreip -> return (False, nreip))
+
 
 patchWithHarpy :: (CPtrdiff -> CodeGen () () CPtrdiff) -> CPtrdiff -> IO CPtrdiff
 patchWithHarpy patcher reip = do
@@ -57,7 +69,9 @@ patchWithHarpy patcher reip = do
   let entry = Just (intPtrToPtr (fromIntegral reip), fixme)
   let cgconfig = defaultCodeGenConfig { customCodeBuffer = entry }
   (_, Right right) <- runCodeGenWithConfig (withDisasm $ patcher reip) () () cgconfig
-  mapM_ (printfJit "patched: %s\n" . showAtt) $ snd right
+  if mateDEBUG
+    then mapM_ (printfJit . printf "patched: %s\n" . showAtt) $ snd right
+    else return ()
   return reip
 
 withDisasm :: CodeGen e s CPtrdiff -> CodeGen e s (CPtrdiff, [Instruction])
@@ -66,13 +80,6 @@ withDisasm patcher = do
   d <- disassemble
   return (reip, d)
 
-patchStaticCall :: CPtrdiff -> CodeGen e s CPtrdiff
-patchStaticCall reip = do
-  entryAddr <- liftIO $ getMethodEntry reip 0
-  call (fromIntegral (entryAddr - (reip + 5)) :: NativeWord)
-  return reip
-
-
 staticFieldHandler :: CPtrdiff -> IO CPtrdiff
 staticFieldHandler reip = do
   -- patch the offset here, first two bytes are part of the insn (opcode + reg)
@@ -90,19 +97,12 @@ patchInstanceOf reip classname = do
   mov edx mtable
   return reip
 
-patchNewObject :: CPtrdiff -> B.ByteString -> CodeGen e s CPtrdiff
-patchNewObject reip classname = do
-  objsize <- liftIO $ getObjectSize classname
-  push32 objsize
-  callMalloc
-  mtable <- liftIO $ getMethodTable classname
-  mov (Disp 0, eax) mtable
-  return reip
-
-patchInvoke :: CPtrdiff -> CPtrdiff -> IO NativeWord -> CPtrdiff -> CodeGen e s CPtrdiff
-patchInvoke method_table table2patch io_offset reip = do
+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 reip method_table
+  entryAddr <- liftIO $ getMethodEntry newmi
   call32_eax (Disp offset)
   -- patch entry in table
   let call_insn = intPtrToPtr . fromIntegral $ table2patch + fromIntegral offset