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