codegen: patch method calls on-demand via traps
[mate.git] / Mate / X86CodeGen.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE ForeignFunctionInterface #-}
3 module Mate.X86CodeGen where
4
5 import Data.Binary
6 import Data.Int
7 import Data.List
8 import Data.Maybe
9 import qualified Data.Map as M
10 import qualified Data.ByteString.Lazy as B
11
12 import Foreign
13 import Foreign.Ptr
14 import Foreign.C.Types
15
16 import Text.Printf
17
18 import qualified JVM.Assembler as J
19 import JVM.Assembler hiding (Instruction)
20
21 import Harpy
22 import Harpy.X86Disassembler
23
24 import Mate.BasicBlocks
25
26 foreign import ccall "dynamic"
27    code_int :: FunPtr (CInt -> CInt -> IO CInt) -> (CInt -> CInt -> IO CInt)
28
29 foreign import ccall "getaddr"
30   getaddr :: CUInt
31
32 foreign import ccall "callertrap"
33   callertrap :: IO ()
34
35 foreign import ccall "register_signal"
36   register_signal :: IO ()
37
38 test_01, test_02, test_03 :: IO ()
39 test_01 = do
40   register_signal
41   (entry, end) <- testCase "./tests/Fib.class" "fib"
42   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
43
44   mapM_ (\(x,entryFuncPtr) -> do
45     result <- code_int entryFuncPtr (fromIntegral x) (fromIntegral 0)
46     let iresult :: Int; iresult = fromIntegral result
47     let kk :: String; kk = if iresult == (fib x) then "OK" else "FAIL (" ++ (show (fib x)) ++ ")"
48     printf "result of fib(%2d): %3d\t\t%s\n" x iresult kk
49     ) $ zip ([0..10] :: [Int]) (repeat entryFuncPtr)
50   printf "patched disasm:\n"
51   Right newdisasm <- disassembleBlock entry end
52   mapM_ (putStrLn . showAtt) newdisasm
53   where
54     fib n
55       | n <= 1 = 1
56       | otherwise = (fib (n - 1)) + (fib (n - 2))
57
58
59 test_02 = do
60   (entry,_) <- testCase "./tests/While.class" "f"
61   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
62   result <- code_int entryFuncPtr (fromIntegral 5) (fromIntegral 4)
63   let iresult :: Int; iresult = fromIntegral result
64   let kk :: String; kk = if iresult == 15 then "OK" else "FAIL"
65   printf "result of f(5,4): %3d\t\t%s\n" iresult kk
66
67   result <- code_int entryFuncPtr (fromIntegral 4) (fromIntegral 3)
68   let iresult :: Int; iresult = fromIntegral result
69   let kk :: String; kk = if iresult == 10 then "OK" else "FAIL"
70   printf "result of f(4,3): %3d\t\t%s\n" iresult kk
71
72
73 test_03 = do
74   (entry,_) <- testCase "./tests/While.class" "g"
75   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
76   result <- code_int entryFuncPtr (fromIntegral 5) (fromIntegral 4)
77   let iresult :: Int; iresult = fromIntegral result
78   let kk :: String; kk = if iresult == 15 then "OK" else "FAIL"
79   printf "result of g(5,4): %3d\t\t%s\n" iresult kk
80
81   result <- code_int entryFuncPtr (fromIntegral 4) (fromIntegral 3)
82   let iresult :: Int; iresult = fromIntegral result
83   let kk :: String; kk = if iresult == 10 then "OK" else "FAIL"
84   printf "result of g(4,3): %3d\t\t%s\n" iresult kk
85
86
87 testCase :: String -> B.ByteString -> IO (Ptr Word8, Int)
88 testCase cf method = do
89       hmap <- parseMethod cf method
90       printMapBB hmap
91       case hmap of
92         Nothing -> error "sorry, no code generation"
93         Just hmap -> do
94               let ebb = emitFromBB hmap
95               (_, Right ((entry, bbstarts, end), disasm)) <- runCodeGen ebb () ()
96               let int_entry = ((fromIntegral $ ptrToIntPtr entry) :: Int)
97               printf "disasm:\n"
98               mapM_ (putStrLn . showAtt) disasm
99               printf "basicblocks addresses:\n"
100               let b = map (\(x,y) -> (x,y + int_entry)) $ M.toList bbstarts
101               mapM_ (\(x,y) -> printf "\tBasicBlock %2d starts at 0x%08x\n" x y) b
102               return (entry, end)
103
104 type EntryPoint = Ptr Word8
105 type EntryPointOffset = Int
106 type PatchInfo = (BlockID, EntryPointOffset)
107
108 type BBStarts = M.Map BlockID Int
109
110 type CompileInfo = (EntryPoint, BBStarts, Int)
111
112 emitFromBB :: MapBB -> CodeGen e s (CompileInfo, [Instruction])
113 emitFromBB hmap =  do
114         llmap <- sequence [newNamedLabel ("bb_" ++ show x) | (x,_) <- M.toList hmap]
115         let lmap = zip (Prelude.fst $ unzip $ M.toList hmap) llmap
116         ep <- getEntryPoint
117         push ebp
118         mov ebp esp
119
120         -- TODO(bernhard): remove me. just for PoC here
121         ep <- getEntryPoint
122         let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
123         push w32_ep
124         -- '5' is the size of the `call' instruction ( + immediate)
125         calladdr <- getCodeOffset
126         let w32_calladdr = 5 + w32_ep + (fromIntegral calladdr) :: Word32
127         let trapaddr = (fromIntegral getaddr :: Word32)
128         call (trapaddr - w32_calladdr)
129
130         bbstarts <- efBB (0,(hmap M.! 0)) M.empty lmap
131         d <- disassemble
132         end <- getCodeOffset
133         return ((ep, bbstarts, end), d)
134   where
135   getLabel :: BlockID -> [(BlockID, Label)] -> Label
136   getLabel _ [] = error "label not found!"
137   getLabel i ((x,l):xs) = if i==x then l else getLabel i xs
138
139   efBB :: (BlockID, BasicBlock) -> BBStarts -> [(BlockID, Label)] -> CodeGen e s (BBStarts)
140   efBB (bid, bb) bbstarts lmap =
141         if M.member bid bbstarts then
142           return bbstarts
143         else do
144           bb_offset <- getCodeOffset
145           let bbstarts' = M.insert bid bb_offset bbstarts
146           defineLabel $ getLabel bid lmap
147           mapM emit $ code bb
148           case successor bb of
149             Return -> return bbstarts'
150             OneTarget t -> do
151               efBB (t, hmap M.! t) bbstarts' lmap
152             TwoTarget t1 t2 -> do
153               bbstarts'' <- efBB (t1, hmap M.! t1) bbstarts' lmap
154               efBB (t2, hmap M.! t2) bbstarts'' lmap
155     -- TODO(bernhard): also use metainformation
156     -- TODO(bernhard): implement `emit' as function which accepts a list of
157     --                 instructions, so we can use patterns for optimizations
158     where
159     emit :: J.Instruction -> CodeGen e s ()
160     emit (ICONST_1) = push (1 :: Word32)
161     emit (ICONST_2) = push (2 :: Word32)
162     emit (ILOAD_ x) = do
163         push (Disp (cArgs_ x), ebp)
164     emit (ISTORE_ x) = do
165         pop eax
166         mov (Disp (cArgs_ x), ebp) eax
167     emit IADD = do pop ebx; pop eax; add eax ebx; push eax
168     emit ISUB = do pop ebx; pop eax; sub eax ebx; push eax
169     emit (IINC x imm) = do
170         add (Disp (cArgs x), ebp) (s8_w32 imm)
171
172     emit (IF_ICMP cond _) = do
173         pop eax -- value2
174         pop ebx -- value1
175         cmp ebx eax -- intel syntax is swapped (TODO(bernhard): test that plz)
176         let sid = case successor bb of TwoTarget _ t -> t
177         let l = getLabel sid lmap
178         case cond of
179           C_EQ -> je  l; C_NE -> jne l
180           C_LT -> jl  l; C_GT -> jg  l
181           C_GE -> jge l; C_LE -> jle l
182
183     emit (IF cond _) = do
184         pop eax -- value1
185         cmp eax (0 :: Word32) -- TODO(bernhard): test that plz
186         let sid = case successor bb of TwoTarget _ t -> t
187         let l = getLabel sid lmap
188         case cond of
189           C_EQ -> je  l; C_NE -> jne l
190           C_LT -> jl  l; C_GT -> jg  l
191           C_GE -> jge l; C_LE -> jle l
192
193     emit (GOTO _ ) = do
194         let sid = case successor bb of OneTarget t -> t
195         jmp $ getLabel sid lmap
196     emit (INVOKESTATIC x) = do
197         -- TODO(bernhard): get and save information about this call
198         -- TODO(bernhard): better try SIGILL instead of SIGSEGV?
199         mov (Addr 0) eax
200         -- discard arguments (TODO(bernhard): don't hardcode it)
201         add esp (4 :: Word32)
202         -- push result on stack (TODO(bernhard): if any)
203         push eax
204
205     emit IRETURN = do
206         pop eax
207         mov esp ebp
208         pop ebp
209         ret
210     emit _ = do cmovbe eax eax -- dummy
211
212   cArgs x = (8 + 4 * (fromIntegral x))
213   cArgs_ x = (8 + 4 * case x of I0 -> 0; I1 -> 1; I2 -> 2; I3 -> 3)
214
215   -- sign extension from w8 to w32 (over s8)
216   --   unfortunately, hs-java is using Word8 everywhere (while
217   --   it should be Int8 actually)
218   s8_w32 :: Word8 -> Word32
219   s8_w32 w8 = fromIntegral s8
220     where s8 = (fromIntegral w8) :: Int8