b7c394c8f8b54b65df9975a6dd835a54064adaba
[mate.git] / Mate / ClassPool.hs
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ForeignFunctionInterface #-}
4 #include "debug.h"
5 module Mate.ClassPool (
6   getClassInfo,
7   getClassFile,
8   getMethodTable,
9   getObjectSize,
10   getMethodOffset,
11   getFieldOffset,
12   getStaticFieldAddr,
13   getInterfaceMethodOffset
14   ) where
15
16 import Data.Int
17 import Data.Word
18 import Data.Binary
19 import qualified Data.Map as M
20 import qualified Data.Set as S
21 import qualified Data.ByteString.Lazy as B
22 import Control.Monad
23
24 #ifdef DEBUG
25 import Text.Printf
26 #endif
27 #ifdef DBG_CLASS
28 import JVM.Dump
29 #endif
30
31 import Foreign.Ptr
32 import Foreign.C.Types
33 import Foreign.Storable
34
35 import JVM.ClassFile
36 import JVM.Converter
37
38 import Mate.BasicBlocks
39 import {-# SOURCE #-} Mate.MethodPool
40 import Mate.Types
41 import Mate.Utilities
42 import Mate.Debug
43 import Mate.GarbageAlloc
44
45 getClassInfo :: B.ByteString -> IO ClassInfo
46 getClassInfo path = do
47   class_map <- get_classmap >>= ptr2classmap
48   case M.lookup path class_map of
49     Nothing -> loadAndInitClass path
50     Just ci -> return ci
51
52 getClassFile :: B.ByteString -> IO (Class Resolved)
53 getClassFile path = do
54   ci <- getClassInfo path
55   return $ ciFile ci
56
57 getStaticFieldOffset :: B.ByteString -> B.ByteString -> IO CUInt
58 getStaticFieldOffset path field = do
59   ci <- getClassInfo path
60   return $ fromIntegral $ ciStaticMap ci M.! field
61
62 getFieldOffset :: B.ByteString -> B.ByteString -> IO Int32
63 getFieldOffset path field = do
64   ci <- getClassInfo path
65   return $ ciFieldMap ci M.! field
66
67 -- method + signature plz!
68 getMethodOffset :: B.ByteString -> B.ByteString -> IO Word32
69 getMethodOffset path method = do
70   ci <- getClassInfo path
71   -- (4+) one slot for "interface-table-ptr"
72   return $ (+4) $ fromIntegral $ ciMethodMap ci M.! method
73
74 getMethodTable :: B.ByteString -> IO Word32
75 getMethodTable path = do
76   ci <- getClassInfo path
77   return $ ciMethodBase ci
78
79 getObjectSize :: B.ByteString -> IO Word32
80 getObjectSize path = do
81   ci <- getClassInfo path
82   -- TODO(bernhard): correct sizes for different types...
83   let fsize = fromIntegral $ M.size $ ciFieldMap ci
84   -- one slot for "method-table-ptr"
85   return $ (1 + fsize) * 4
86
87 foreign export ccall getStaticFieldAddr :: CUInt -> IO CUInt
88 getStaticFieldAddr :: CUInt -> IO CUInt
89 getStaticFieldAddr from = do
90   trapmap <- get_trapmap >>= ptr2trapmap
91   let w32_from = fromIntegral from
92   let sfi = trapmap M.! w32_from
93   case sfi of
94     (SFI (StaticFieldInfo cls field)) -> getStaticFieldOffset cls field
95     _ -> error "getFieldAddr: no trapInfo. abort"
96
97 -- interface + method + signature plz!
98 getInterfaceMethodOffset :: B.ByteString -> B.ByteString -> B.ByteString -> IO Word32
99 getInterfaceMethodOffset ifname meth sig = do
100   loadInterface ifname
101   ifmmap <- get_interfacemethodmap >>= ptr2interfacemethodmap
102   let k = ifname `B.append` meth `B.append` sig
103   case M.lookup k ifmmap of
104     Just w32 -> return $ w32 + 4
105     Nothing -> error "getInterfaceMethodOffset: no offset set"
106
107
108 loadClass :: B.ByteString -> IO ClassInfo
109 loadClass path = do
110   let rpath = toString $ path `B.append` ".class"
111   cfile <- parseClassFile rpath
112 #ifdef DBG_CLASS
113   dumpClass cfile
114 #endif
115   -- load all interfaces, which are implemented by this class
116   sequence_ [ loadInterface i | i <- interfaces cfile ]
117   superclass <- if path /= "java/lang/Object"
118       then do
119         sc <- loadClass $ superClass cfile
120         return $ Just sc
121       else return Nothing
122
123   (staticmap, fieldmap) <- calculateFields cfile superclass
124   (methodmap, mbase) <- calculateMethodMap cfile superclass
125   immap <- get_interfacemethodmap >>= ptr2interfacemethodmap
126
127   -- allocate interface offset table for this class
128   -- TODO(bernhard): we have some duplicates in immap (i.e. some
129   --                 entries have the same offset), so we could
130   --                 save some memory here.
131   iftable <- mallocClassData ((4*) $ M.size immap)
132   let w32_iftable = fromIntegral $ ptrToIntPtr iftable :: Word32
133   -- store interface-table at offset 0 in method-table
134   pokeElemOff (intPtrToPtr $ fromIntegral mbase) 0 w32_iftable
135   printfCp "staticmap: %s @ %s\n" (show staticmap) (toString path)
136   printfCp "fieldmap:  %s @ %s\n" (show fieldmap) (toString path)
137   printfCp "methodmap: %s @ %s\n" (show methodmap) (toString path)
138   printfCp "mbase: 0x%08x\n" mbase
139   printfCp "interfacemethod: %s @ %s\n" (show immap) (toString path)
140   printfCp "iftable: 0x%08x\n" w32_iftable
141   virtual_map <- get_virtualmap >>= ptr2virtualmap
142   let virtual_map' = M.insert mbase path virtual_map
143   virtualmap2ptr virtual_map' >>= set_virtualmap
144
145   class_map <- get_classmap >>= ptr2classmap
146   let new_ci = ClassInfo path cfile staticmap fieldmap methodmap mbase False
147   let class_map' = M.insert path new_ci class_map
148   classmap2ptr class_map' >>= set_classmap
149   return new_ci
150
151
152 loadInterface :: B.ByteString -> IO ()
153 loadInterface path = do
154   imap <- get_interfacesmap >>= ptr2interfacesmap
155   -- interface already loaded?
156   case M.lookup path imap of
157     Just _ -> return ()
158     Nothing -> do
159       printfCp "interface: loading \"%s\"\n" $ toString path
160       let ifpath = toString $ path `B.append` ".class"
161       cfile <- parseClassFile ifpath
162       -- load "superinterfaces" first
163       sequence_ [ loadInterface i | i <- interfaces cfile ]
164       immap <- get_interfacemethodmap >>= ptr2interfacemethodmap
165
166       -- load map again, because there could be new entries now
167       -- due to loading superinterfaces
168       imap' <- get_interfacesmap >>= ptr2interfacesmap
169       let max_off = fromIntegral $ M.size immap * 4
170       -- create index of methods by this interface
171       let mm = zipbase max_off (classMethods cfile)
172
173       -- create for each method from *every* superinterface a entry to,
174       -- but just put in the same offset as it is already in the map
175       let (ifnames, methodnames) = unzip $ concat
176             [ zip (repeat ifname) (classMethods $ imap' M.! ifname)
177             | ifname <- interfaces cfile ]
178       let sm = zipWith (\x y -> (entry y, immap M.! getname x y)) ifnames methodnames
179
180       -- merge all offset tables
181       let methodmap = M.fromList sm `M.union` M.fromList mm `M.union` immap
182       interfacemethodmap2ptr methodmap >>= set_interfacemethodmap
183
184       interfacesmap2ptr (M.insert path cfile imap') >>= set_interfacesmap
185   where
186   zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..]
187   entry = getname path
188   getname p y = p `B.append` methodName y `B.append` encode (methodSignature y)
189
190
191 calculateFields :: Class Resolved -> Maybe ClassInfo -> IO (FieldMap, FieldMap)
192 calculateFields cf superclass = do
193     -- TODO(bernhard): correct sizes. int only atm
194
195     let (sfields, ifields) = span (S.member ACC_STATIC . fieldAccessFlags) (classFields cf)
196
197     staticbase <- mallocClassData $ fromIntegral (length sfields) * 4
198     let i_sb = fromIntegral $ ptrToIntPtr staticbase
199     let sm = zipbase i_sb sfields
200     let sc_sm = getsupermap superclass ciStaticMap
201     -- new fields "overwrite" old ones, if they have the same name
202     let staticmap = M.fromList sm `M.union` sc_sm
203
204     let sc_im = getsupermap superclass ciFieldMap
205     -- "+ 4" for the method table pointer
206     let max_off = (4+) $ fromIntegral $ M.size sc_im * 4
207     let im = zipbase max_off ifields
208     -- new fields "overwrite" old ones, if they have the same name
209     let fieldmap = M.fromList im `M.union` sc_im
210
211     return (staticmap, fieldmap)
212   where
213   zipbase base = zipWith (\x y -> (fieldName y, x + base)) [0,4..]
214
215 -- helper
216 getsupermap :: Maybe ClassInfo -> (ClassInfo -> FieldMap) -> FieldMap
217 getsupermap superclass getter = case superclass of Just x -> getter x; Nothing -> M.empty
218
219
220 calculateMethodMap :: Class Resolved -> Maybe ClassInfo -> IO (FieldMap, Word32)
221 calculateMethodMap cf superclass = do
222     let methods = filter
223                   (\x -> (not . S.member ACC_STATIC . methodAccessFlags) x &&
224                          ((/=) "<init>" . methodName) x)
225                   (classMethods cf)
226     let sc_mm = getsupermap superclass ciMethodMap
227     let max_off = fromIntegral $ M.size sc_mm * 4
228     let mm = zipbase max_off methods
229     let methodmap = M.fromList mm `M.union` sc_mm
230
231     -- (+1): one slot for the interface-table-ptr
232     methodbase <- mallocClassData (((+1) $ fromIntegral $ M.size methodmap) * 4)
233     return (methodmap, fromIntegral $ ptrToIntPtr methodbase)
234   where zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..]
235           where entry y = methodName y `B.append` encode (methodSignature y)
236
237
238 loadAndInitClass :: B.ByteString -> IO ClassInfo
239 loadAndInitClass path = do
240   class_map <- get_classmap >>= ptr2classmap
241   ci <- case M.lookup path class_map of
242     Nothing -> loadClass path
243     Just x -> return x
244
245   -- first try to execute class initializer of superclass
246   when (path /= "java/lang/Object") (void $ loadAndInitClass $ superClass $ ciFile ci)
247
248   -- execute class initializer
249   case lookupMethod "<clinit>" (ciFile ci) of
250     Just m -> do
251       hmap <- parseMethod (ciFile ci) "<clinit>"
252       case hmap of
253         Just hmap' -> do
254           let mi = MethodInfo "<clinit>" path (methodSignature m)
255           entry <- compileBB hmap' mi
256           addMethodRef entry mi [path]
257           printfCp "executing static initializer from %s now\n" (toString path)
258           executeFuncPtr entry
259           printfCp "static initializer from %s done\n" (toString path)
260         Nothing -> error "loadClass: static initializer not found (WTF?). abort"
261     Nothing -> return ()
262
263   class_map' <- get_classmap >>= ptr2classmap
264   let new_ci = ci { ciInitDone = True }
265   let class_map'' = M.insert path new_ci class_map'
266   classmap2ptr class_map'' >>= set_classmap
267   return new_ci