codegen: use label mechanism of harpy
[mate.git] / Mate / X86CodeGen.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 module Mate.X86CodeGen where
3
4 import Data.Binary
5 import Data.Int
6 import Data.List
7 import Data.Maybe
8 import qualified Data.Map as M
9 import qualified Data.ByteString.Lazy as B
10
11 import Foreign
12 import Foreign.Ptr
13 import Foreign.C.Types
14
15 import Text.Printf
16
17 import qualified JVM.Assembler as J
18 import JVM.Assembler hiding (Instruction)
19
20 import Harpy
21 import Harpy.X86Disassembler
22
23 import Mate.BasicBlocks
24
25 test_01, test_02, test_03 :: IO ()
26 test_01 = testCase "./tests/Fib.class" "fib"
27 test_02 = testCase "./tests/While.class" "f"
28 test_03 = testCase "./tests/While.class" "g"
29
30 testCase :: String -> B.ByteString -> IO ()
31 testCase cf method = do
32       hmap <- parseMethod cf method
33       printMapBB hmap
34       case hmap of
35         Nothing -> putStrLn "sorry, no code generation"
36         Just hmap -> do
37               let ebb = emitFromBB hmap
38               (_, Right ((entry, bbstarts), disasm)) <- runCodeGen ebb () ()
39               let int_entry = ((fromIntegral $ ptrToIntPtr entry) :: Int)
40               printf "disasm:\n"
41               mapM_ (putStrLn . showAtt) disasm
42               printf "basicblocks addresses:\n"
43               let b = map (\(x,y) -> (x,y + int_entry)) $ M.toList bbstarts
44               mapM_ (\(x,y) -> printf "\tBasicBlock %2d starts at 0x%08x\n" x y) b
45
46 type EntryPoint = Ptr Word8
47 type EntryPointOffset = Int
48 type PatchInfo = (BlockID, EntryPointOffset)
49
50 type BBStarts = M.Map BlockID Int
51
52 type CompileInfo = (EntryPoint, BBStarts)
53
54 emitFromBB :: MapBB -> CodeGen e s (CompileInfo, [Instruction])
55 emitFromBB hmap =  do
56         llmap <- sequence [newNamedLabel ("bb_" ++ show x) | (x,_) <- M.toList hmap]
57         let lmap = zip (Prelude.fst $ unzip $ M.toList hmap) llmap
58         ep <- getEntryPoint
59         push ebp
60         mov ebp esp
61         bbstarts <- efBB (0,(hmap M.! 0)) M.empty lmap
62         mov esp ebp
63         pop ebp
64         ret
65         d <- disassemble
66         return ((ep, bbstarts), d)
67   where
68   getLabel :: BlockID -> [(BlockID, Label)] -> Label
69   getLabel _ [] = error "label not found!"
70   getLabel i ((x,l):xs) = if i==x then l else getLabel i xs
71
72   efBB :: (BlockID, BasicBlock) -> BBStarts -> [(BlockID, Label)] -> CodeGen e s (BBStarts)
73   efBB (bid, bb) bbstarts lmap =
74         if M.member bid bbstarts then
75           return bbstarts
76         else do
77           bb_offset <- getCodeOffset
78           let bbstarts' = M.insert bid bb_offset bbstarts
79           defineLabel $ getLabel bid lmap
80           mapM emit $ code bb
81           case successor bb of
82             Return -> return bbstarts'
83             OneTarget t -> do
84               efBB (t, hmap M.! t) bbstarts' lmap
85             TwoTarget t1 t2 -> do
86               bbstarts'' <- efBB (t1, hmap M.! t1) bbstarts' lmap
87               efBB (t2, hmap M.! t2) bbstarts'' lmap
88     -- TODO(bernhard): also use metainformation
89     -- TODO(bernhard): implement `emit' as function which accepts a list of
90     --                 instructions, so we can use patterns for optimizations
91     where
92     emit :: J.Instruction -> CodeGen e s ()
93     emit (ICONST_1) = push (1 :: Word32)
94     emit (ICONST_2) = push (2 :: Word32)
95     emit (ILOAD_ x) = do
96         push (Disp (cArgs_ x), ebp)
97     emit (ISTORE_ x) = do
98         pop eax
99         mov (Disp (cArgs_ x), ebp) eax
100     emit IADD = do pop ebx; pop eax; add eax ebx; push eax
101     emit ISUB = do pop ebx; pop eax; sub eax ebx; push eax
102     emit (IINC x imm) = do
103         add (Disp (cArgs x), ebp) (s8_w32 imm)
104
105     emit (IF_ICMP cond _) = do
106         pop eax -- value2
107         pop ebx -- value1
108         cmp eax ebx -- intel syntax is swapped (TODO(bernhard): test that plz)
109         let sid = case successor bb of TwoTarget _ t -> t
110         let l = getLabel sid lmap
111         case cond of
112           C_EQ -> je  l; C_NE -> jne l
113           C_LT -> jl  l; C_GT -> jg  l
114           C_GE -> jge l; C_LE -> jle l
115
116     emit (IF cond _) = do
117         pop eax -- value1
118         cmp eax (0 :: Word32) -- TODO(bernhard): test that plz
119         let sid = case successor bb of TwoTarget _ t -> t
120         let l = getLabel sid lmap
121         case cond of
122           C_EQ -> je  l; C_NE -> jne l
123           C_LT -> jl  l; C_GT -> jg  l
124           C_GE -> jge l; C_LE -> jle l
125
126     emit (GOTO _ ) = do
127         let sid = case successor bb of OneTarget t -> t
128         jmp $ getLabel sid lmap
129
130     emit IRETURN = do pop eax
131     emit _ = do cmovbe eax eax -- dummy
132
133   cArgs x = (8 + 4 * (fromIntegral x))
134   cArgs_ x = (8 + 4 * case x of I0 -> 0; I1 -> 1; I2 -> 2; I3 -> 3)
135
136   -- sign extension from w8 to w32 (over s8)
137   --   unfortunately, hs-java is using Word8 everywhere (while
138   --   it should be Int8 actually)
139   s8_w32 :: Word8 -> Word32
140   s8_w32 w8 = fromIntegral s8
141     where s8 = (fromIntegral w8) :: Int8