codegen: factor offset calculation
[mate.git] / Mate / X86CodeGen.hs
index 23165ddb1bfcb4cfe74838e1d1d261b2a5ea939c..ac51092d3e858e020da03fcd5262ec806b37484a 100644 (file)
@@ -7,6 +7,7 @@ import Data.Int
 import Data.Maybe
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
+import Control.Monad
 
 import Foreign
 import Foreign.C.Types
@@ -16,13 +17,14 @@ import Text.Printf
 import qualified JVM.Assembler as J
 import JVM.Assembler hiding (Instruction)
 import JVM.ClassFile
-import JVM.Converter
 
 import Harpy
 import Harpy.X86Disassembler
 
 import Mate.BasicBlocks
+import Mate.Types
 import Mate.Utilities
+import Mate.ClassPool
 
 foreign import ccall "dynamic"
    code_int :: FunPtr (CInt -> CInt -> IO CInt) -> (CInt -> CInt -> IO CInt)
@@ -36,16 +38,10 @@ foreign import ccall "callertrap"
 foreign import ccall "register_signal"
   register_signal :: IO ()
 
-foreign import ccall "get_cmap"
-  get_cmap :: IO (Ptr ())
-
-foreign import ccall "set_cmap"
-  set_cmap :: Ptr () -> IO ()
-
 test_01, test_02, test_03 :: IO ()
 test_01 = do
   register_signal
-  (entry, end) <- testCase "./tests/Fib.class" "fib"
+  (entry, end) <- testCase "./tests/Fib" "fib"
   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
 
   mapM_ (\x -> do
@@ -65,7 +61,7 @@ test_01 = do
 
 
 test_02 = do
-  (entry,_) <- testCase "./tests/While.class" "f"
+  (entry,_) <- testCase "./tests/While" "f"
   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
   result <- code_int entryFuncPtr 5 4
   let iresult :: Int; iresult = fromIntegral result
@@ -79,7 +75,7 @@ test_02 = do
 
 
 test_03 = do
-  (entry,_) <- testCase "./tests/While.class" "g"
+  (entry,_) <- testCase "./tests/While" "g"
   let entryFuncPtr = ((castPtrToFunPtr entry) :: FunPtr (CInt -> CInt -> IO CInt))
   result <- code_int entryFuncPtr 5 4
   let iresult :: Int; iresult = fromIntegral result
@@ -92,9 +88,9 @@ test_03 = do
   printf "result of g(4,3): %3d\t\t%s\n" iresult2 kk2
 
 
-testCase :: String -> B.ByteString -> IO (Ptr Word8, Int)
+testCase :: B.ByteString -> B.ByteString -> IO (Ptr Word8, Int)
 testCase cf method = do
-      cls <- parseClassFile cf
+      cls <- getClassFile cf
       hmap <- parseMethod cls method
       printMapBB hmap
       case hmap of
@@ -116,16 +112,7 @@ type PatchInfo = (BlockID, EntryPointOffset)
 
 type BBStarts = M.Map BlockID Int
 
-type CompileInfo = (EntryPoint, BBStarts, Int, CMap)
-
--- B.ByteString: encoded name: <Class>.<methodname><signature>
--- Class Resolved: classfile
--- Word16: index of invoke-instruction
-type MethodInfo = (B.ByteString, Class Resolved, Word16)
-
--- Word32 = point of method call in generated code
--- MethodInfo = relevant information about callee
-type CMap = M.Map Word32 MethodInfo
+type CompileInfo = (EntryPoint, BBStarts, Int, TMap)
 
 
 emitFromBB :: Class Resolved -> MapBB -> CodeGen e s (CompileInfo, [Instruction])
@@ -145,7 +132,7 @@ emitFromBB cls hmap =  do
   getLabel _ [] = error "label not found!"
   getLabel i ((x,l):xs) = if i==x then l else getLabel i xs
 
-  efBB :: (BlockID, BasicBlock) -> CMap -> BBStarts -> [(BlockID, Label)] -> CodeGen e s (CMap, BBStarts)
+  efBB :: (BlockID, BasicBlock) -> TMap -> BBStarts -> [(BlockID, Label)] -> CodeGen e s (TMap, BBStarts)
   efBB (bid, bb) calls bbstarts lmap =
         if M.member bid bbstarts then
           return (calls, bbstarts)
@@ -157,6 +144,8 @@ emitFromBB cls hmap =  do
           let calls' = calls `M.union` (M.fromList $ catMaybes cs)
           case successor bb of
             Return -> return (calls', bbstarts')
+            FallThrough t -> do
+              efBB (t, hmap M.! t) calls' bbstarts' lmap
             OneTarget t -> do
               efBB (t, hmap M.! t) calls' bbstarts' lmap
             TwoTarget t1 t2 -> do
@@ -166,37 +155,53 @@ emitFromBB cls hmap =  do
     -- TODO(bernhard): implement `emit' as function which accepts a list of
     --                 instructions, so we can use patterns for optimizations
     where
-    emit' :: J.Instruction -> CodeGen e s (Maybe (Word32, MethodInfo))
+    getCurrentOffset :: CodeGen e s (Word32)
+    getCurrentOffset = do
+      ep <- getEntryPoint
+      let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
+      offset <- getCodeOffset
+      return $ w32_ep + (fromIntegral offset)
+
+    emit' :: J.Instruction -> CodeGen e s (Maybe (Word32, TrapInfo))
     emit' (INVOKESTATIC cpidx) = do
-        ep <- getEntryPoint
-        let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
         let l = buildMethodID cls cpidx
-        calladdr <- getCodeOffset
-        let w32_calladdr = w32_ep + (fromIntegral calladdr) :: Word32
-        newNamedLabel (toString l) >>= defineLabel
-        -- TODO(bernhard): better try SIGILL instead of SIGSEGV?
-        mov (Addr 0) eax
-        -- discard arguments (TODO(bernhard): don't hardcode it)
-        add esp (4 :: Word32)
-        -- push result on stack (TODO(bernhard): if any)
+        calladdr <- getCurrentOffset
+        newNamedLabel (show l) >>= defineLabel
+        -- causes SIGILL. in the signal handler we patch it to the acutal call.
+        -- place a nop at the end, therefore the disasm doesn't screw up
+        emit32 (0xffff9090 :: Word32) >> emit8 (0x90 :: Word8)
+        -- discard arguments on stack
+        let argcnt = (methodGetArgsCount cls cpidx) * 4
+        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, MI l)
+    emit' (PUTSTATIC cpidx) = do
+        pop eax
+        trapaddr <- getCurrentOffset
+        mov (Addr 0x00000000) eax -- it's a trap
+        return $ Just $ (trapaddr, SFI $ buildFieldID cls cpidx)
+    emit' (GETSTATIC cpidx) = do
+        trapaddr <- getCurrentOffset
+        mov eax (Addr 0x00000000) -- it's a trap
         push eax
-        return $ Just $ (w32_calladdr, (l, cls, cpidx))
+        return $ Just $ (trapaddr, SFI $ buildFieldID cls cpidx)
     emit' insn = emit insn >> return Nothing
 
     emit :: J.Instruction -> CodeGen e s ()
     emit POP = do -- print dropped value
-        ep <- getEntryPoint
-        let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
+        calladdr <- getCurrentOffset
         -- '5' is the size of the `call' instruction ( + immediate)
-        calladdr <- getCodeOffset
-        let w32_calladdr = 5 + w32_ep + (fromIntegral calladdr) :: Word32
+        let w32_calladdr = 5 + calladdr
         let trapaddr = (fromIntegral getaddr :: Word32)
         call (trapaddr - w32_calladdr)
         add esp (4 :: Word32)
     emit (BIPUSH val) = push ((fromIntegral val) :: Word32)
+    emit (SIPUSH val) = push ((fromIntegral $ ((fromIntegral val) :: Int16)) :: Word32)
     emit (ICONST_0) = push (0 :: Word32)
     emit (ICONST_1) = push (1 :: Word32)
     emit (ICONST_2) = push (2 :: Word32)
+    emit (ICONST_4) = push (4 :: Word32)
     emit (ICONST_5) = push (5 :: Word32)
     emit (ILOAD_ x) = do
         push (Disp (cArgs_ x), ebp)
@@ -240,7 +245,7 @@ emitFromBB cls hmap =  do
         mov esp ebp
         pop ebp
         ret
-    emit _ = do cmovbe eax eax -- dummy
+    emit invalid = error $ "insn not implemented yet: " ++ (show invalid)
 
   cArgs x = (8 + 4 * (fromIntegral x))
   cArgs_ x = (8 + 4 * case x of I0 -> 0; I1 -> 1; I2 -> 2; I3 -> 3)