refactor: reduce global var in trap.c to one pointer
[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 <- getClassMap
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 <- getTrapMap
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 <- getInterfaceMethodMap
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 <- getInterfaceMethodMap
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 <- getVirtualMap
142   setVirtualMap $ M.insert mbase path virtual_map
143
144   class_map <- getClassMap
145   let new_ci = ClassInfo path cfile staticmap fieldmap methodmap mbase False
146   setClassMap $ M.insert path new_ci class_map
147   return new_ci
148
149
150 loadInterface :: B.ByteString -> IO ()
151 loadInterface path = do
152   imap <- getInterfaceMap
153   -- interface already loaded?
154   case M.lookup path imap of
155     Just _ -> return ()
156     Nothing -> do
157       printfCp "interface: loading \"%s\"\n" $ toString path
158       let ifpath = toString $ path `B.append` ".class"
159       cfile <- parseClassFile ifpath
160       -- load "superinterfaces" first
161       sequence_ [ loadInterface i | i <- interfaces cfile ]
162       immap <- getInterfaceMethodMap
163
164       -- load map again, because there could be new entries now
165       -- due to loading superinterfaces
166       imap' <- getInterfaceMap
167       let max_off = fromIntegral $ M.size immap * 4
168       -- create index of methods by this interface
169       let mm = zipbase max_off (classMethods cfile)
170
171       -- create for each method from *every* superinterface a entry to,
172       -- but just put in the same offset as it is already in the map
173       let (ifnames, methodnames) = unzip $ concat
174             [ zip (repeat ifname) (classMethods $ imap' M.! ifname)
175             | ifname <- interfaces cfile ]
176       let sm = zipWith (\x y -> (entry y, immap M.! getname x y)) ifnames methodnames
177
178       -- merge all offset tables
179       setInterfaceMethodMap $ M.fromList sm `M.union` M.fromList mm `M.union` immap
180       setInterfaceMap $ M.insert path cfile imap'
181   where
182   zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..]
183   entry = getname path
184   getname p y = p `B.append` methodName y `B.append` encode (methodSignature y)
185
186
187 calculateFields :: Class Resolved -> Maybe ClassInfo -> IO (FieldMap, FieldMap)
188 calculateFields cf superclass = do
189     -- TODO(bernhard): correct sizes. int only atm
190
191     let (sfields, ifields) = span (S.member ACC_STATIC . fieldAccessFlags) (classFields cf)
192
193     staticbase <- mallocClassData $ fromIntegral (length sfields) * 4
194     let i_sb = fromIntegral $ ptrToIntPtr staticbase
195     let sm = zipbase i_sb sfields
196     let sc_sm = getsupermap superclass ciStaticMap
197     -- new fields "overwrite" old ones, if they have the same name
198     let staticmap = M.fromList sm `M.union` sc_sm
199
200     let sc_im = getsupermap superclass ciFieldMap
201     -- "+ 4" for the method table pointer
202     let max_off = (4+) $ fromIntegral $ M.size sc_im * 4
203     let im = zipbase max_off ifields
204     -- new fields "overwrite" old ones, if they have the same name
205     let fieldmap = M.fromList im `M.union` sc_im
206
207     return (staticmap, fieldmap)
208   where
209   zipbase base = zipWith (\x y -> (fieldName y, x + base)) [0,4..]
210
211 -- helper
212 getsupermap :: Maybe ClassInfo -> (ClassInfo -> FieldMap) -> FieldMap
213 getsupermap superclass getter = case superclass of Just x -> getter x; Nothing -> M.empty
214
215
216 calculateMethodMap :: Class Resolved -> Maybe ClassInfo -> IO (FieldMap, Word32)
217 calculateMethodMap cf superclass = do
218     let methods = filter
219                   (\x -> (not . S.member ACC_STATIC . methodAccessFlags) x &&
220                          ((/=) "<init>" . methodName) x)
221                   (classMethods cf)
222     let sc_mm = getsupermap superclass ciMethodMap
223     let max_off = fromIntegral $ M.size sc_mm * 4
224     let mm = zipbase max_off methods
225     let methodmap = M.fromList mm `M.union` sc_mm
226
227     -- (+1): one slot for the interface-table-ptr
228     methodbase <- mallocClassData (((+1) $ fromIntegral $ M.size methodmap) * 4)
229     return (methodmap, fromIntegral $ ptrToIntPtr methodbase)
230   where zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..]
231           where entry y = methodName y `B.append` encode (methodSignature y)
232
233
234 loadAndInitClass :: B.ByteString -> IO ClassInfo
235 loadAndInitClass path = do
236   class_map <- getClassMap
237   ci <- case M.lookup path class_map of
238     Nothing -> loadClass path
239     Just x -> return x
240
241   -- first try to execute class initializer of superclass
242   when (path /= "java/lang/Object") (void $ loadAndInitClass $ superClass $ ciFile ci)
243
244   -- execute class initializer
245   case lookupMethod "<clinit>" (ciFile ci) of
246     Just m -> do
247       hmap <- parseMethod (ciFile ci) "<clinit>"
248       case hmap of
249         Just hmap' -> do
250           let mi = MethodInfo "<clinit>" path (methodSignature m)
251           entry <- compileBB hmap' mi
252           addMethodRef entry mi [path]
253           printfCp "executing static initializer from %s now\n" (toString path)
254           executeFuncPtr entry
255           printfCp "static initializer from %s done\n" (toString path)
256         Nothing -> error "loadClass: static initializer not found (WTF?). abort"
257     Nothing -> return ()
258
259   class_map' <- getClassMap
260   let new_ci = ci { ciInitDone = True }
261   setClassMap $ M.insert path new_ci class_map'
262   return new_ci