debug: use #ifdef guards
[mate.git] / Mate / MethodPool.hs
index 48afcde650f3b81ff10b7a6862cc3e7c96ac650d..a9aee0fd67de2bf991be1b5a95d6097cdcdde8d6 100644 (file)
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
 module Mate.MethodPool where
@@ -9,72 +10,94 @@ import qualified Data.Set as S
 import qualified Data.ByteString.Lazy as B
 import System.Plugins
 
-import Text.Printf
-
 import Foreign.Ptr
 import Foreign.C.Types
 import Foreign.C.String
-import Foreign.StablePtr
 
 import JVM.ClassFile
-import JVM.Converter
 
 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.ClassPool
 
 
-foreign import ccall "get_mmap"
-  get_mmap :: IO (Ptr ())
-
-foreign import ccall "set_mmap"
-  set_mmap :: Ptr () -> IO ()
-
 foreign import ccall "dynamic"
    code_void :: FunPtr (IO ()) -> (IO ())
 
 
-foreign export ccall getMethodEntry :: CUInt -> Ptr () -> Ptr () -> IO CUInt
-getMethodEntry :: CUInt -> Ptr () -> Ptr () -> IO CUInt
-getMethodEntry signal_from ptr_mmap ptr_cmap = do
-  mmap <- ptr2mmap ptr_mmap
-  cmap <- ptr2cmap ptr_cmap
+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@(MethodInfo method cm sig) = cmap M.! w32_from
-  -- TODO(bernhard): replace parsing with some kind of classpool
-  cls <- parseClassFile $ toString $ cm `B.append` ".class"
-  case M.lookup mi mmap of
+  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
     Nothing -> do
-      printf "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi)
-      let mm = lookupMethod method cls
+      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
       case mm of
-        Just mm' -> do
+        Just (mm', clsnames, cls') -> do
             let flags = methodAccessFlags mm'
             case S.member ACC_NATIVE flags of
               False -> do
-                hmap <- parseMethod cls method
-                printMapBB hmap
+                hmap <- parseMethod cls' method
                 case hmap of
                   Just hmap' -> do
-                    entry <- compileBB hmap' mi
-                    return $ fromIntegral $ ((fromIntegral $ ptrToIntPtr entry) :: Word32)
+                    entry <- compileBB hmap' (MethodInfo method (thisClass cls') sig)
+                    addMethodRef entry mi' clsnames
+                    return $ fromIntegral entry
                   Nothing -> error $ (show method) ++ " not found. abort"
               True -> do
-                let symbol = (replace "/" "_" $ toString cm) ++ "__" ++ (toString method) ++ "__" ++ (replace "(" "_" (replace ")" "_" $ toString $ encode sig))
+                -- 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
-                mmap2ptr mmap' >>= set_mmap
+                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
+  case res of
+    Just x -> return $ Just (x, nextclsn, cls)
+    Nothing -> if thisname == "java/lang/Object"
+      then return $ Nothing
+      else do
+        supercl <- getClassFile (superClass cls)
+        lookupMethodRecursive name nextclsn supercl
+  where
+  res = lookupMethod name 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)
@@ -87,7 +110,7 @@ loadNativeFunction sym = do
         ptr <- withCString sym c_lookupSymbol
         if (ptr == nullPtr)
           then error $ "dyn. loading of \"" ++ sym ++ "\" failed."
-          else return $ fromIntegral $ minusPtr ptr nullPtr
+          else return $ fromIntegral $ ptrToIntPtr ptr
 
 -- t_01 :: IO ()
 -- t_01 = do
@@ -100,52 +123,45 @@ loadNativeFunction sym = do
 
 initMethodPool :: IO ()
 initMethodPool = do
-  mmap2ptr M.empty >>= set_mmap
-  cmap2ptr M.empty >>= set_cmap
+  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
 
-compileBB :: MapBB -> MethodInfo -> IO (Ptr Word8)
+
+addMethodRef :: Word32 -> 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
+
+
+compileBB :: MapBB -> MethodInfo -> IO Word32
 compileBB hmap methodinfo = do
-  mmap <- get_mmap >>= ptr2mmap
-  cmap <- get_cmap >>= ptr2cmap
+  tmap <- get_trapmap >>= ptr2trapmap
 
-  -- TODO(bernhard): replace parsing with some kind of classpool
-  cls <- parseClassFile $ toString $ (cName methodinfo) `B.append` ".class"
-  let ebb = emitFromBB cls hmap
-  (_, Right ((entry, _, _, new_cmap), disasm)) <- runCodeGen ebb () ()
-  let w32_entry = ((fromIntegral $ ptrToIntPtr entry) :: Word32)
+  cls <- getClassFile (methClassName methodinfo)
+  let ebb = emitFromBB (methName methodinfo) cls hmap
+  (_, Right right) <- runCodeGen ebb () ()
 
-  let mmap' = M.insert methodinfo w32_entry mmap
-  let cmap' = M.union cmap new_cmap -- prefers elements in cmap
-  mmap2ptr mmap' >>= set_mmap
-  cmap2ptr cmap' >>= set_cmap
+  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) disasm
+  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
   -- (3) `br *0x<addr>'; obtain the address from the disasm above
   -- (4) `cont' and press enter
-  return entry
-
-
-executeFuncPtr :: Ptr Word8 -> IO ()
-executeFuncPtr entry = code_void $ ((castPtrToFunPtr entry) :: FunPtr (IO ()))
-
--- TODO(bernhard): make some typeclass magic 'n stuff
-mmap2ptr :: MMap -> IO (Ptr ())
-mmap2ptr mmap = do
-  ptr_mmap <- newStablePtr mmap
-  return $ castStablePtrToPtr ptr_mmap
-
-ptr2mmap :: Ptr () -> IO MMap
-ptr2mmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr MMap)
+  return $ fromIntegral $ ptrToIntPtr entry
 
-cmap2ptr :: CMap -> IO (Ptr ())
-cmap2ptr cmap = do
-  ptr_cmap <- newStablePtr cmap
-  return $ castStablePtrToPtr ptr_cmap
 
-ptr2cmap :: Ptr () -> IO CMap
-ptr2cmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
+executeFuncPtr :: Word32 -> IO ()
+executeFuncPtr entry =
+  code_void $ ((castPtrToFunPtr $ intPtrToPtr $ fromIntegral entry) :: FunPtr (IO ()))