instanceOf: class hierarchy are considered properly now
[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
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 a entry to,
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   where
210     zipbase base = zipWith (\x y -> (entry y, x + base)) [0,ptrSize..]
211     entry = getname path
212     getname p y = p `B.append` methodName y `B.append` encode (methodSignature y)
213
214
215 calculateFields :: Class Direct -> Maybe ClassInfo -> IO (FieldMap, FieldMap)
216 calculateFields cf superclass = do
217     -- TODO(bernhard): correct sizes. int only atm
218
219     let (sfields, ifields) = partition (S.member ACC_STATIC . fieldAccessFlags) (classFields cf)
220
221     let sc_sm = getsupermap superclass ciStaticMap
222     staticbase <- mallocClassData $ fromIntegral (length sfields) * ptrSize
223     let sm = zipbase (fromIntegral $ ptrToIntPtr staticbase) sfields
224     -- new fields "overwrite" old ones, if they have the same name
225     let staticmap = sm `M.union` sc_sm
226
227     let sc_im = getsupermap superclass ciFieldMap
228     -- "+ (2*ptrsize)" for the method table pointer and GC data
229     let max_off = (+ (2*ptrSize)) $ fromIntegral $ M.size sc_im * ptrSize
230     let im = zipbase max_off ifields
231     -- new fields "overwrite" old ones, if they have the same name
232     let fieldmap = im `M.union` sc_im
233
234     return (staticmap, fieldmap)
235   where
236     zipbase :: Int32 -> [Field Direct] -> FieldMap
237     zipbase base = foldr (\(x,y) -> M.insert (fieldName y) (x + base)) M.empty . zip [0,ptrSize..]
238
239 -- helper
240 getsupermap :: Maybe ClassInfo -> (ClassInfo -> FieldMap) -> FieldMap
241 getsupermap superclass getter = case superclass of Just x -> getter x; Nothing -> M.empty
242
243
244 calculateMethodMap :: Class Direct -> Maybe ClassInfo -> IO (FieldMap, NativeWord)
245 calculateMethodMap cf superclass = do
246     let methods = filter
247                   (\x -> (not . S.member ACC_STATIC . methodAccessFlags) x &&
248                          ((/=) "<init>" . methodName) x)
249                   (classMethods cf)
250     let sc_mm = getsupermap superclass ciMethodMap
251     let max_off = fromIntegral $ M.size sc_mm * ptrSize
252     let mm = zipbase max_off methods
253     let methodmap = M.fromList mm `M.union` sc_mm
254
255     -- (+1): one slot for the interface-table-ptr
256     methodbase <- mallocClassData (((+1) $ fromIntegral $ M.size methodmap) * ptrSize)
257     return (methodmap, fromIntegral $ ptrToIntPtr methodbase)
258   where zipbase base = zipWith (\x y -> (entry y, x + base)) [0,ptrSize..]
259           where entry y = methodName y `B.append` encode (methodSignature y)
260
261
262 loadAndInitClass :: B.ByteString -> IO ClassInfo
263 loadAndInitClass path = do
264   class_map <- getClassMap
265   ci <- case M.lookup path class_map of
266     Nothing -> readClass path
267     Just x -> return x
268
269   -- first try to execute class initializer of superclass
270   when (path /= "java/lang/Object") (void $ loadAndInitClass $ superClass $ ciFile ci)
271
272   -- execute class initializer
273   case lookupMethod "<clinit>" (ciFile ci) of
274     Just m -> do
275       rawmethod <- parseMethod (ciFile ci) "<clinit>" $ MethodSignature [] ReturnsVoid
276       let mi = MethodInfo "<clinit>" path (methodSignature m)
277       entry <- compileBB rawmethod mi
278       addMethodRef entry mi [path]
279       printfCp $ printf "executing static initializer from %s now\n" (toString path)
280       executeFuncPtr entry
281       printfCp $ printf "static initializer from %s done\n" (toString path)
282     Nothing -> return ()
283
284   class_map' <- getClassMap
285   let new_ci = ci { ciInitDone = True }
286   setClassMap $ M.insert path new_ci class_map'
287   return new_ci
288
289
290 readClassFile :: String -> IO (Class Direct)
291 readClassFile path' = readIORef classPaths >>= rcf
292   where
293     path = replace "." "/" path'
294     rcf :: [MClassPath] -> IO (Class Direct)
295     rcf [] = error $ "readClassFile: Class \"" ++ show path ++ "\" not found."
296     rcf (Directory pre:xs) = do
297       let cf = pre ++ path ++ ".class"
298       printfCp $ printf "rcf: searching @ %s for %s\n" (show pre) (show path)
299       b <- doesFileExist cf
300       if b
301         then parseClassFile cf
302         else rcf xs
303     rcf (JAR p:xs) = do
304       printfCp $ printf "rcf: searching %s in JAR\n" (show path)
305       entry <- getEntry p path
306       case entry of
307         Just (LoadedJAR _ cls) -> return cls
308         Nothing -> rcf xs
309         _ -> error $ "readClassFile: Class \"" ++ show path ++ "\" in JAR not found. #1"
310
311 data MClassPath =
312   Directory String |
313   JAR [Tree CPEntry]
314
315 classPaths :: IORef [MClassPath]
316 {-# NOINLINE classPaths #-}
317 classPaths = unsafePerformIO $ newIORef []
318
319 addClassPath :: String -> IO ()
320 addClassPath x = do
321   cps <- readIORef classPaths
322   writeIORef classPaths (Directory x:cps)
323
324 addClassPathJAR :: String -> IO ()
325 addClassPathJAR x = do
326   cps <- readIORef classPaths
327   t <- execClassPath $ addJAR x
328   writeIORef classPaths (JAR t:cps)