methodPool: compile methods on-demand
[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 qualified Data.Map as M
8 import qualified Data.ByteString.Lazy as B
9
10 import Foreign
11 import Foreign.C.Types
12
13 import Text.Printf
14
15 import qualified JVM.Assembler as J
16 import JVM.Assembler hiding (Instruction)
17 import JVM.Converter
18
19 import Harpy
20 import Harpy.X86Disassembler
21
22 import Mate.BasicBlocks
23
24 foreign import ccall "dynamic"
25    code_int :: FunPtr (CInt -> CInt -> IO CInt) -> (CInt -> CInt -> IO CInt)
26
27 foreign import ccall "getaddr"
28   getaddr :: CUInt
29
30 foreign import ccall "callertrap"
31   callertrap :: IO ()
32
33 foreign import ccall "register_signal"
34   register_signal :: IO ()
35
36 test_01, test_02, test_03 :: IO ()
37 test_01 = do
38   register_signal
39   (entry, end) <- testCase "./tests/Fib.class" "fib"
40   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
41
42   mapM_ (\x -> do
43     result <- code_int entryFuncPtr x 0
44     let iresult :: Int; iresult = fromIntegral result
45     let kk :: String; kk = if iresult == (fib x) then "OK" else "FAIL (" ++ (show (fib x)) ++ ")"
46     printf "result of fib(%2d): %3d\t\t%s\n" (fromIntegral x :: Int) iresult kk
47     ) $ ([0..10] :: [CInt])
48   printf "patched disasm:\n"
49   Right newdisasm <- disassembleBlock entry end
50   mapM_ (putStrLn . showAtt) newdisasm
51   where
52     fib :: CInt -> Int
53     fib n
54       | n <= 1 = 1
55       | otherwise = (fib (n - 1)) + (fib (n - 2))
56
57
58 test_02 = do
59   (entry,_) <- testCase "./tests/While.class" "f"
60   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
61   result <- code_int entryFuncPtr 5 4
62   let iresult :: Int; iresult = fromIntegral result
63   let kk :: String; kk = if iresult == 15 then "OK" else "FAIL"
64   printf "result of f(5,4): %3d\t\t%s\n" iresult kk
65
66   result2 <- code_int entryFuncPtr 4 3
67   let iresult2 :: Int; iresult2 = fromIntegral result2
68   let kk2 :: String; kk2 = if iresult2 == 10 then "OK" else "FAIL"
69   printf "result of f(4,3): %3d\t\t%s\n" iresult2 kk2
70
71
72 test_03 = do
73   (entry,_) <- testCase "./tests/While.class" "g"
74   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
75   result <- code_int entryFuncPtr 5 4
76   let iresult :: Int; iresult = fromIntegral result
77   let kk :: String; kk = if iresult == 15 then "OK" else "FAIL"
78   printf "result of g(5,4): %3d\t\t%s\n" iresult kk
79
80   result2 <- code_int entryFuncPtr 4 3
81   let iresult2 :: Int; iresult2 = fromIntegral result2
82   let kk2 :: String; kk2 = if iresult2 == 10 then "OK" else "FAIL"
83   printf "result of g(4,3): %3d\t\t%s\n" iresult2 kk2
84
85
86 testCase :: String -> B.ByteString -> IO (Ptr Word8, Int)
87 testCase cf method = do
88       cls <- parseClassFile cf
89       hmap <- parseMethod cls 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         bbstarts <- efBB (0,(hmap M.! 0)) M.empty lmap
121         d <- disassemble
122         end <- getCodeOffset
123         return ((ep, bbstarts, end), d)
124   where
125   getLabel :: BlockID -> [(BlockID, Label)] -> Label
126   getLabel _ [] = error "label not found!"
127   getLabel i ((x,l):xs) = if i==x then l else getLabel i xs
128
129   efBB :: (BlockID, BasicBlock) -> BBStarts -> [(BlockID, Label)] -> CodeGen e s (BBStarts)
130   efBB (bid, bb) bbstarts lmap =
131         if M.member bid bbstarts then
132           return bbstarts
133         else do
134           bb_offset <- getCodeOffset
135           let bbstarts' = M.insert bid bb_offset bbstarts
136           defineLabel $ getLabel bid lmap
137           mapM_ emit $ code bb
138           case successor bb of
139             Return -> return bbstarts'
140             OneTarget t -> do
141               efBB (t, hmap M.! t) bbstarts' lmap
142             TwoTarget t1 t2 -> do
143               bbstarts'' <- efBB (t1, hmap M.! t1) bbstarts' lmap
144               efBB (t2, hmap M.! t2) bbstarts'' lmap
145     -- TODO(bernhard): also use metainformation
146     -- TODO(bernhard): implement `emit' as function which accepts a list of
147     --                 instructions, so we can use patterns for optimizations
148     where
149     emit :: J.Instruction -> CodeGen e s ()
150     emit POP = do -- print dropped value
151         ep <- getEntryPoint
152         let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
153         -- '5' is the size of the `call' instruction ( + immediate)
154         calladdr <- getCodeOffset
155         let w32_calladdr = 5 + w32_ep + (fromIntegral calladdr) :: Word32
156         let trapaddr = (fromIntegral getaddr :: Word32)
157         call (trapaddr - w32_calladdr)
158     emit (BIPUSH val) = push ((fromIntegral val) :: Word32)
159     emit (ICONST_1) = push (1 :: Word32)
160     emit (ICONST_2) = push (2 :: Word32)
161     emit (ICONST_5) = push (5 :: 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; _ -> error "bad"
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; _ -> error "bad"
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; _ -> error "bad"
195         jmp $ getLabel sid lmap
196     emit (INVOKESTATIC _) = 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 RETURN = do mov esp ebp; pop ebp; ret
206     emit IRETURN = do
207         pop eax
208         mov esp ebp
209         pop ebp
210         ret
211     emit _ = do cmovbe eax eax -- dummy
212
213   cArgs x = (8 + 4 * (fromIntegral x))
214   cArgs_ x = (8 + 4 * case x of I0 -> 0; I1 -> 1; I2 -> 2; I3 -> 3)
215
216   -- sign extension from w8 to w32 (over s8)
217   --   unfortunately, hs-java is using Word8 everywhere (while
218   --   it should be Int8 actually)
219   s8_w32 :: Word8 -> Word32
220   s8_w32 w8 = fromIntegral s8
221     where s8 = (fromIntegral w8) :: Int8