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