refactor: better names for TrapInfo^WTrapCause
[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     emit' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause))
114     emit' (INVOKESPECIAL cpidx) = emitInvoke cpidx True
115     emit' (INVOKESTATIC cpidx) = emitInvoke cpidx False
116     emit' (INVOKEINTERFACE cpidx _) = do
117         -- get methodInfo entry
118         let mi@(MethodInfo methodname ifacename msig@(MethodSignature args _)) = buildMethodID cls cpidx
119         newNamedLabel (show mi) >>= defineLabel
120         -- objref lives somewhere on the argument stack
121         mov eax (Disp ((*4) $ fromIntegral $ length args), esp)
122         -- get method-table-ptr, keep it in eax (for trap handling)
123         mov eax (Disp 0, eax)
124         -- get interface-table-ptr
125         mov ebx (Disp 0, eax)
126         -- get method offset
127         offset <- liftIO $ getInterfaceMethodOffset ifacename methodname (encode msig)
128         -- make actual (indirect) call
129         calladdr <- getCurrentOffset
130         call (Disp offset, ebx)
131         -- discard arguments on stack (+4 for "this")
132         let argcnt = 4 + 4 * methodGetArgsCount cls cpidx
133         when (argcnt > 0) (add esp argcnt)
134         -- push result on stack if method has a return value
135         when (methodHaveReturnValue cls cpidx) (push eax)
136         -- note, the "mi" has the wrong class reference here.
137         -- we figure that out at run-time, in the methodpool,
138         -- depending on the method-table-ptr
139         let imm8 = is8BitOffset offset
140         return $ Just (calladdr + (if imm8 then 3 else 6), InterfaceMethod imm8 mi)
141     emit' (INVOKEVIRTUAL cpidx) = do
142         -- get methodInfo entry
143         let mi@(MethodInfo methodname objname msig@(MethodSignature args _))  = buildMethodID cls cpidx
144         newNamedLabel (show mi) >>= defineLabel
145         -- objref lives somewhere on the argument stack
146         mov eax (Disp ((*4) $ fromIntegral $ length args), esp)
147         -- get method-table-ptr
148         mov eax (Disp 0, eax)
149         -- get method offset
150         let nameAndSig = methodname `B.append` encode msig
151         offset <- liftIO $ getMethodOffset objname nameAndSig
152         -- make actual (indirect) call
153         calladdr <- getCurrentOffset
154         call (Disp offset, eax)
155         -- discard arguments on stack (+4 for "this")
156         let argcnt = 4 + 4 * methodGetArgsCount cls cpidx
157         when (argcnt > 0) (add esp argcnt)
158         -- push result on stack if method has a return value
159         when (methodHaveReturnValue cls cpidx) (push eax)
160         -- note, the "mi" has the wrong class reference here.
161         -- we figure that out at run-time, in the methodpool,
162         -- depending on the method-table-ptr
163         let imm8 = is8BitOffset offset
164         return $ Just (calladdr + (if imm8 then 3 else 6), VirtualMethod imm8 mi)
165     emit' (PUTSTATIC cpidx) = do
166         pop eax
167         trapaddr <- getCurrentOffset
168         mov (Addr 0x00000000) eax -- it's a trap
169         return $ Just (trapaddr, StaticField $ buildStaticFieldID cls cpidx)
170     emit' (GETSTATIC cpidx) = do
171         trapaddr <- getCurrentOffset
172         mov eax (Addr 0x00000000) -- it's a trap
173         push eax
174         return $ Just (trapaddr, StaticField $ buildStaticFieldID cls cpidx)
175     emit' insn = emit insn >> return Nothing
176
177     emit :: J.Instruction -> CodeGen e s ()
178     emit POP = add esp (4 :: Word32) -- drop value
179     emit DUP = push (Disp 0, esp)
180     emit DUP_X1 = do pop eax; pop ebx; push eax; push ebx; push eax
181     emit AASTORE = emit IASTORE
182     emit IASTORE = do
183         pop eax -- value
184         pop ebx -- offset
185         add ebx (1 :: Word32)
186         pop ecx -- aref
187         mov (ecx, ebx, S4) eax
188     emit CASTORE = do
189         pop eax -- value
190         pop ebx -- offset
191         add ebx (1 :: Word32)
192         pop ecx -- aref
193         mov (ecx, ebx, S1) eax -- TODO(bernhard): char is two byte
194     emit AALOAD = emit IALOAD
195     emit IALOAD = do
196         pop ebx -- offset
197         add ebx (1 :: Word32)
198         pop ecx -- aref
199         push (ecx, ebx, S4)
200     emit CALOAD = do
201         pop ebx -- offset
202         add ebx (1 :: Word32)
203         pop ecx -- aref
204         push (ecx, ebx, S1) -- TODO(bernhard): char is two byte
205     emit ARRAYLENGTH = do
206         pop eax
207         push (Disp 0, eax)
208     emit (ANEWARRAY _) = emit (NEWARRAY 10) -- 10 == T_INT
209     emit (NEWARRAY typ) = do
210         let tsize = case decodeS (0 :: Integer) (B.pack [typ]) of
211                     T_INT -> 4
212                     T_CHAR -> 2
213                     _ -> error "newarray: type not implemented yet"
214         -- get length from stack, but leave it there
215         mov eax (Disp 0, esp)
216         mov ebx (tsize :: Word32)
217         -- multiple amount with native size of one element
218         mul ebx -- result is in eax
219         add eax (4 :: Word32) -- for "length" entry
220         -- push amount of bytes to allocate
221         push eax
222         callMalloc
223         pop eax -- ref to arraymemory
224         pop ebx -- length
225         mov (Disp 0, eax) ebx -- store length at offset 0
226         push eax -- push ref again
227     emit (NEW objidx) = do
228         let objname = buildClassID cls objidx
229         amount <- liftIO $ getObjectSize objname
230         push (amount :: Word32)
231         callMalloc
232         -- TODO(bernhard): save reference somewhere for GC
233         -- set method table pointer
234         mtable <- liftIO $ getMethodTable objname
235         mov (Disp 0, eax) mtable
236     emit (CHECKCAST _) = nop -- TODO(bernhard): ...
237     -- TODO(bernhard): ...
238     emit (INSTANCEOF _) = do
239       pop eax
240       push (1 :: Word32)
241     emit ATHROW = nop -- TODO(bernhard): ...
242     emit I2C = do
243       pop eax
244       and eax (0x000000ff :: Word32)
245       push eax
246     emit (BIPUSH val) = push (fromIntegral val :: Word32)
247     emit (SIPUSH val) = push (fromIntegral (fromIntegral val :: Int16) :: Word32)
248     emit ACONST_NULL = push (0 :: Word32)
249     emit (ICONST_M1) = push ((-1) :: Word32)
250     emit (ICONST_0) = push (0 :: Word32)
251     emit (ICONST_1) = push (1 :: Word32)
252     emit (ICONST_2) = push (2 :: Word32)
253     emit (ICONST_3) = push (3 :: Word32)
254     emit (ICONST_4) = push (4 :: Word32)
255     emit (ICONST_5) = push (5 :: Word32)
256     emit (ALOAD_ x) = emit (ILOAD_ x)
257     emit (ILOAD_ x) = push (Disp (cArgs_ x), ebp)
258     emit (ALOAD x) = emit (ILOAD x)
259     emit (ILOAD x) = push (Disp (cArgs x), ebp)
260     emit (ASTORE_ x) = emit (ISTORE_ x)
261     emit (ISTORE_ x) = do
262         pop eax
263         mov (Disp (cArgs_ x), ebp) eax
264     emit (ASTORE x) = emit (ISTORE x)
265     emit (ISTORE x) = do
266         pop eax
267         mov (Disp (cArgs x), ebp) eax
268
269     emit (LDC1 x) = emit (LDC2 $ fromIntegral x)
270     emit (LDC2 x) = do
271         value <- case constsPool cls M.! x of
272                       (CString s) -> liftIO $ getUniqueStringAddr s
273                       e -> error $ "LDCI... missing impl.: " ++ show e
274         push value
275     emit (GETFIELD x) = do
276         offset <- emitFieldOffset x
277         push (Disp (fromIntegral offset), eax) -- get field
278     emit (PUTFIELD x) = do
279         pop ebx -- value to write
280         offset <- emitFieldOffset x
281         mov (Disp (fromIntegral offset), eax) ebx -- set field
282
283     emit IADD = do pop ebx; pop eax; add eax ebx; push eax
284     emit ISUB = do pop ebx; pop eax; sub eax ebx; push eax
285     emit IMUL = do pop ebx; pop eax; mul ebx; push eax
286     emit IDIV = do pop ebx; pop eax; xor edx edx; div ebx; push eax
287     emit IREM = do pop ebx; pop eax; xor edx edx; div ebx; push edx
288     emit IXOR = do pop ebx; pop eax; xor eax ebx; push eax
289     emit INEG = do pop eax; neg eax; push eax
290     emit (IINC x imm) =
291         add (Disp (cArgs x), ebp) (s8_w32 imm)
292
293     emit (IFNONNULL x) = emit (IF C_NE x)
294     emit (IFNULL x) = emit (IF C_EQ x)
295     emit (IF_ACMP cond x) = emit (IF_ICMP cond x)
296     emit (IF_ICMP cond _) = do
297         pop eax -- value2
298         pop ebx -- value1
299         cmp ebx eax -- intel syntax is swapped (TODO(bernhard): test that plz)
300         emitIF cond
301
302     emit (IF cond _) = do
303         pop eax -- value1
304         cmp eax (0 :: Word32) -- TODO(bernhard): test that plz
305         emitIF cond
306
307     emit (GOTO _ ) = do
308         let sid = case successor bb of OneTarget t -> t; _ -> error "bad"
309         jmp $ getLabel sid lmap
310
311     emit RETURN = do mov esp ebp; pop ebp; ret
312     emit ARETURN = emit IRETURN
313     emit IRETURN = do pop eax; emit RETURN
314     emit invalid = error $ "insn not implemented yet: " ++ show invalid
315
316     emitFieldOffset :: Word16 -> CodeGen e s Int32
317     emitFieldOffset x = do
318         pop eax -- this pointer
319         let (cname, fname) = buildFieldOffset cls x
320         liftIO $ getFieldOffset cname fname
321
322     emitIF :: CMP -> CodeGen e s ()
323     emitIF cond = let
324       sid = case successor bb of TwoTarget _ t -> t; _ -> error "bad"
325       l = getLabel sid lmap
326       in case cond of
327         C_EQ -> je  l; C_NE -> jne l
328         C_LT -> jl  l; C_GT -> jg  l
329         C_GE -> jge l; C_LE -> jle l
330
331     callMalloc :: CodeGen e s ()
332     callMalloc = do
333         call mallocObjectAddr
334         add esp (4 :: Word32)
335         push eax
336
337   -- for locals we use a different storage
338   cArgs :: Word8 -> Word32
339   cArgs x = if x' >= thisMethodArgCnt
340       -- TODO(bernhard): maybe s/(-4)/(-8)/
341       then fromIntegral $ (-4) * (x' - thisMethodArgCnt + 1)
342       else 4 + (thisMethodArgCnt * 4) - (4 * x')
343     where x' = fromIntegral x
344
345   cArgs_ :: IMM -> Word32
346   cArgs_ x = cArgs $ case x of I0 -> 0; I1 -> 1; I2 -> 2; I3 -> 3
347
348   thisMethodArgCnt :: Word32
349   thisMethodArgCnt = isNonStatic + fromIntegral (length args)
350     where
351     (Just m) = lookupMethodSig method sig cls
352     (MethodSignature args _) = sig
353     isNonStatic = if S.member ACC_STATIC (methodAccessFlags m)
354         then 0 else 1 -- one argument for the this pointer
355
356
357   -- sign extension from w8 to w32 (over s8)
358   --   unfortunately, hs-java is using Word8 everywhere (while
359   --   it should be Int8 actually)
360   s8_w32 :: Word8 -> Word32
361   s8_w32 w8 = fromIntegral s8
362     where s8 = fromIntegral w8 :: Int8
363
364   is8BitOffset :: Word32 -> Bool
365   is8BitOffset w32 = s32 < 128 && s32 > (-127)
366     where s32 = fromIntegral w32 :: Int32