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