X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=Mate%2FClassPool.hs;h=8b1cb4107c7f1c7216c30ef7327582ba21324c75;hb=a4bb7e3e5262cf10f1a013705d8908ad28225491;hp=88749995a59e7e5b95e7f7f40f73a5bb923d7a55;hpb=094e3cea9aa9d638b071fb52a12f04f6ddd80dc1;p=mate.git diff --git a/Mate/ClassPool.hs b/Mate/ClassPool.hs index 8874999..8b1cb41 100644 --- a/Mate/ClassPool.hs +++ b/Mate/ClassPool.hs @@ -1,6 +1,4 @@ -{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} -#include "debug.h" module Mate.ClassPool ( getClassInfo, classLoaded, @@ -16,7 +14,6 @@ module Mate.ClassPool ( ) where import Data.Int -import Data.Word import Data.Binary import qualified Data.Map as M import qualified Data.Set as S @@ -25,12 +22,7 @@ import qualified Data.ByteString.Lazy as B import Data.String.Utils import Control.Monad -#ifdef DEBUG -import Text.Printf -#endif -#ifdef DBG_CLASS -import JVM.Dump -#endif +-- import JVM.Dump import Foreign.Ptr import Foreign.C.Types @@ -51,6 +43,7 @@ import Mate.Types import Mate.Debug import Mate.GarbageAlloc import Mate.NativeSizes +import {-# SOURCE #-} Mate.ClassHierarchy getClassInfo :: B.ByteString -> IO ClassInfo getClassInfo path = do @@ -80,24 +73,25 @@ getFieldOffset path field = do return $ ciFieldMap ci M.! field -- method + signature plz! -getMethodOffset :: B.ByteString -> B.ByteString -> IO Word32 +getMethodOffset :: B.ByteString -> B.ByteString -> IO NativeWord getMethodOffset path method = do ci <- getClassInfo path -- (+ ptrSize) one slot for "interface-table-ptr" return $ (+ ptrSize) $ fromIntegral $ ciMethodMap ci M.! method -getMethodTable :: B.ByteString -> IO Word32 +getMethodTable :: B.ByteString -> IO NativeWord getMethodTable path = do ci <- getClassInfo path return $ ciMethodBase ci -getObjectSize :: B.ByteString -> IO Word32 +getObjectSize :: B.ByteString -> IO NativeWord getObjectSize path = do ci <- getClassInfo path -- TODO(bernhard): correct sizes for different types... let fsize = fromIntegral $ M.size $ ciFieldMap ci -- one slot for "method-table-ptr" - return $ (1 + fsize) * ptrSize + -- one slot for GC-data + return $ (2 + fsize) * ptrSize getStaticFieldAddr :: CPtrdiff -> IO CPtrdiff getStaticFieldAddr from = do @@ -110,7 +104,7 @@ getStaticFieldAddr from = do _ -> error "getFieldAddr: no TrapCause found. abort" -- interface + method + signature plz! -getInterfaceMethodOffset :: B.ByteString -> B.ByteString -> B.ByteString -> IO Word32 +getInterfaceMethodOffset :: B.ByteString -> B.ByteString -> B.ByteString -> IO NativeWord getInterfaceMethodOffset ifname meth sig = do loadInterface ifname ifmmap <- getInterfaceMethodMap @@ -127,9 +121,8 @@ readClass path = do Just cm -> return cm Nothing -> do cfile <- readClassFile $ toString path -#ifdef DBG_CLASS - dumpClass cfile -#endif + -- TODO(bernhard): hDumpClass + -- dumpClass cfile -- load all interfaces, which are implemented by this class sequence_ [ loadInterface i | i <- interfaces cfile ] superclass <- if path /= "java/lang/Object" @@ -146,22 +139,40 @@ readClass path = do -- TODO(bernhard): we have some duplicates in immap (i.e. some -- entries have the same offset), so we could -- save some memory here. - iftable <- mallocClassData ((4*) $ M.size immap) - let w32_iftable = fromIntegral $ ptrToIntPtr iftable :: Word32 + iftable <- mallocClassData ((ptrSize*) $ M.size immap) + let wn_iftable = fromIntegral $ ptrToIntPtr iftable :: NativeWord -- store interface-table at offset 0 in method-table - pokeElemOff (intPtrToPtr $ fromIntegral mbase) 0 w32_iftable - printfCp "staticmap: %s @ %s\n" (show staticmap) (toString path) - printfCp "fieldmap: %s @ %s\n" (show fieldmap) (toString path) - printfCp "methodmap: %s @ %s\n" (show methodmap) (toString path) - printfCp "mbase: 0x%08x\n" mbase - printfCp "interfacemethod: %s @ %s\n" (show immap) (toString path) - printfCp "iftable: 0x%08x\n" w32_iftable + pokeElemOff (intPtrToPtr $ fromIntegral mbase) 0 wn_iftable + let hexDumpMap :: Integral v => String -> M.Map B.ByteString v -> IO () + hexDumpMap header mmap = do + let printValue :: B.ByteString -> IO () + printValue key = printfCp $ printf "\t%-70s: 0x%08x\n" (toString key) val + where val = fromIntegral (mmap M.! key) :: NativeWord + printfCp $ printf "%s\n" header + mapM_ printValue (M.keys mmap) + if mateDEBUG + then do + let strpath = toString path + hexDumpMap ("staticmap @ " ++ strpath) staticmap + hexDumpMap ("fieldmap @ " ++ strpath) fieldmap + hexDumpMap ("methodmap @ " ++ strpath) methodmap + hexDumpMap ("interfacemap @ " ++ strpath) immap + printfCp $ printf "mbase: 0x%08x\n" mbase + printfCp $ printf "iftable: 0x%08x\n" wn_iftable + else return () virtual_map <- getVirtualMap setVirtualMap $ M.insert mbase path virtual_map class_map <- getClassMap let new_ci = ClassInfo path cfile staticmap fieldmap methodmap mbase False setClassMap $ M.insert path new_ci class_map + + -- add Class to Hierarchy + super_mtable <- case superclass of + Nothing -> return 0 + Just x -> getMethodTable $ ciName x + addClassEntry mbase super_mtable (interfaces cfile) + return new_ci @@ -172,7 +183,7 @@ loadInterface path = do case M.lookup path imap of Just _ -> return () Nothing -> do - printfCp "interface: loading \"%s\"\n" $ toString path + printfCp $ printf "interface: loading \"%s\"\n" $ toString path cfile <- readClassFile $ toString path -- load "superinterfaces" first sequence_ [ loadInterface i | i <- interfaces cfile ] @@ -181,11 +192,11 @@ loadInterface path = do -- load map again, because there could be new entries now -- due to loading superinterfaces imap' <- getInterfaceMap - let max_off = fromIntegral $ M.size immap * 4 + let max_off = fromIntegral $ M.size immap * ptrSize -- create index of methods by this interface let mm = zipbase max_off (classMethods cfile) - -- create for each method from *every* superinterface a entry to, + -- create for each method from *every* superinterface an entry too, -- but just put in the same offset as it is already in the map let (ifnames, methodnames) = unzip $ concat [ zip (repeat ifname) (classMethods $ imap' M.! ifname) @@ -195,8 +206,11 @@ loadInterface path = do -- merge all offset tables setInterfaceMethodMap $ M.fromList sm `M.union` M.fromList mm `M.union` immap setInterfaceMap $ M.insert path cfile imap' + + -- add Interface to Hierarchy + addInterfaceEntry path (interfaces cfile) where - zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..] + zipbase base = zipWith (\x y -> (entry y, x + base)) [0,ptrSize..] entry = getname path getname p y = p `B.append` methodName y `B.append` encode (methodSignature y) @@ -208,14 +222,14 @@ calculateFields cf superclass = do let (sfields, ifields) = partition (S.member ACC_STATIC . fieldAccessFlags) (classFields cf) let sc_sm = getsupermap superclass ciStaticMap - staticbase <- mallocClassData $ fromIntegral (length sfields) * 4 + staticbase <- mallocClassData $ fromIntegral (length sfields) * ptrSize let sm = zipbase (fromIntegral $ ptrToIntPtr staticbase) sfields -- new fields "overwrite" old ones, if they have the same name let staticmap = sm `M.union` sc_sm let sc_im = getsupermap superclass ciFieldMap - -- "+ 4" for the method table pointer - let max_off = (4+) $ fromIntegral $ M.size sc_im * 4 + -- "+ (2*ptrsize)" for the method table pointer and GC data + let max_off = (+ (2*ptrSize)) $ fromIntegral $ M.size sc_im * ptrSize let im = zipbase max_off ifields -- new fields "overwrite" old ones, if they have the same name let fieldmap = im `M.union` sc_im @@ -223,28 +237,28 @@ calculateFields cf superclass = do return (staticmap, fieldmap) where zipbase :: Int32 -> [Field Direct] -> FieldMap - zipbase base = foldr (\(x,y) -> M.insert (fieldName y) (x + base)) M.empty . zip [0,4..] + zipbase base = foldr (\(x,y) -> M.insert (fieldName y) (x + base)) M.empty . zip [0,ptrSize..] -- helper getsupermap :: Maybe ClassInfo -> (ClassInfo -> FieldMap) -> FieldMap getsupermap superclass getter = case superclass of Just x -> getter x; Nothing -> M.empty -calculateMethodMap :: Class Direct -> Maybe ClassInfo -> IO (FieldMap, Word32) +calculateMethodMap :: Class Direct -> Maybe ClassInfo -> IO (FieldMap, NativeWord) calculateMethodMap cf superclass = do let methods = filter (\x -> (not . S.member ACC_STATIC . methodAccessFlags) x && ((/=) "" . methodName) x) (classMethods cf) let sc_mm = getsupermap superclass ciMethodMap - let max_off = fromIntegral $ M.size sc_mm * 4 + let max_off = fromIntegral $ M.size sc_mm * ptrSize let mm = zipbase max_off methods let methodmap = M.fromList mm `M.union` sc_mm -- (+1): one slot for the interface-table-ptr - methodbase <- mallocClassData (((+1) $ fromIntegral $ M.size methodmap) * 4) + methodbase <- mallocClassData (((+1) $ fromIntegral $ M.size methodmap) * ptrSize) return (methodmap, fromIntegral $ ptrToIntPtr methodbase) - where zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..] + where zipbase base = zipWith (\x y -> (entry y, x + base)) [0,ptrSize..] where entry y = methodName y `B.append` encode (methodSignature y) @@ -265,9 +279,9 @@ loadAndInitClass path = do let mi = MethodInfo "" path (methodSignature m) entry <- compileBB rawmethod mi addMethodRef entry mi [path] - printfCp "executing static initializer from %s now\n" (toString path) + printfCp $ printf "executing static initializer from %s now\n" (toString path) executeFuncPtr entry - printfCp "static initializer from %s done\n" (toString path) + printfCp $ printf "static initializer from %s done\n" (toString path) Nothing -> return () class_map' <- getClassMap @@ -284,13 +298,13 @@ readClassFile path' = readIORef classPaths >>= rcf rcf [] = error $ "readClassFile: Class \"" ++ show path ++ "\" not found." rcf (Directory pre:xs) = do let cf = pre ++ path ++ ".class" - printfCp "rcf: searching @ %s for %s\n" (show pre) (show path) + printfCp $ printf "rcf: searching @ %s for %s\n" (show pre) (show path) b <- doesFileExist cf if b then parseClassFile cf else rcf xs rcf (JAR p:xs) = do - printfCp "rcf: searching %s in JAR\n" (show path) + printfCp $ printf "rcf: searching %s in JAR\n" (show path) entry <- getEntry p path case entry of Just (LoadedJAR _ cls) -> return cls