X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=Mate%2FMethodPool.hs;h=d1df9cf1bb27fe95354b4a2a2daa72c7eab8081c;hb=HEAD;hp=db83f98b51465b917c3795da42a6dc8439d3ce11;hpb=b4cb8e6b7b66e82580b0637ec5a9d9b7531121b4;p=mate.git diff --git a/Mate/MethodPool.hs b/Mate/MethodPool.hs index db83f98..d1df9cf 100644 --- a/Mate/MethodPool.hs +++ b/Mate/MethodPool.hs @@ -5,6 +5,7 @@ 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 @@ -39,11 +40,11 @@ foreign import ccall "&loadLibrary" foreign import ccall "&printGCStats" printGCStatsAddr :: FunPtr (IO ()) -getMethodEntry :: MethodInfo -> IO CPtrdiff +getMethodEntry :: MethodInfo -> IO (CPtrdiff, JpcNpcMap) getMethodEntry mi@(MethodInfo method cm sig) = do mmap <- getMethodMap - entryaddr <- case M.lookup mi mmap of + (entryaddr, jnmap) <- case M.lookup mi mmap of Nothing -> do cls <- getClassFile cm printfMp $ printf "getMethodEntry: no method \"%s\" found. compile it\n" (show mi) @@ -57,11 +58,11 @@ getMethodEntry mi@(MethodInfo method cm sig) = do if scm == "jmate/lang/MateRuntime" then case smethod of "loadLibrary" -> - return . funPtrToAddr $ loadLibraryAddr + return (funPtrToAddr loadLibraryAddr, BI.empty) "printGCStats" -> - return . funPtrToAddr $ printGCStatsAddr + return (funPtrToAddr printGCStatsAddr, BI.empty) "printMemoryUsage" -> - return . funPtrToAddr $ printMemoryUsageAddr + return (funPtrToAddr printMemoryUsageAddr, BI.empty) _ -> error $ "native-call: " ++ smethod ++ " not found." else do @@ -72,16 +73,17 @@ getMethodEntry mi@(MethodInfo method cm sig) = do symbol = sym1 ++ "__" ++ smethod ++ "__" ++ sym2 printfMp $ printf "native-call: symbol: %s\n" symbol nf <- loadNativeFunction symbol - setMethodMap $ M.insert mi nf mmap - return nf + let nf' = (nf, BI.empty) + setMethodMap $ M.insert mi nf' mmap + return nf' else do rawmethod <- parseMethod cls' method sig - entry <- compileBB rawmethod (MethodInfo method (thisClass cls') sig) + entry <- compileBB mi rawmethod (MethodInfo method (thisClass cls') sig) addMethodRef entry mi clsnames - return $ fromIntegral entry + return entry Nothing -> error $ show method ++ " not found. abort" Just w32 -> return w32 - return $ fromIntegral entryaddr + return (fromIntegral entryaddr, jnmap) funPtrToAddr :: Num b => FunPtr a -> b funPtrToAddr = fromIntegral . ptrToIntPtr . castFunPtrToPtr @@ -125,24 +127,24 @@ loadNativeFunction sym = do -- mmap2ptr mmap >>= set_mmap -- demo_mmap -- access Data.Map from C -addMethodRef :: NativeWord -> MethodInfo -> [B.ByteString] -> IO () +addMethodRef :: (NativeWord, JpcNpcMap) -> MethodInfo -> [B.ByteString] -> IO () addMethodRef entry (MethodInfo mmname _ msig) clsnames = do mmap <- getMethodMap let newmap = foldr (\i -> M.insert (MethodInfo mmname i msig) entry) M.empty clsnames setMethodMap $ mmap `M.union` newmap -compileBB :: RawMethod -> MethodInfo -> IO NativeWord -compileBB rawmethod methodinfo = do +compileBB :: MethodInfo -> RawMethod -> MethodInfo -> IO (NativeWord, JpcNpcMap) +compileBB mi rawmethod methodinfo = do tmap <- getTrapMap cls <- getClassFile (methClassName methodinfo) printfJit $ printf "emit code of \"%s\" from \"%s\":\n" (toString $ methName methodinfo) (toString $ methClassName methodinfo) - let ebb = emitFromBB cls rawmethod + let ebb = emitFromBB cls mi rawmethod let cgconfig = defaultCodeGenConfig { codeBufferSize = fromIntegral $ rawCodeLength rawmethod * 32 } - (_, Right right) <- runCodeGenWithConfig ebb () () cgconfig + (jnmap, Right right) <- runCodeGenWithConfig ebb () BI.empty cgconfig - let ((entry, _, _, new_tmap), _) = right + 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) @@ -158,7 +160,7 @@ compileBB rawmethod methodinfo = do -- (2) on getLine, press CTRL+C -- (3) `br *0x'; obtain the address from the disasm above -- (4) `cont' and press enter - return $ fromIntegral $ ptrToIntPtr entry + return (fromIntegral $ ptrToIntPtr entry, jnmap) executeFuncPtr :: NativeWord -> IO ()