codegen: eliminate code duplication
[mate.git] / Mate / X86CodeGen.hs
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ForeignFunctionInterface #-}
4 #include "debug.h"
5 module Mate.X86CodeGen where
6
7 import Prelude hiding (and, div)
8 import Data.Binary
9 import Data.BinaryState
10 import Data.Int
11 import Data.Maybe
12 import qualified Data.Map as M
13 import qualified Data.Set as S
14 import qualified Data.ByteString.Lazy as B
15 import Control.Monad
16
17 import Foreign hiding (xor)
18 import Foreign.C.Types
19
20 import qualified JVM.Assembler as J
21 import JVM.Assembler hiding (Instruction)
22 import JVM.ClassFile
23
24 import Harpy
25 import Harpy.X86Disassembler
26
27 import Mate.BasicBlocks
28 import Mate.Types
29 import Mate.Utilities
30 import Mate.ClassPool
31 import Mate.Strings
32 #ifdef DEBUG
33 import Text.Printf
34 #endif
35
36
37 foreign import ccall "&mallocObject"
38   mallocObjectAddr :: FunPtr (Int -> IO CUInt)
39
40 type EntryPoint = Ptr Word8
41 type EntryPointOffset = Int
42 type PatchInfo = (BlockID, EntryPointOffset)
43
44 type BBStarts = M.Map BlockID Int
45
46 type CompileInfo = (EntryPoint, BBStarts, Int, TrapMap)
47
48
49 emitFromBB :: B.ByteString -> MethodSignature -> Class Direct -> MapBB -> CodeGen e s (CompileInfo, [Instruction])
50 emitFromBB method sig cls hmap =  do
51         llmap <- sequence [newNamedLabel ("bb_" ++ show x) | (x,_) <- M.toList hmap]
52         let lmap = zip (Prelude.fst $ unzip $ M.toList hmap) llmap
53         ep <- getEntryPoint
54         push ebp
55         mov ebp esp
56         -- TODO(bernhard): determine a reasonable value.
57         --                 e.g. (locals used) * 4
58         sub esp (0x60 :: Word32)
59
60         (calls, bbstarts) <- efBB (0, hmap M.! 0) M.empty M.empty lmap
61         d <- disassemble
62         end <- getCodeOffset
63         return ((ep, bbstarts, end, calls), d)
64   where
65   getLabel :: BlockID -> [(BlockID, Label)] -> Label
66   getLabel _ [] = error "label not found!"
67   getLabel i ((x,l):xs) = if i==x then l else getLabel i xs
68
69   efBB :: (BlockID, BasicBlock) -> TrapMap -> BBStarts -> [(BlockID, Label)] -> CodeGen e s (TrapMap, BBStarts)
70   efBB (bid, bb) calls bbstarts lmap =
71         if M.member bid bbstarts then
72           return (calls, bbstarts)
73         else do
74           bb_offset <- getCodeOffset
75           let bbstarts' = M.insert bid bb_offset bbstarts
76           defineLabel $ getLabel bid lmap
77           cs <- mapM emit' $ code bb
78           let calls' = calls `M.union` M.fromList (catMaybes cs)
79           case successor bb of
80             Return -> return (calls', bbstarts')
81             FallThrough t -> efBB (t, hmap M.! t) calls' bbstarts' lmap
82             OneTarget t -> efBB (t, hmap M.! t) calls' bbstarts' lmap
83             TwoTarget t1 t2 -> do
84               (calls'', bbstarts'') <- efBB (t1, hmap M.! t1) calls' bbstarts' lmap
85               efBB (t2, hmap M.! t2) calls'' bbstarts'' lmap
86     -- TODO(bernhard): also use metainformation
87     -- TODO(bernhard): implement `emit' as function which accepts a list of
88     --                 instructions, so we can use patterns for optimizations
89     where
90     getCurrentOffset :: CodeGen e s Word32
91     getCurrentOffset = do
92       ep <- getEntryPoint
93       let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
94       offset <- getCodeOffset
95       return $ w32_ep + fromIntegral offset
96
97     emitInvoke :: Word16 -> Bool -> CodeGen e s (Maybe (Word32, TrapCause))
98     emitInvoke cpidx hasThis = do
99         let l = buildMethodID cls cpidx
100         calladdr <- getCurrentOffset
101         newNamedLabel (show l) >>= defineLabel
102         -- causes SIGILL. in the signal handler we patch it to the acutal call.
103         -- place a nop at the end, therefore the disasm doesn't screw up
104         emit32 (0xffff9090 :: Word32) >> emit8 (0x90 :: Word8)
105         -- discard arguments on stack
106         let argcnt = ((if hasThis then 1 else 0) + methodGetArgsCount cls cpidx) * 4
107         when (argcnt > 0) (add esp argcnt)
108         -- push result on stack if method has a return value
109         when (methodHaveReturnValue cls cpidx) (push eax)
110         -- +2 is for correcting eip in trap context
111         return $ Just (calladdr + 2, StaticMethod l)
112
113     invokeEpilog :: Word16 -> Word32 -> (Bool -> TrapCause) -> CodeGen e s (Maybe (Word32, TrapCause))
114     invokeEpilog cpidx offset trapcause = do
115         -- make actual (indirect) call
116         calladdr <- getCurrentOffset
117         call (Disp offset, eax)
118         -- discard arguments on stack (+4 for "this")
119         let argcnt = 4 + 4 * methodGetArgsCount cls cpidx
120         when (argcnt > 0) (add esp argcnt)
121         -- push result on stack if method has a return value
122         when (methodHaveReturnValue cls cpidx) (push eax)
123         let imm8 = is8BitOffset offset
124         return $ Just (calladdr + (if imm8 then 3 else 6), trapcause imm8)
125
126     emit' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause))
127     emit' (INVOKESPECIAL cpidx) = emitInvoke cpidx True
128     emit' (INVOKESTATIC cpidx) = emitInvoke cpidx False
129     emit' (INVOKEINTERFACE cpidx _) = do
130         -- get methodInfo entry
131         let mi@(MethodInfo methodname ifacename msig@(MethodSignature args _)) = buildMethodID cls cpidx
132         newNamedLabel (show mi) >>= defineLabel
133         -- objref lives somewhere on the argument stack
134         mov eax (Disp ((*4) $ fromIntegral $ length args), esp)
135         -- get method-table-ptr, keep it in eax (for trap handling)
136         mov eax (Disp 0, eax)
137         -- get interface-table-ptr
138         mov ebx (Disp 0, eax)
139         -- get method offset
140         offset <- liftIO $ getInterfaceMethodOffset ifacename methodname (encode msig)
141         -- note, that "mi" has the wrong class reference here.
142         -- we figure that out at run-time, in the methodpool,
143         -- depending on the method-table-ptr
144         invokeEpilog cpidx offset (\x -> InterfaceMethod x mi)
145     emit' (INVOKEVIRTUAL cpidx) = do
146         -- get methodInfo entry
147         let mi@(MethodInfo methodname objname msig@(MethodSignature args _))  = buildMethodID cls cpidx
148         newNamedLabel (show mi) >>= defineLabel
149         -- objref lives somewhere on the argument stack
150         mov eax (Disp ((*4) $ fromIntegral $ length args), esp)
151         -- get method-table-ptr
152         mov eax (Disp 0, eax)
153         -- get method offset
154         let nameAndSig = methodname `B.append` encode msig
155         offset <- liftIO $ getMethodOffset objname nameAndSig
156         -- note, that "mi" has the wrong class reference here.
157         -- we figure that out at run-time, in the methodpool,
158         -- depending on the method-table-ptr
159         invokeEpilog cpidx offset (\x -> VirtualMethod x mi)
160     emit' (PUTSTATIC cpidx) = do
161         pop eax
162         trapaddr <- getCurrentOffset
163         mov (Addr 0x00000000) eax -- it's a trap
164         return $ Just (trapaddr, StaticField $ buildStaticFieldID cls cpidx)
165     emit' (GETSTATIC cpidx) = do
166         trapaddr <- getCurrentOffset
167         mov eax (Addr 0x00000000) -- it's a trap
168         push eax
169         return $ Just (trapaddr, StaticField $ buildStaticFieldID cls cpidx)
170     emit' insn = emit insn >> return Nothing
171
172     emit :: J.Instruction -> CodeGen e s ()
173     emit POP = add esp (4 :: Word32) -- drop value
174     emit DUP = push (Disp 0, esp)
175     emit DUP_X1 = do pop eax; pop ebx; push eax; push ebx; push eax
176     emit AASTORE = emit IASTORE
177     emit IASTORE = do
178         pop eax -- value
179         pop ebx -- offset
180         add ebx (1 :: Word32)
181         pop ecx -- aref
182         mov (ecx, ebx, S4) eax
183     emit CASTORE = do
184         pop eax -- value
185         pop ebx -- offset
186         add ebx (1 :: Word32)
187         pop ecx -- aref
188         mov (ecx, ebx, S1) eax -- TODO(bernhard): char is two byte
189     emit AALOAD = emit IALOAD
190     emit IALOAD = do
191         pop ebx -- offset
192         add ebx (1 :: Word32)
193         pop ecx -- aref
194         push (ecx, ebx, S4)
195     emit CALOAD = do
196         pop ebx -- offset
197         add ebx (1 :: Word32)
198         pop ecx -- aref
199         push (ecx, ebx, S1) -- TODO(bernhard): char is two byte
200     emit ARRAYLENGTH = do
201         pop eax
202         push (Disp 0, eax)
203     emit (ANEWARRAY _) = emit (NEWARRAY 10) -- 10 == T_INT
204     emit (NEWARRAY typ) = do
205         let tsize = case decodeS (0 :: Integer) (B.pack [typ]) of
206                     T_INT -> 4
207                     T_CHAR -> 2
208                     _ -> error "newarray: type not implemented yet"
209         -- get length from stack, but leave it there
210         mov eax (Disp 0, esp)
211         mov ebx (tsize :: Word32)
212         -- multiple amount with native size of one element
213         mul ebx -- result is in eax
214         add eax (4 :: Word32) -- for "length" entry
215         -- push amount of bytes to allocate
216         push eax
217         callMalloc
218         pop eax -- ref to arraymemory
219         pop ebx -- length
220         mov (Disp 0, eax) ebx -- store length at offset 0
221         push eax -- push ref again
222     emit (NEW objidx) = do
223         let objname = buildClassID cls objidx
224         amount <- liftIO $ getObjectSize objname
225         push (amount :: Word32)
226         callMalloc
227         -- TODO(bernhard): save reference somewhere for GC
228         -- set method table pointer
229         mtable <- liftIO $ getMethodTable objname
230         mov (Disp 0, eax) mtable
231     emit (CHECKCAST _) = nop -- TODO(bernhard): ...
232     -- TODO(bernhard): ...
233     emit (INSTANCEOF _) = do
234       pop eax
235       push (1 :: Word32)
236     emit ATHROW = nop -- TODO(bernhard): ...
237     emit I2C = do
238       pop eax
239       and eax (0x000000ff :: Word32)
240       push eax
241     emit (BIPUSH val) = push (fromIntegral val :: Word32)
242     emit (SIPUSH val) = push (fromIntegral (fromIntegral val :: Int16) :: Word32)
243     emit ACONST_NULL = push (0 :: Word32)
244     emit (ICONST_M1) = push ((-1) :: Word32)
245     emit (ICONST_0) = push (0 :: Word32)
246     emit (ICONST_1) = push (1 :: Word32)
247     emit (ICONST_2) = push (2 :: Word32)
248     emit (ICONST_3) = push (3 :: Word32)
249     emit (ICONST_4) = push (4 :: Word32)
250     emit (ICONST_5) = push (5 :: Word32)
251     emit (ALOAD_ x) = emit (ILOAD_ x)
252     emit (ILOAD_ x) = push (Disp (cArgs_ x), ebp)
253     emit (ALOAD x) = emit (ILOAD x)
254     emit (ILOAD x) = push (Disp (cArgs x), ebp)
255     emit (ASTORE_ x) = emit (ISTORE_ x)
256     emit (ISTORE_ x) = do
257         pop eax
258         mov (Disp (cArgs_ x), ebp) eax
259     emit (ASTORE x) = emit (ISTORE x)
260     emit (ISTORE x) = do
261         pop eax
262         mov (Disp (cArgs x), ebp) eax
263
264     emit (LDC1 x) = emit (LDC2 $ fromIntegral x)
265     emit (LDC2 x) = do
266         value <- case constsPool cls M.! x of
267                       (CString s) -> liftIO $ getUniqueStringAddr s
268                       e -> error $ "LDCI... missing impl.: " ++ show e
269         push value
270     emit (GETFIELD x) = do
271         offset <- emitFieldOffset x
272         push (Disp (fromIntegral offset), eax) -- get field
273     emit (PUTFIELD x) = do
274         pop ebx -- value to write
275         offset <- emitFieldOffset x
276         mov (Disp (fromIntegral offset), eax) ebx -- set field
277
278     emit IADD = do pop ebx; pop eax; add eax ebx; push eax
279     emit ISUB = do pop ebx; pop eax; sub eax ebx; push eax
280     emit IMUL = do pop ebx; pop eax; mul ebx; push eax
281     emit IDIV = do pop ebx; pop eax; xor edx edx; div ebx; push eax
282     emit IREM = do pop ebx; pop eax; xor edx edx; div ebx; push edx
283     emit IXOR = do pop ebx; pop eax; xor eax ebx; push eax
284     emit INEG = do pop eax; neg eax; push eax
285     emit (IINC x imm) =
286         add (Disp (cArgs x), ebp) (s8_w32 imm)
287
288     emit (IFNONNULL x) = emit (IF C_NE x)
289     emit (IFNULL x) = emit (IF C_EQ x)
290     emit (IF_ACMP cond x) = emit (IF_ICMP cond x)
291     emit (IF_ICMP cond _) = do
292         pop eax -- value2
293         pop ebx -- value1
294         cmp ebx eax -- intel syntax is swapped (TODO(bernhard): test that plz)
295         emitIF cond
296
297     emit (IF cond _) = do
298         pop eax -- value1
299         cmp eax (0 :: Word32) -- TODO(bernhard): test that plz
300         emitIF cond
301
302     emit (GOTO _ ) = do
303         let sid = case successor bb of OneTarget t -> t; _ -> error "bad"
304         jmp $ getLabel sid lmap
305
306     emit RETURN = do mov esp ebp; pop ebp; ret
307     emit ARETURN = emit IRETURN
308     emit IRETURN = do pop eax; emit RETURN
309     emit invalid = error $ "insn not implemented yet: " ++ show invalid
310
311     emitFieldOffset :: Word16 -> CodeGen e s Int32
312     emitFieldOffset x = do
313         pop eax -- this pointer
314         let (cname, fname) = buildFieldOffset cls x
315         liftIO $ getFieldOffset cname fname
316
317     emitIF :: CMP -> CodeGen e s ()
318     emitIF cond = let
319       sid = case successor bb of TwoTarget _ t -> t; _ -> error "bad"
320       l = getLabel sid lmap
321       in case cond of
322         C_EQ -> je  l; C_NE -> jne l
323         C_LT -> jl  l; C_GT -> jg  l
324         C_GE -> jge l; C_LE -> jle l
325
326     callMalloc :: CodeGen e s ()
327     callMalloc = do
328         call mallocObjectAddr
329         add esp (4 :: Word32)
330         push eax
331
332   -- for locals we use a different storage
333   cArgs :: Word8 -> Word32
334   cArgs x = if x' >= thisMethodArgCnt
335       -- TODO(bernhard): maybe s/(-4)/(-8)/
336       then fromIntegral $ (-4) * (x' - thisMethodArgCnt + 1)
337       else 4 + (thisMethodArgCnt * 4) - (4 * x')
338     where x' = fromIntegral x
339
340   cArgs_ :: IMM -> Word32
341   cArgs_ x = cArgs $ case x of I0 -> 0; I1 -> 1; I2 -> 2; I3 -> 3
342
343   thisMethodArgCnt :: Word32
344   thisMethodArgCnt = isNonStatic + fromIntegral (length args)
345     where
346     (Just m) = lookupMethodSig method sig cls
347     (MethodSignature args _) = sig
348     isNonStatic = if S.member ACC_STATIC (methodAccessFlags m)
349         then 0 else 1 -- one argument for the this pointer
350
351
352   -- sign extension from w8 to w32 (over s8)
353   --   unfortunately, hs-java is using Word8 everywhere (while
354   --   it should be Int8 actually)
355   s8_w32 :: Word8 -> Word32
356   s8_w32 w8 = fromIntegral s8
357     where s8 = fromIntegral w8 :: Int8
358
359   is8BitOffset :: Word32 -> Bool
360   is8BitOffset w32 = s32 < 128 && s32 > (-127)
361     where s32 = fromIntegral w32 :: Int32