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