invokevirtual: implement lazy class loading right
[mate.git] / Mate / Types.hs
index 5405a43a4f708df4a3be729fbf12983768c29711..5e5bf221e0ba26420943967d2b77e2cdcedb7ab6 100644 (file)
@@ -1,7 +1,7 @@
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE CPP #-}
 module Mate.Types where
 
-import Data.Word
 import Data.Int
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
@@ -12,6 +12,8 @@ import System.IO.Unsafe
 import JVM.ClassFile
 import JVM.Assembler
 
+import Mate.NativeSizes
+
 
 type BlockID = Int
 -- Represents a CFG node
@@ -24,17 +26,24 @@ data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockI
 
 type MapBB = M.Map BlockID BasicBlock
 
+data RawMethod = RawMethod {
+  rawMapBB :: MapBB,
+  rawLocals :: Int,
+  rawStackSize :: Int,
+  rawArgCount :: NativeWord,
+  rawCodeLength :: NativeWord }
 
 
--- Word32 = point of method call in generated code
+-- NativeWord = point of method call in generated code
 -- MethodInfo = relevant information about callee
-type TrapMap = M.Map Word32 TrapCause
+type TrapMap = M.Map NativeWord TrapCause
 
 data TrapCause =
   StaticMethod MethodInfo | -- for static calls
-  VirtualMethod Bool MethodInfo | -- for virtual calls
-  InterfaceMethod Bool MethodInfo | -- for interface calls
-  StaticField StaticFieldInfo deriving Show
+  VirtualCall Bool MethodInfo (IO NativeWord) | -- for invoke{interface,virtual}
+  InstanceOf B.ByteString | -- class name
+  NewObject B.ByteString | -- class name
+  StaticField StaticFieldInfo
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
@@ -43,8 +52,8 @@ data StaticFieldInfo = StaticFieldInfo {
 
 
 -- B.ByteString = name of method
--- Word32 = entrypoint of method
-type MethodMap = M.Map MethodInfo Word32
+-- NativeWord = entrypoint of method
+type MethodMap = M.Map MethodInfo NativeWord
 
 data MethodInfo = MethodInfo {
   methName :: B.ByteString,
@@ -67,7 +76,7 @@ data ClassInfo = ClassInfo {
   ciStaticMap  :: FieldMap,
   ciFieldMap :: FieldMap,
   ciMethodMap :: FieldMap,
-  ciMethodBase :: Word32,
+  ciMethodBase :: NativeWord,
   ciInitDone :: Bool }
 
 
@@ -77,20 +86,20 @@ type FieldMap = M.Map B.ByteString Int32
 
 -- java strings are allocated only once, therefore we
 -- use a hashmap to store the address for a String
-type StringMap = M.Map B.ByteString Word32
+type StringMap = M.Map B.ByteString NativeWord
 
 
 -- map "methodtable addr" to "classname"
 -- we need that to identify the actual type
 -- on the invokevirtual insn
-type VirtualMap = M.Map Word32 B.ByteString
+type VirtualMap = M.Map NativeWord B.ByteString
 
 
 -- store each parsed Interface upon first loading
 type InterfaceMap = M.Map B.ByteString (Class Direct)
 
 -- store offset for each <Interface><Method><Signature> pair
-type InterfaceMethodMap = M.Map B.ByteString Word32
+type InterfaceMethodMap = M.Map B.ByteString NativeWord
 
 
 {-
@@ -98,6 +107,7 @@ toString :: B.ByteString -> String
 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
 -}
 
+-- better solutions for a global map hack are welcome! (typeclasses, TH, ...?)
 
 data MateCtx = MateCtx {
   ctxMethodMap :: MethodMap,
@@ -115,79 +125,32 @@ mateCtx :: IORef MateCtx
 {-# NOINLINE mateCtx #-}
 mateCtx = unsafePerformIO $ newIORef emptyMateCtx
 
+-- TODO(bernhard): if we ever have thread support, don't forget MVars
+#define SETMAP(name) set##name :: name -> IO (); \
+  set##name m = do ctx <- readIORef mateCtx; \
+  writeIORef mateCtx $ ctx { ctx##name = m };
 
-setMethodMap :: MethodMap -> IO ()
-setMethodMap m = do
-  ctx <- readIORef mateCtx
-  writeIORef mateCtx $ ctx { ctxMethodMap = m }
-
-getMethodMap :: IO MethodMap
-getMethodMap = do
-  ctx <- readIORef mateCtx
-  return $ ctxMethodMap ctx
-
-
-setTrapMap :: TrapMap -> IO ()
-setTrapMap m = do
-  ctx <- readIORef mateCtx
-  writeIORef mateCtx $ ctx { ctxTrapMap = m }
-
-getTrapMap :: IO TrapMap
-getTrapMap = do
-  ctx <- readIORef mateCtx
-  return $ ctxTrapMap ctx
-
-
-setClassMap :: ClassMap -> IO ()
-setClassMap m = do
-  ctx <- readIORef mateCtx
-  writeIORef mateCtx $ ctx { ctxClassMap = m }
-
-getClassMap :: IO ClassMap
-getClassMap = do
-  ctx <- readIORef mateCtx
-  return $ ctxClassMap ctx
-
-
-setVirtualMap :: VirtualMap -> IO ()
-setVirtualMap m = do
-  ctx <- readIORef mateCtx
-  writeIORef mateCtx $ ctx { ctxVirtualMap = m }
-
-getVirtualMap :: IO VirtualMap
-getVirtualMap = do
-  ctx <- readIORef mateCtx
-  return $ ctxVirtualMap ctx
-
-
-setStringMap :: StringMap -> IO ()
-setStringMap m = do
-  ctx <- readIORef mateCtx
-  writeIORef mateCtx $ ctx { ctxStringMap = m }
+#define GETMAP(name) get##name :: IO name ; \
+  get##name = do ctx <- readIORef mateCtx; \
+  return $ ctx##name ctx;
 
-getStringMap :: IO StringMap
-getStringMap = do
-  ctx <- readIORef mateCtx
-  return $ ctxStringMap ctx
+SETMAP(MethodMap);
+GETMAP(MethodMap)
 
+SETMAP(TrapMap)
+GETMAP(TrapMap)
 
-setInterfaceMap :: InterfaceMap -> IO ()
-setInterfaceMap m = do
-  ctx <- readIORef mateCtx
-  writeIORef mateCtx $ ctx { ctxInterfaceMap = m }
+SETMAP(ClassMap)
+GETMAP(ClassMap)
 
-getInterfaceMap :: IO InterfaceMap
-getInterfaceMap = do
-  ctx <- readIORef mateCtx
-  return $ ctxInterfaceMap ctx
+SETMAP(VirtualMap)
+GETMAP(VirtualMap)
 
+SETMAP(StringMap)
+GETMAP(StringMap)
 
-setInterfaceMethodMap :: InterfaceMethodMap -> IO ()
-setInterfaceMethodMap m = do
-  ctx <- readIORef mateCtx
-  writeIORef mateCtx $ ctx { ctxInterfaceMethodMap = m }
+SETMAP(InterfaceMap)
+GETMAP(InterfaceMap)
 
-getInterfaceMethodMap :: IO InterfaceMethodMap
-getInterfaceMethodMap = do
-  ctx <- readIORef mateCtx
-  return $ ctxInterfaceMethodMap ctx
+SETMAP(InterfaceMethodMap)
+GETMAP(InterfaceMethodMap)