instanceOf: also consider interfaces
[mate.git] / Mate / ClassPool.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 module Mate.ClassPool (
3   getClassInfo,
4   classLoaded,
5   getClassFile,
6   getMethodTable,
7   getObjectSize,
8   getMethodOffset,
9   getFieldOffset,
10   getStaticFieldAddr,
11   getInterfaceMethodOffset,
12   addClassPath,
13   addClassPathJAR
14   ) where
15
16 import Data.Int
17 import Data.Binary
18 import qualified Data.Map as M
19 import qualified Data.Set as S
20 import Data.List
21 import qualified Data.ByteString.Lazy as B
22 import Data.String.Utils
23 import Control.Monad
24
25 -- import JVM.Dump
26
27 import Foreign.Ptr
28 import Foreign.C.Types
29 import Foreign.Storable
30
31 import Data.IORef
32 import System.IO.Unsafe
33 import System.Directory
34
35 import JVM.ClassFile
36 import JVM.Converter
37 import Java.ClassPath hiding (Directory)
38 import Java.JAR
39
40 import Mate.BasicBlocks
41 import {-# SOURCE #-} Mate.MethodPool
42 import Mate.Types
43 import Mate.Debug
44 import Mate.GarbageAlloc
45 import Mate.NativeSizes
46 import {-# SOURCE #-} Mate.ClassHierarchy
47
48 getClassInfo :: B.ByteString -> IO ClassInfo
49 getClassInfo path = do
50   class_map <- getClassMap
51   case M.lookup path class_map of
52     Nothing -> loadAndInitClass path
53     Just ci -> return ci
54
55 classLoaded :: B.ByteString -> IO Bool
56 classLoaded path = do
57   class_map <- getClassMap
58   return $ M.member path class_map
59
60 getClassFile :: B.ByteString -> IO (Class Direct)
61 getClassFile path = do
62   ci <- getClassInfo path
63   return $ ciFile ci
64
65 getStaticFieldOffset :: B.ByteString -> B.ByteString -> IO CPtrdiff
66 getStaticFieldOffset path field = do
67   ci <- getClassInfo path
68   return $ fromIntegral $ ciStaticMap ci M.! field
69
70 getFieldOffset :: B.ByteString -> B.ByteString -> IO Int32
71 getFieldOffset path field = do
72   ci <- getClassInfo path
73   return $ ciFieldMap ci M.! field
74
75 -- method + signature plz!
76 getMethodOffset :: B.ByteString -> B.ByteString -> IO NativeWord
77 getMethodOffset path method = do
78   ci <- getClassInfo path
79   -- (+ ptrSize) one slot for "interface-table-ptr"
80   return $ (+ ptrSize) $ fromIntegral $ ciMethodMap ci M.! method
81
82 getMethodTable :: B.ByteString -> IO NativeWord
83 getMethodTable path = do
84   ci <- getClassInfo path
85   return $ ciMethodBase ci
86
87 getObjectSize :: B.ByteString -> IO NativeWord
88 getObjectSize path = do
89   ci <- getClassInfo path
90   -- TODO(bernhard): correct sizes for different types...
91   let fsize = fromIntegral $ M.size $ ciFieldMap ci
92   -- one slot for "method-table-ptr"
93   -- one slot for GC-data
94   return $ (2 + fsize) * ptrSize
95
96 getStaticFieldAddr :: CPtrdiff -> IO CPtrdiff
97 getStaticFieldAddr from = do
98   trapmap <- getTrapMap
99   let w32_from = fromIntegral from
100   let sfi = trapmap M.! w32_from
101   setTrapMap $ M.delete w32_from trapmap
102   case sfi of
103     (StaticField (StaticFieldInfo cls field)) -> getStaticFieldOffset cls field
104     _ -> error "getFieldAddr: no TrapCause found. abort"
105
106 -- interface + method + signature plz!
107 getInterfaceMethodOffset :: B.ByteString -> B.ByteString -> B.ByteString -> IO NativeWord
108 getInterfaceMethodOffset ifname meth sig = do
109   loadInterface ifname
110   ifmmap <- getInterfaceMethodMap
111   let k = ifname `B.append` meth `B.append` sig
112   case M.lookup k ifmmap of
113     Just w32 -> return $ w32 + 4
114     Nothing -> error "getInterfaceMethodOffset: no offset set"
115
116
117 readClass :: B.ByteString -> IO ClassInfo
118 readClass path = do
119   class_map' <- getClassMap
120   case M.lookup path class_map' of
121     Just cm -> return cm
122     Nothing -> do
123       cfile <- readClassFile $ toString path
124       -- TODO(bernhard): hDumpClass
125       -- dumpClass cfile
126       -- load all interfaces, which are implemented by this class
127       sequence_ [ loadInterface i | i <- interfaces cfile ]
128       superclass <- if path /= "java/lang/Object"
129           then do
130             sc <- readClass $ superClass cfile
131             return $ Just sc
132           else return Nothing
133
134       (staticmap, fieldmap) <- calculateFields cfile superclass
135       (methodmap, mbase) <- calculateMethodMap cfile superclass
136       immap <- getInterfaceMethodMap
137
138       -- allocate interface offset table for this class
139       -- TODO(bernhard): we have some duplicates in immap (i.e. some
140       --                 entries have the same offset), so we could
141       --                 save some memory here.
142       iftable <- mallocClassData ((ptrSize*) $ M.size immap)
143       let wn_iftable = fromIntegral $ ptrToIntPtr iftable :: NativeWord
144       -- store interface-table at offset 0 in method-table
145       pokeElemOff (intPtrToPtr $ fromIntegral mbase) 0 wn_iftable
146       let hexDumpMap :: Integral v => String -> M.Map B.ByteString v -> IO ()
147           hexDumpMap header mmap = do
148             let printValue :: B.ByteString -> IO ()
149                 printValue key = printfCp $ printf "\t%-70s: 0x%08x\n" (toString key) val
150                   where val = fromIntegral (mmap M.! key) :: NativeWord
151             printfCp $ printf "%s\n" header
152             mapM_ printValue (M.keys mmap)
153       if mateDEBUG
154         then do
155           let strpath = toString path
156           hexDumpMap ("staticmap @ " ++ strpath) staticmap
157           hexDumpMap ("fieldmap @ " ++ strpath) fieldmap
158           hexDumpMap ("methodmap @ " ++ strpath) methodmap
159           hexDumpMap ("interfacemap @ " ++ strpath) immap
160           printfCp $ printf "mbase:   0x%08x\n" mbase
161           printfCp $ printf "iftable: 0x%08x\n" wn_iftable
162         else return ()
163       virtual_map <- getVirtualMap
164       setVirtualMap $ M.insert mbase path virtual_map
165
166       class_map <- getClassMap
167       let new_ci = ClassInfo path cfile staticmap fieldmap methodmap mbase False
168       setClassMap $ M.insert path new_ci class_map
169
170       -- add Class to Hierarchy
171       super_mtable <- case superclass of
172         Nothing -> return 0
173         Just x -> getMethodTable $ ciName x
174       addClassEntry mbase super_mtable (interfaces cfile)
175
176       return new_ci
177
178
179 loadInterface :: B.ByteString -> IO ()
180 loadInterface path = do
181   imap <- getInterfaceMap
182   -- interface already loaded?
183   case M.lookup path imap of
184     Just _ -> return ()
185     Nothing -> do
186       printfCp $ printf "interface: loading \"%s\"\n" $ toString path
187       cfile <- readClassFile $ toString path
188       -- load "superinterfaces" first
189       sequence_ [ loadInterface i | i <- interfaces cfile ]
190       immap <- getInterfaceMethodMap
191
192       -- load map again, because there could be new entries now
193       -- due to loading superinterfaces
194       imap' <- getInterfaceMap
195       let max_off = fromIntegral $ M.size immap * ptrSize
196       -- create index of methods by this interface
197       let mm = zipbase max_off (classMethods cfile)
198
199       -- create for each method from *every* superinterface an entry too,
200       -- but just put in the same offset as it is already in the map
201       let (ifnames, methodnames) = unzip $ concat
202             [ zip (repeat ifname) (classMethods $ imap' M.! ifname)
203             | ifname <- interfaces cfile ]
204       let sm = zipWith (\x y -> (entry y, immap M.! getname x y)) ifnames methodnames
205
206       -- merge all offset tables
207       setInterfaceMethodMap $ M.fromList sm `M.union` M.fromList mm `M.union` immap
208       setInterfaceMap $ M.insert path cfile imap'
209
210       -- add Interface to Hierarchy
211       addInterfaceEntry path (interfaces cfile)
212   where
213     zipbase base = zipWith (\x y -> (entry y, x + base)) [0,ptrSize..]
214     entry = getname path
215     getname p y = p `B.append` methodName y `B.append` encode (methodSignature y)
216
217
218 calculateFields :: Class Direct -> Maybe ClassInfo -> IO (FieldMap, FieldMap)
219 calculateFields cf superclass = do
220     -- TODO(bernhard): correct sizes. int only atm
221
222     let (sfields, ifields) = partition (S.member ACC_STATIC . fieldAccessFlags) (classFields cf)
223
224     let sc_sm = getsupermap superclass ciStaticMap
225     staticbase <- mallocClassData $ fromIntegral (length sfields) * ptrSize
226     let sm = zipbase (fromIntegral $ ptrToIntPtr staticbase) sfields
227     -- new fields "overwrite" old ones, if they have the same name
228     let staticmap = sm `M.union` sc_sm
229
230     let sc_im = getsupermap superclass ciFieldMap
231     -- "+ (2*ptrsize)" for the method table pointer and GC data
232     let max_off = (+ (2*ptrSize)) $ fromIntegral $ M.size sc_im * ptrSize
233     let im = zipbase max_off ifields
234     -- new fields "overwrite" old ones, if they have the same name
235     let fieldmap = im `M.union` sc_im
236
237     return (staticmap, fieldmap)
238   where
239     zipbase :: Int32 -> [Field Direct] -> FieldMap
240     zipbase base = foldr (\(x,y) -> M.insert (fieldName y) (x + base)) M.empty . zip [0,ptrSize..]
241
242 -- helper
243 getsupermap :: Maybe ClassInfo -> (ClassInfo -> FieldMap) -> FieldMap
244 getsupermap superclass getter = case superclass of Just x -> getter x; Nothing -> M.empty
245
246
247 calculateMethodMap :: Class Direct -> Maybe ClassInfo -> IO (FieldMap, NativeWord)
248 calculateMethodMap cf superclass = do
249     let methods = filter
250                   (\x -> (not . S.member ACC_STATIC . methodAccessFlags) x &&
251                          ((/=) "<init>" . methodName) x)
252                   (classMethods cf)
253     let sc_mm = getsupermap superclass ciMethodMap
254     let max_off = fromIntegral $ M.size sc_mm * ptrSize
255     let mm = zipbase max_off methods
256     let methodmap = M.fromList mm `M.union` sc_mm
257
258     -- (+1): one slot for the interface-table-ptr
259     methodbase <- mallocClassData (((+1) $ fromIntegral $ M.size methodmap) * ptrSize)
260     return (methodmap, fromIntegral $ ptrToIntPtr methodbase)
261   where zipbase base = zipWith (\x y -> (entry y, x + base)) [0,ptrSize..]
262           where entry y = methodName y `B.append` encode (methodSignature y)
263
264
265 loadAndInitClass :: B.ByteString -> IO ClassInfo
266 loadAndInitClass path = do
267   class_map <- getClassMap
268   ci <- case M.lookup path class_map of
269     Nothing -> readClass path
270     Just x -> return x
271
272   -- first try to execute class initializer of superclass
273   when (path /= "java/lang/Object") (void $ loadAndInitClass $ superClass $ ciFile ci)
274
275   -- execute class initializer
276   case lookupMethod "<clinit>" (ciFile ci) of
277     Just m -> do
278       rawmethod <- parseMethod (ciFile ci) "<clinit>" $ MethodSignature [] ReturnsVoid
279       let mi = MethodInfo "<clinit>" path (methodSignature m)
280       entry <- compileBB rawmethod mi
281       addMethodRef entry mi [path]
282       printfCp $ printf "executing static initializer from %s now\n" (toString path)
283       executeFuncPtr entry
284       printfCp $ printf "static initializer from %s done\n" (toString path)
285     Nothing -> return ()
286
287   class_map' <- getClassMap
288   let new_ci = ci { ciInitDone = True }
289   setClassMap $ M.insert path new_ci class_map'
290   return new_ci
291
292
293 readClassFile :: String -> IO (Class Direct)
294 readClassFile path' = readIORef classPaths >>= rcf
295   where
296     path = replace "." "/" path'
297     rcf :: [MClassPath] -> IO (Class Direct)
298     rcf [] = error $ "readClassFile: Class \"" ++ show path ++ "\" not found."
299     rcf (Directory pre:xs) = do
300       let cf = pre ++ path ++ ".class"
301       printfCp $ printf "rcf: searching @ %s for %s\n" (show pre) (show path)
302       b <- doesFileExist cf
303       if b
304         then parseClassFile cf
305         else rcf xs
306     rcf (JAR p:xs) = do
307       printfCp $ printf "rcf: searching %s in JAR\n" (show path)
308       entry <- getEntry p path
309       case entry of
310         Just (LoadedJAR _ cls) -> return cls
311         Nothing -> rcf xs
312         _ -> error $ "readClassFile: Class \"" ++ show path ++ "\" in JAR not found. #1"
313
314 data MClassPath =
315   Directory String |
316   JAR [Tree CPEntry]
317
318 classPaths :: IORef [MClassPath]
319 {-# NOINLINE classPaths #-}
320 classPaths = unsafePerformIO $ newIORef []
321
322 addClassPath :: String -> IO ()
323 addClassPath x = do
324   cps <- readIORef classPaths
325   writeIORef classPaths (Directory x:cps)
326
327 addClassPathJAR :: String -> IO ()
328 addClassPathJAR x = do
329   cps <- readIORef classPaths
330   t <- execClassPath $ addJAR x
331   writeIORef classPaths (JAR t:cps)