codegen: handle exceptions of a method
[mate.git] / Mate / MethodPool.hs
index a9aee0fd67de2bf991be1b5a95d6097cdcdde8d6..d1df9cf1bb27fe95354b4a2a2daa72c7eab8081c 100644 (file)
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
 module Mate.MethodPool where
@@ -6,9 +5,11 @@ module Mate.MethodPool where
 import Data.Binary
 import Data.String.Utils
 import qualified Data.Map as M
+import qualified Data.Bimap as BI
 import qualified Data.Set as S
 import qualified Data.ByteString.Lazy as B
 import System.Plugins
+import Control.Monad
 
 import Foreign.Ptr
 import Foreign.C.Types
@@ -17,151 +18,151 @@ import Foreign.C.String
 import JVM.ClassFile
 
 import Harpy
-#ifdef DEBUG
 import Harpy.X86Disassembler
 
-import Text.Printf
-#endif
-
 import Mate.BasicBlocks
 import Mate.Types
-import Mate.X86CodeGen
-import Mate.Utilities
+import Mate.NativeMachine
 import Mate.ClassPool
-
+import Mate.Debug
+import Mate.Utilities
+import Mate.Rts()
 
 foreign import ccall "dynamic"
-   code_void :: FunPtr (IO ()) -> (IO ())
-
-
-foreign export ccall getMethodEntry :: CUInt -> CUInt -> IO CUInt
-getMethodEntry :: CUInt -> CUInt -> IO CUInt
-getMethodEntry signal_from methodtable = do
-  mmap <- get_methodmap >>= ptr2methodmap
-  tmap <- get_trapmap >>= ptr2trapmap
-  vmap <- get_virtualmap >>= ptr2virtualmap
-
-  let w32_from = fromIntegral signal_from
-  let mi = tmap M.! w32_from
-  let mi'@(MethodInfo method cm sig) =
-        case mi of
-          (MI x) -> x
-          (VI (MethodInfo methname _ msig)) ->
-              (MethodInfo methname (vmap M.! (fromIntegral methodtable)) msig)
-          _ -> error $ "getMethodEntry: no trapInfo. abort."
-  case M.lookup mi' mmap of
+   code_void :: FunPtr (IO ()) -> IO ()
+
+foreign import ccall "&printMemoryUsage"
+  printMemoryUsageAddr :: FunPtr (IO ())
+foreign import ccall "&loadLibrary"
+  loadLibraryAddr :: FunPtr (IO ())
+
+foreign import ccall "&printGCStats"
+  printGCStatsAddr :: FunPtr (IO ())
+
+getMethodEntry :: MethodInfo -> IO (CPtrdiff, JpcNpcMap)
+getMethodEntry mi@(MethodInfo method cm sig) = do
+  mmap <- getMethodMap
+
+  (entryaddr, jnmap) <- case M.lookup mi mmap of
     Nothing -> do
       cls <- getClassFile cm
-#ifdef DEBUG
-      printf "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi')
-#endif
-      mm <- lookupMethodRecursive method [] cls
+      printfMp $ printf "getMethodEntry: no method \"%s\" found. compile it\n" (show mi)
+      mm <- lookupMethodRecursive method sig [] cls
       case mm of
         Just (mm', clsnames, cls') -> do
             let flags = methodAccessFlags mm'
-            case S.member ACC_NATIVE flags of
-              False -> do
-                hmap <- parseMethod cls' method
-                case hmap of
-                  Just hmap' -> do
-                    entry <- compileBB hmap' (MethodInfo method (thisClass cls') sig)
-                    addMethodRef entry mi' clsnames
-                    return $ fromIntegral entry
-                  Nothing -> error $ (show method) ++ " not found. abort"
-              True -> do
-                -- TODO(bernhard): cleaner please... *do'h*
-                let symbol = (replace "/" "_" $ toString cm) ++ "__" ++ (toString method) ++ "__" ++ (replace ";" "_" $ replace "/" "_" $ replace "(" "_" (replace ")" "_" $ toString $ encode sig))
-#ifdef DEBUG
-                printf "native-call: symbol: %s\n" symbol
-#endif
-                nf <- loadNativeFunction symbol
-                let w32_nf = fromIntegral nf
-                let mmap' = M.insert mi' w32_nf mmap
-                methodmap2ptr mmap' >>= set_methodmap
-                return nf
-        Nothing -> error $ (show method) ++ " not found. abort"
-    Just w32 -> return (fromIntegral w32)
-
-lookupMethodRecursive :: B.ByteString -> [B.ByteString] -> Class Resolved
-                         -> IO (Maybe ((Method Resolved, [B.ByteString], Class Resolved)))
-lookupMethodRecursive name clsnames cls = do
+            if S.member ACC_NATIVE flags
+              then do
+                let scm = toString cm; smethod = toString method
+                if scm == "jmate/lang/MateRuntime" then
+                  case smethod of
+                    "loadLibrary" ->
+                       return (funPtrToAddr loadLibraryAddr, BI.empty)
+                    "printGCStats" ->
+                       return (funPtrToAddr printGCStatsAddr, BI.empty)
+                    "printMemoryUsage" ->
+                       return (funPtrToAddr printMemoryUsageAddr, BI.empty)
+                    _ ->
+                       error $ "native-call: " ++ smethod ++ " not found."
+                else do
+                  -- TODO(bernhard): cleaner please... *do'h*
+                  let sym1 = replace "/" "_" scm
+                      parenth = replace "(" "_" $ replace ")" "_" $ toString $ encode sig
+                      sym2 = replace ";" "_" $ replace "/" "_" parenth
+                      symbol = sym1 ++ "__" ++ smethod ++ "__" ++ sym2
+                  printfMp $ printf "native-call: symbol: %s\n" symbol
+                  nf <- loadNativeFunction symbol
+                  let nf' = (nf, BI.empty)
+                  setMethodMap $ M.insert mi nf' mmap
+                  return nf'
+              else do
+                rawmethod <- parseMethod cls' method sig
+                entry <- compileBB mi rawmethod (MethodInfo method (thisClass cls') sig)
+                addMethodRef entry mi clsnames
+                return entry
+        Nothing -> error $ show method ++ " not found. abort"
+    Just w32 -> return w32
+  return (fromIntegral entryaddr, jnmap)
+
+funPtrToAddr :: Num b => FunPtr a -> b
+funPtrToAddr = fromIntegral . ptrToIntPtr . castFunPtrToPtr
+
+lookupMethodRecursive :: B.ByteString -> MethodSignature -> [B.ByteString] -> Class Direct
+                         -> IO (Maybe (Method Direct, [B.ByteString], Class Direct))
+lookupMethodRecursive name sig clsnames cls =
   case res of
     Just x -> return $ Just (x, nextclsn, cls)
     Nothing -> if thisname == "java/lang/Object"
-      then return Nothing
+      then return Nothing
       else do
         supercl <- getClassFile (superClass cls)
-        lookupMethodRecursive name nextclsn supercl
+        lookupMethodRecursive name sig nextclsn supercl
   where
-  res = lookupMethod name cls
-  thisname = thisClass cls
-  nextclsn :: [B.ByteString]
-  nextclsn = thisname:clsnames
+    res = lookupMethodSig name sig cls
+    thisname = thisClass cls
+    nextclsn :: [B.ByteString]
+    nextclsn = thisname:clsnames
 
 -- TODO(bernhard): UBERHAX.  ghc patch?
 foreign import ccall safe "lookupSymbol"
    c_lookupSymbol :: CString -> IO (Ptr a)
 
-loadNativeFunction :: String -> IO (CUInt)
+loadNativeFunction :: String -> IO NativeWord
 loadNativeFunction sym = do
-        _ <- loadRawObject "ffi/native.o"
-        -- TODO(bernhard): WTF
-        resolveObjs (return ())
-        ptr <- withCString sym c_lookupSymbol
-        if (ptr == nullPtr)
-          then error $ "dyn. loading of \"" ++ sym ++ "\" failed."
-          else return $ fromIntegral $ ptrToIntPtr ptr
+  _ <- loadRawObject "ffi/native.o"
+  -- TODO(bernhard): WTF
+  resolveObjs (return ())
+  ptr <- withCString sym c_lookupSymbol
+  if ptr == nullPtr
+    then error $ "dyn. loading of \"" ++ sym ++ "\" failed."
+    else return $ fromIntegral $ ptrToIntPtr ptr
 
 -- t_01 :: IO ()
 -- t_01 = do
 --   (entry, _) <- testCase "./tests/Fib.class" "fib"
---   let int_entry = ((fromIntegral $ ptrToIntPtr entry) :: Word32)
+--   let int_entry = ((fromIntegral $ ptrToIntPtr entry) :: NativeWord)
 --   let mmap = M.insert ("fib" :: String) int_entry M.empty
 --   mapM_ (\(x,y) -> printf "%s at 0x%08x\n" x y) $ M.toList mmap
 --   mmap2ptr mmap >>= set_mmap
 --   demo_mmap -- access Data.Map from C
 
-initMethodPool :: IO ()
-initMethodPool = do
-  methodmap2ptr M.empty >>= set_methodmap
-  trapmap2ptr M.empty >>= set_trapmap
-  classmap2ptr M.empty >>= set_classmap
-  virtualmap2ptr M.empty >>= set_virtualmap
-  stringsmap2ptr M.empty >>= set_stringsmap
-
-
-addMethodRef :: Word32 -> MethodInfo -> [B.ByteString] -> IO ()
+addMethodRef :: (NativeWord, JpcNpcMap) -> MethodInfo -> [B.ByteString] -> IO ()
 addMethodRef entry (MethodInfo mmname _ msig) clsnames = do
-  mmap <- get_methodmap >>= ptr2methodmap
-  let newmap = M.fromList $ map (\x -> ((MethodInfo mmname x msig), entry)) clsnames
-  methodmap2ptr (mmap `M.union` newmap) >>= set_methodmap
+  mmap <- getMethodMap
+  let newmap = foldr (\i -> M.insert (MethodInfo mmname i msig) entry) M.empty clsnames
+  setMethodMap $ mmap `M.union` newmap
 
 
-compileBB :: MapBB -> MethodInfo -> IO Word32
-compileBB hmap methodinfo = do
-  tmap <- get_trapmap >>= ptr2trapmap
+compileBB :: MethodInfo -> RawMethod -> MethodInfo -> IO (NativeWord, JpcNpcMap)
+compileBB mi rawmethod methodinfo = do
+  tmap <- getTrapMap
 
   cls <- getClassFile (methClassName methodinfo)
-  let ebb = emitFromBB (methName methodinfo) cls hmap
-  (_, Right right) <- runCodeGen ebb () ()
-
-  let ((entry, _, _, new_tmap), _) = right
-  let tmap' = M.union tmap new_tmap -- prefers elements in cmap
-  trapmap2ptr tmap' >>= set_trapmap
-
-#ifdef DEBUG
-  printf "disasm:\n"
-  mapM_ (putStrLn . showAtt) (snd right)
-#endif
-  -- UNCOMMENT NEXT LINE FOR GDB FUN
-  -- _ <- getLine
-  -- (1) start it with `gdb ./mate' and then `run <classfile>'
-  -- (2) on getLine, press ctrl+c
+  printfJit $ printf "emit code of \"%s\" from \"%s\":\n" (toString $ methName methodinfo) (toString $ methClassName methodinfo)
+  let ebb = emitFromBB cls mi rawmethod
+  let cgconfig = defaultCodeGenConfig { codeBufferSize = fromIntegral $ rawCodeLength rawmethod * 32 }
+  (jnmap, Right right) <- runCodeGenWithConfig ebb () BI.empty cgconfig
+
+  let ((entry, _, new_tmap), _) = right
+  setTrapMap $ tmap `M.union` new_tmap -- prefers elements in tmap
+
+  printfJit $ printf "generated code of \"%s\" from \"%s\":\n" (toString $ methName methodinfo) (toString $ methClassName methodinfo)
+  printfJit $ printf "\tstacksize: 0x%04x, locals: 0x%04x\n" (rawStackSize rawmethod) (rawLocals rawmethod)
+  when mateDEBUG $ mapM_ (printfJit . printf "%s\n" . showIntel) (snd right)
+  printfJit $ printf "\n\n"
+  -- UNCOMMENT NEXT LINES FOR GDB FUN
+  -- if (toString $ methName methodinfo) == "thejavamethodIwant2debug"
+  --   then putStrLn "press CTRL+C now for setting a breakpoint. then `c' and ENTER for continue" >> getLine
+  --   else return "foo"
+  -- (1) build a debug build (see HACKING) and execute `make tests/Fib.gdb'
+  --     for example, where the suffix is important
+  -- (2) on getLine, press CTRL+C
   -- (3) `br *0x<addr>'; obtain the address from the disasm above
   -- (4) `cont' and press enter
-  return $ fromIntegral $ ptrToIntPtr entry
+  return (fromIntegral $ ptrToIntPtr entry, jnmap)
 
 
-executeFuncPtr :: Word32 -> IO ()
+executeFuncPtr :: NativeWord -> IO ()
 executeFuncPtr entry =
-  code_void ((castPtrToFunPtr $ intPtrToPtr $ fromIntegral entry) :: FunPtr (IO ()))
+  code_void ((castPtrToFunPtr $ intPtrToPtr $ fromIntegral entry) :: FunPtr (IO ()))