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