staticcall trap: use different magic sequence
[mate.git] / Mate / X86TrapHandling.hs
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ForeignFunctionInterface #-}
4 #include "debug.h"
5 module Mate.X86TrapHandling (
6   mateHandler,
7   register_signal
8   ) where
9
10 import qualified Data.Map as M
11
12 import Foreign
13 import Foreign.C.Types
14
15 import Mate.Types
16 import {-# SOURCE #-} Mate.MethodPool
17 import Mate.ClassPool
18
19 foreign import ccall "register_signal"
20   register_signal :: IO ()
21
22 data TrapType =
23     StaticMethodCall
24   | StaticFieldAccess
25   | VirtualMethodCall Bool
26   | InterfaceMethodCall Bool
27
28 getTrapType :: TrapMap -> CPtrdiff -> CPtrdiff -> TrapType
29 getTrapType tmap signal_from from2 =
30   case M.lookup (fromIntegral signal_from) tmap of
31     (Just (StaticMethod _)) -> StaticMethodCall
32     (Just (StaticField _)) -> StaticFieldAccess
33     (Just _) -> error "getTrapMap: doesn't happen"
34     -- maybe we've a hit on the second `from' value
35     Nothing -> case M.lookup (fromIntegral from2) tmap of
36       (Just (VirtualMethod imm8 _)) -> VirtualMethodCall imm8
37       (Just (InterfaceMethod imm8 _)) -> InterfaceMethodCall imm8
38       (Just _) -> error "getTrapType: abort #1 :-("
39       Nothing -> error $ "getTrapType: abort #2 :-(" ++ show signal_from ++ ", " ++ show from2 ++ ", " ++ show tmap
40
41 foreign export ccall mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
42 mateHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> CPtrdiff -> IO CPtrdiff
43 mateHandler eip eax ebx esp = do
44   callerAddr <- callerAddrFromStack esp
45   tmap <- getTrapMap
46   case getTrapType tmap eip callerAddr of
47     StaticMethodCall  -> staticCallHandler eip
48     StaticFieldAccess -> staticFieldHandler eip
49     VirtualMethodCall imm8   -> invokeHandler eax eax esp imm8
50     InterfaceMethodCall imm8 -> invokeHandler eax ebx esp imm8
51
52 staticCallHandler :: CPtrdiff -> IO CPtrdiff
53 staticCallHandler eip = do
54   -- the actual insn to patch as pointer
55   let insn_ptr = intPtrToPtr (fromIntegral eip) :: Ptr CUChar
56   -- call offset is displaced by one byte (as the first byte is the opcode)
57   let imm_ptr = intPtrToPtr (fromIntegral (eip + 1)) :: Ptr CPtrdiff
58   -- in codegen we set the immediate to some magic value
59   -- in order to produce a SIGILL signal. we also do a safety
60   -- check here, if we're really the "owner" of this signal.
61   checkMe <- peek imm_ptr
62   if checkMe == 0x909090ff then
63     do
64       entryAddr <- getMethodEntry eip 0
65       poke insn_ptr 0xe8 -- `call' opcode
66       -- it's a relative call, so we have to calculate the offset. why "+ 5"?
67       -- (1) the whole insn is 5 bytes long
68       -- (2) offset is calculated wrt to the beginning of the next insn
69       poke imm_ptr (entryAddr - (eip + 5))
70       return eip
71     else error "staticCallHandler: something is wrong here. abort\n"
72
73 staticFieldHandler :: CPtrdiff -> IO CPtrdiff
74 staticFieldHandler eip = do
75   -- patch the offset here, first two bytes are part of the insn (opcode + reg)
76   let imm_ptr = intPtrToPtr (fromIntegral (eip + 2)) :: Ptr CPtrdiff
77   checkMe <- peek imm_ptr
78   if checkMe == 0x00000000 then
79     do
80       getStaticFieldAddr eip >>= poke imm_ptr
81       return eip
82     else error "staticFieldHandler: something is wrong here. abort.\n"
83
84 invokeHandler :: CPtrdiff -> CPtrdiff -> CPtrdiff -> Bool -> IO CPtrdiff
85 invokeHandler method_table table2patch esp imm8 = do
86   -- table2patch: note, that can be a method-table or a interface-table
87   callerAddr <- callerAddrFromStack esp
88   offset <- if imm8 then offsetOfCallInsn8 esp else offsetOfCallInsn32 esp
89   entryAddr <- getMethodEntry callerAddr method_table
90   let call_insn = intPtrToPtr (fromIntegral $ table2patch + fromIntegral offset)
91   poke call_insn entryAddr
92   return entryAddr
93
94
95 callerAddrFromStack :: CPtrdiff -> IO CPtrdiff
96 callerAddrFromStack = peek . intPtrToPtr . fromIntegral
97
98 offsetOfCallInsn8 :: CPtrdiff -> IO CPtrdiff
99 offsetOfCallInsn8 esp = do
100   let ret_ptr = intPtrToPtr (fromIntegral esp) :: Ptr CPtrdiff
101   ret <- peek ret_ptr
102   retval <- peek (intPtrToPtr (fromIntegral (ret - 1)) :: Ptr CUChar)
103   return $ fromIntegral retval
104
105 offsetOfCallInsn32 :: CPtrdiff -> IO CPtrdiff
106 offsetOfCallInsn32 esp = do
107   let ret_ptr = intPtrToPtr (fromIntegral esp) :: Ptr CPtrdiff
108   ret <- peek ret_ptr
109   peek (intPtrToPtr $ fromIntegral (ret - 4))