debug: show disasm in intel syntax
[mate.git] / Mate / X86TrapHandling.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE ForeignFunctionInterface #-}
3 module Mate.X86TrapHandling (
4   mateHandler,
5   register_signal
6   ) where
7
8 import Numeric
9 import qualified Data.Map as M
10 import Control.Monad
11
12 import Foreign
13 import Foreign.C.Types
14
15 import Harpy hiding (fst)
16
17 import Mate.Types
18 import Mate.NativeSizes
19 import {-# SOURCE #-} Mate.MethodPool
20 import Mate.ClassPool
21 import Mate.X86CodeGen
22
23 import Mate.Debug
24 import Harpy.X86Disassembler
25
26 foreign import ccall "register_signal"
27   register_signal :: IO ()
28
29 foreign export ccall mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
30 mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
31 mateHandler reip reax rebx resi = do
32   tmap <- getTrapMap
33   let reipw32 = fromIntegral reip
34   (deleteMe, ret_nreip) <- case M.lookup reipw32 tmap of
35     (Just (StaticMethod patcher)) ->
36         patchWithHarpy patcher reip >>= delFalse
37     (Just (StaticField _))  ->
38         staticFieldHandler reip >>= delTrue
39     (Just (ObjectField patcher)) ->
40         patchWithHarpy patcher reip >>= delTrue
41     (Just (InstanceOf patcher))  ->
42         patchWithHarpy (patcher reax) reip >>= delFalse
43     (Just (NewObject patcher))   ->
44         patchWithHarpy patcher reip >>= delTrue
45     (Just (VirtualCall False mi io_offset)) ->
46         patchWithHarpy (patchInvoke mi reax reax io_offset) reip
47         >>= delFalse
48     (Just (VirtualCall True  mi io_offset)) ->
49         patchWithHarpy (patchInvoke mi rebx reax io_offset) reip
50         >>= delFalse
51     Nothing -> case resi of
52         0x13371234 -> delFalse (-1)
53         _ -> error $ "getTrapType: abort :-( " ++ showHex reip ". "
54              ++ concatMap (`showHex` ", ") (M.keys tmap)
55   when deleteMe $ setTrapMap $ M.delete reipw32 tmap
56   return ret_nreip
57     where
58       delTrue x = return (True,x)
59       delFalse x = return (False,x)
60
61
62 patchWithHarpy :: (CPtrdiff -> CodeGen () () CPtrdiff) -> CPtrdiff -> IO CPtrdiff
63 patchWithHarpy patcher reip = do
64   -- this is just an upperbound. if the value is to low, patching fails. find
65   -- something better?
66   let fixme = 1024
67   let entry = Just (intPtrToPtr (fromIntegral reip), fixme)
68   let cgconfig = defaultCodeGenConfig { customCodeBuffer = entry }
69   (_, Right right) <- runCodeGenWithConfig (withDisasm $ patcher reip) () () cgconfig
70   when mateDEBUG $ mapM_ (printfJit . printf "patched: %s\n" . showIntel) $ snd right
71   return $ fst right
72
73 withDisasm :: CodeGen e s CPtrdiff -> CodeGen e s (CPtrdiff, [Instruction])
74 withDisasm patcher = do
75   reip <- patcher
76   d <- disassemble
77   return (reip, d)
78
79 staticFieldHandler :: CPtrdiff -> IO CPtrdiff
80 staticFieldHandler reip = do
81   -- patch the offset here, first two bytes are part of the insn (opcode + reg)
82   let imm_ptr = intPtrToPtr (fromIntegral (reip + 2)) :: Ptr CPtrdiff
83   checkMe <- peek imm_ptr
84   if checkMe == 0x00000000 then
85     do
86       getStaticFieldAddr reip >>= poke imm_ptr
87       return reip
88     else error "staticFieldHandler: something is wrong here. abort.\n"
89
90 patchInvoke :: MethodInfo -> CPtrdiff -> CPtrdiff -> IO NativeWord -> CPtrdiff -> CodeGen e s CPtrdiff
91 patchInvoke (MethodInfo methname _ msig)  method_table table2patch io_offset reip = do
92   vmap <- liftIO getVirtualMap
93   let newmi = MethodInfo methname (vmap M.! fromIntegral method_table) msig
94   offset <- liftIO io_offset
95   entryAddr <- liftIO $ getMethodEntry newmi
96   call32Eax (Disp offset)
97   -- patch entry in table
98   let call_insn = intPtrToPtr . fromIntegral $ table2patch + fromIntegral offset
99   liftIO $ poke call_insn entryAddr
100   return reip