X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=Mate%2FX86CodeGen.hs;h=1097e8565035257771068e76e3b9291ae0819c68;hb=d52e9acb9411a9d8386ec95aa9952edb950c65b2;hp=710b5b60d5a1589adc5c1d7253dd0ef23416ac89;hpb=3c1c1355bc77bf53846255a628416aa36a730e23;p=mate.git diff --git a/Mate/X86CodeGen.hs b/Mate/X86CodeGen.hs index 710b5b6..1097e85 100644 --- a/Mate/X86CodeGen.hs +++ b/Mate/X86CodeGen.hs @@ -1,7 +1,5 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ForeignFunctionInterface #-} -#include "debug.h" module Mate.X86CodeGen where import Prelude hiding (and, div) @@ -9,9 +7,11 @@ import Data.Binary import Data.BinaryState import Data.Int import Data.Maybe +import Data.List (genericLength) import qualified Data.Map as M import qualified Data.ByteString.Lazy as B import Control.Monad +import Control.Applicative import Foreign hiding (xor) import Foreign.C.Types @@ -28,13 +28,11 @@ import Mate.NativeSizes import Mate.Types import Mate.Utilities import Mate.ClassPool +import {-# SOURCE #-} Mate.MethodPool import Mate.Strings -#ifdef DEBUG -import Text.Printf -#endif -foreign import ccall "&mallocObject" +foreign import ccall "&mallocObjectGC" mallocObjectAddr :: FunPtr (Int -> IO CPtrdiff) type EntryPoint = Ptr Word8 @@ -91,6 +89,13 @@ emitFromBB cls method = do -- TODO(bernhard): implement `emit' as function which accepts a list of -- instructions, so we can use patterns for optimizations where + forceRegDump :: CodeGen e s () + forceRegDump = do + push esi + mov esi (0x13371234 :: Word32) + mov esi (Addr 0) + pop esi + getCurrentOffset :: CodeGen e s Word32 getCurrentOffset = do ep <- getEntryPoint @@ -105,26 +110,47 @@ emitFromBB cls method = do newNamedLabel (show l) >>= defineLabel -- causes SIGILL. in the signal handler we patch it to the acutal call. -- place two nop's at the end, therefore the disasm doesn't screw up - emit32 (0x9090ffff :: Word32) >> emit8 (0x90 :: Word8) + emit32 (0x9090ffff :: Word32); nop + let patcher reip = do + entryAddr <- liftIO $ getMethodEntry l + call (fromIntegral (entryAddr - (reip + 5)) :: NativeWord) + return reip -- discard arguments on stack let argcnt = ((if hasThis then 1 else 0) + methodGetArgsCount (methodNameTypeByIdx cls cpidx)) * ptrSize when (argcnt > 0) (add esp argcnt) -- push result on stack if method has a return value when (methodHaveReturnValue cls cpidx) (push eax) - return $ Just (calladdr, StaticMethod l) + return $ Just (calladdr, StaticMethod patcher) - invokeEpilog :: Word16 -> Word32 -> (Bool -> TrapCause) -> CodeGen e s (Maybe (Word32, TrapCause)) - invokeEpilog cpidx offset trapcause = do + virtualCall :: Word16 -> Bool -> CodeGen e s (Maybe (Word32, TrapCause)) + virtualCall cpidx isInterface = do + let mi@(MethodInfo methodname objname msig@(MethodSignature args _)) = buildMethodID cls cpidx + newNamedLabel (show mi) >>= defineLabel + -- get method offset for call @ runtime + let offset = if isInterface + then getInterfaceMethodOffset objname methodname (encode msig) + else getMethodOffset objname (methodname `B.append` encode msig) + let argsLen = genericLength args + -- objref lives somewhere on the argument stack + mov ebx (Disp (argsLen * ptrSize), esp) + if isInterface + then mov ebx (Disp 0, ebx) -- get method-table-ptr, keep it in ebx + else return () -- invokevirtual + -- get method-table-ptr (or interface-table-ptr) + mov eax (Disp 0, ebx) -- make actual (indirect) call calladdr <- getCurrentOffset - call (Disp offset, eax) + -- will be patched to this: call (Disp 0xXXXXXXXX, eax) + emit32 (0x9090ffff :: Word32); nop; nop -- discard arguments on stack (`+1' for "this") let argcnt = ptrSize * (1 + methodGetArgsCount (methodNameTypeByIdx cls cpidx)) when (argcnt > 0) (add esp argcnt) -- push result on stack if method has a return value when (methodHaveReturnValue cls cpidx) (push eax) - let imm8 = is8BitOffset offset - return $ Just (calladdr + (if imm8 then 3 else 6), trapcause imm8) + -- note, that "mi" has the wrong class reference here. + -- we figure that out at run-time, in the methodpool, + -- depending on the method-table-ptr + return $ Just (calladdr, VirtualCall isInterface mi offset) emit'' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause)) emit'' insn = newNamedLabel ("jvm_insn: " ++ show insn) >>= defineLabel >> emit' insn @@ -132,37 +158,9 @@ emitFromBB cls method = do emit' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapCause)) emit' (INVOKESPECIAL cpidx) = emitInvoke cpidx True emit' (INVOKESTATIC cpidx) = emitInvoke cpidx False - emit' (INVOKEINTERFACE cpidx _) = do - -- get methodInfo entry - let mi@(MethodInfo methodname ifacename msig@(MethodSignature args _)) = buildMethodID cls cpidx - newNamedLabel (show mi) >>= defineLabel - -- objref lives somewhere on the argument stack - mov eax (Disp ((* ptrSize) $ fromIntegral $ length args), esp) - -- get method-table-ptr, keep it in eax (for trap handling) - mov eax (Disp 0, eax) - -- get interface-table-ptr - mov ebx (Disp 0, eax) - -- get method offset - offset <- liftIO $ getInterfaceMethodOffset ifacename methodname (encode msig) - -- note, that "mi" has the wrong class reference here. - -- we figure that out at run-time, in the methodpool, - -- depending on the method-table-ptr - invokeEpilog cpidx offset (`InterfaceMethod` mi) - emit' (INVOKEVIRTUAL cpidx) = do - -- get methodInfo entry - let mi@(MethodInfo methodname objname msig@(MethodSignature args _)) = buildMethodID cls cpidx - newNamedLabel (show mi) >>= defineLabel - -- objref lives somewhere on the argument stack - mov eax (Disp ((* ptrSize) $ fromIntegral $ length args), esp) - -- get method-table-ptr - mov eax (Disp 0, eax) - -- get method offset - let nameAndSig = methodname `B.append` encode msig - offset <- liftIO $ getMethodOffset objname nameAndSig - -- note, that "mi" has the wrong class reference here. - -- we figure that out at run-time, in the methodpool, - -- depending on the method-table-ptr - invokeEpilog cpidx offset (`VirtualMethod` mi) + emit' (INVOKEINTERFACE cpidx _) = virtualCall cpidx True + emit' (INVOKEVIRTUAL cpidx) = virtualCall cpidx False + emit' (PUTSTATIC cpidx) = do pop eax trapaddr <- getCurrentOffset @@ -173,6 +171,62 @@ emitFromBB cls method = do mov eax (Addr 0x00000000) -- it's a trap push eax return $ Just (trapaddr, StaticField $ buildStaticFieldID cls cpidx) + + emit' (GETFIELD x) = do + pop eax -- this pointer + trapaddr <- getCurrentOffset + -- like: 099db064 ff b0 e4 14 00 00 pushl 5348(%eax) + emit32 (0x9090ffff :: Word32); nop; nop + let patcher reip = do + let (cname, fname) = buildFieldOffset cls x + offset <- liftIO $ fromIntegral <$> getFieldOffset cname fname + push32_rel_eax (Disp offset) -- get field + return reip + return $ Just (trapaddr, ObjectField patcher) + emit' (PUTFIELD x) = do + pop ebx -- value to write + pop eax -- this pointer + trapaddr <- getCurrentOffset + -- like: 4581fc6b 89 98 30 7b 00 00 movl %ebx,31536(%eax) + emit32 (0x9090ffff :: Word32); nop; nop + let patcher reip = do + let (cname, fname) = buildFieldOffset cls x + offset <- liftIO $ fromIntegral <$> getFieldOffset cname fname + mov32_rel_ebx_eax (Disp offset) -- set field + return reip + return $ Just (trapaddr, ObjectField patcher) + + emit' (INSTANCEOF cpidx) = do + pop eax + mov eax (Disp 0, eax) -- mtable of objectref + trapaddr <- getCurrentOffset + -- place something like `mov edx $mtable_of_objref' instead + emit32 (0x9090ffff :: Word32); nop + cmp eax edx + sete al + movzxb eax al + push eax + forceRegDump + return $ Just (trapaddr, InstanceOf $ buildClassID cls cpidx) + emit' (NEW objidx) = do + let objname = buildClassID cls objidx + trapaddr <- getCurrentOffset + -- place something like `push $objsize' instead + emit32 (0x9090ffff :: Word32); nop + callMalloc + -- 0x13371337 is just a placeholder; will be replaced with mtable ptr + mov (Disp 0, eax) (0x13371337 :: Word32) + mov (Disp 4, eax) (0x1337babe :: Word32) + let patcher reip = do + objsize <- liftIO $ getObjectSize objname + push32 objsize + callMalloc + mtable <- liftIO $ getMethodTable objname + mov (Disp 0, eax) mtable + mov (Disp 4, eax) (0x1337babe :: Word32) + return reip + return $ Just (trapaddr, NewObject patcher) + emit' insn = emit insn >> return Nothing emit :: J.Instruction -> CodeGen e s () @@ -226,20 +280,8 @@ emitFromBB cls method = do pop ebx -- length mov (Disp 0, eax) ebx -- store length at offset 0 push eax -- push ref again - emit (NEW objidx) = do - let objname = buildClassID cls objidx - amount <- liftIO $ getObjectSize objname - push (amount :: Word32) - callMalloc - -- TODO(bernhard): save reference somewhere for GC - -- set method table pointer - mtable <- liftIO $ getMethodTable objname - mov (Disp 0, eax) mtable + emit (CHECKCAST _) = nop -- TODO(bernhard): ... - -- TODO(bernhard): ... - emit (INSTANCEOF _) = do - pop eax - push (1 :: Word32) emit ATHROW = -- TODO(bernhard): ... emit32 (0xffffffff :: Word32) emit I2C = do @@ -276,13 +318,6 @@ emitFromBB cls method = do (CInteger i) -> liftIO $ return i e -> error $ "LDCI... missing impl.: " ++ show e push value - emit (GETFIELD x) = do - offset <- emitFieldOffset x - push (Disp (fromIntegral offset), eax) -- get field - emit (PUTFIELD x) = do - pop ebx -- value to write - offset <- emitFieldOffset x - mov (Disp (fromIntegral offset), eax) ebx -- set field emit IADD = do pop ebx; pop eax; add eax ebx; push eax emit ISUB = do pop ebx; pop eax; sub eax ebx; push eax @@ -318,12 +353,6 @@ emitFromBB cls method = do emit IRETURN = do pop eax; emit RETURN emit invalid = error $ "insn not implemented yet: " ++ show invalid - emitFieldOffset :: Word16 -> CodeGen e s Int32 - emitFieldOffset x = do - pop eax -- this pointer - let (cname, fname) = buildFieldOffset cls x - liftIO $ getFieldOffset cname fname - emitIF :: CMP -> CodeGen e s () emitIF cond = let sid = case successor bb of TwoTarget _ t -> t; _ -> error "bad" @@ -340,12 +369,6 @@ emitFromBB cls method = do jmp l2 - callMalloc :: CodeGen e s () - callMalloc = do - call mallocObjectAddr - add esp (ptrSize :: Word32) - push eax - -- for locals we use a different storage cArgs :: Word8 -> Word32 cArgs x = ptrSize * (argcount - x' + isLocal) @@ -365,6 +388,28 @@ emitFromBB cls method = do s8_w32 w8 = fromIntegral s8 where s8 = fromIntegral w8 :: Int8 - is8BitOffset :: Word32 -> Bool - is8BitOffset w32 = s32 < 128 && s32 > (-127) - where s32 = fromIntegral w32 :: Int32 +callMalloc :: CodeGen e s () +callMalloc = do + call mallocObjectAddr + add esp (ptrSize :: Word32) + push eax + + +-- harpy tries to cut immediates (or displacements), if they fit in 8bit. +-- however, this is bad for patching so we want to put always 32bit. + +-- push imm32 +push32 :: Word32 -> CodeGen e s () +push32 imm32 = emit8 0x68 >> emit32 imm32 + +-- call disp32(%eax) +call32_eax :: Disp -> CodeGen e s () +call32_eax (Disp disp32) = emit8 0xff >> emit8 0x90 >> emit32 disp32 + +-- push disp32(%eax) +push32_rel_eax :: Disp -> CodeGen e s () +push32_rel_eax (Disp disp32) = emit8 0xff >> emit8 0xb0 >> emit32 disp32 + +-- mov %ebx, disp32(%eax) +mov32_rel_ebx_eax :: Disp -> CodeGen e s () +mov32_rel_ebx_eax (Disp disp32) = emit8 0x89 >> emit8 0x98 >> emit32 disp32