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