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