maxlocals: store it in new data type RawMethod, with MapBB & Co
[mate.git] / Mate / Types.hs
index 7d1583dbb0b1bb51f4e17ba67fe48128988e36c5..1978bb38fe3d8564b4ce87d2868015916239eaad 100644 (file)
@@ -1,16 +1,14 @@
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ForeignFunctionInterface #-}
+{-# LANGUAGE CPP #-}
 module Mate.Types where
 
-import Data.Char
 import Data.Word
 import Data.Int
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
-import Codec.Binary.UTF8.String hiding (encode,decode)
 
-import Foreign.Ptr
-import Foreign.StablePtr
+import Data.IORef
+import System.IO.Unsafe
 
 import JVM.ClassFile
 import JVM.Assembler
@@ -27,20 +25,25 @@ data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockI
 
 type MapBB = M.Map BlockID BasicBlock
 
+data RawMethod = RawMethod {
+  rawMapBB :: MapBB,
+  rawLocals :: Int,
+  rawStackSize :: Int }
 
 
 -- Word32 = point of method call in generated code
 -- MethodInfo = relevant information about callee
-type TrapMap = M.Map Word32 TrapInfo
+type TrapMap = M.Map Word32 TrapCause
 
-data TrapInfo =
-  MI MethodInfo | -- for static calls
-  VI MethodInfo | -- for virtual calls
-  SFI StaticFieldInfo
+data TrapCause =
+  StaticMethod MethodInfo | -- for static calls
+  VirtualMethod Bool MethodInfo | -- for virtual calls
+  InterfaceMethod Bool MethodInfo | -- for interface calls
+  StaticField StaticFieldInfo deriving Show
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
-  sfiFieldName :: B.ByteString }
+  sfiFieldName :: B.ByteString } deriving Show
 
 
 
@@ -54,18 +57,9 @@ data MethodInfo = MethodInfo {
   methSignature :: MethodSignature
   } deriving (Eq, Ord)
 
--- TODO(bernhard): not really efficient. also, outsource that to hs-java
---                 deriving should be enough?
-instance Ord MethodSignature where
-  compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
-    | cmp_args /= EQ = cmp_args
-    | otherwise = (show ret_a) `compare` (show ret_b)
-    where
-    cmp_args = (show args_a) `compare` (show args_b)
-
 instance Show MethodInfo where
   show (MethodInfo method c sig) =
-    (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig)
+    toString c ++ "." ++ toString method ++ "." ++ show sig
 
 
 
@@ -74,7 +68,7 @@ type ClassMap = M.Map B.ByteString ClassInfo
 
 data ClassInfo = ClassInfo {
   ciName :: B.ByteString,
-  ciFile :: Class Resolved,
+  ciFile :: Class Direct,
   ciStaticMap  :: FieldMap,
   ciFieldMap :: FieldMap,
   ciMethodMap :: FieldMap,
@@ -88,7 +82,7 @@ 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 StringsMap = M.Map B.ByteString Word32
+type StringMap = M.Map B.ByteString Word32
 
 
 -- map "methodtable addr" to "classname"
@@ -97,81 +91,62 @@ type StringsMap = M.Map B.ByteString Word32
 type VirtualMap = M.Map Word32 B.ByteString
 
 
-toString :: B.ByteString -> String
-toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
-
-
--- those functions are for the "global map hax"
--- TODO(bernhard): other solution please
-foreign import ccall "get_trapmap"
-  get_trapmap :: IO (Ptr ())
-
-foreign import ccall "set_trapmap"
-  set_trapmap :: Ptr () -> IO ()
+-- store each parsed Interface upon first loading
+type InterfaceMap = M.Map B.ByteString (Class Direct)
 
-foreign import ccall "get_methodmap"
-  get_methodmap :: IO (Ptr ())
+-- store offset for each <Interface><Method><Signature> pair
+type InterfaceMethodMap = M.Map B.ByteString Word32
 
-foreign import ccall "set_methodmap"
-  set_methodmap :: Ptr () -> IO ()
 
-foreign import ccall "get_classmap"
-  get_classmap :: IO (Ptr ())
-
-foreign import ccall "set_classmap"
-  set_classmap :: Ptr () -> IO ()
-
-foreign import ccall "get_virtualmap"
-  get_virtualmap :: IO (Ptr ())
-
-foreign import ccall "set_virtualmap"
-  set_virtualmap :: Ptr () -> IO ()
+{-
+toString :: B.ByteString -> String
+toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
+-}
 
-foreign import ccall "get_stringsmap"
-  get_stringsmap :: IO (Ptr ())
+-- better solutions for a global map hack are welcome! (typeclasses, TH, ...?)
 
-foreign import ccall "set_stringsmap"
-  set_stringsmap :: Ptr () -> IO ()
+data MateCtx = MateCtx {
+  ctxMethodMap :: MethodMap,
+  ctxTrapMap :: TrapMap,
+  ctxClassMap :: ClassMap,
+  ctxVirtualMap :: VirtualMap,
+  ctxStringMap :: StringMap,
+  ctxInterfaceMap :: InterfaceMap,
+  ctxInterfaceMethodMap :: InterfaceMethodMap }
 
--- TODO(bernhard): make some typeclass magic 'n stuff
---                 or remove that sh**
-methodmap2ptr :: MethodMap -> IO (Ptr ())
-methodmap2ptr methodmap = do
-  ptr_methodmap <- newStablePtr methodmap
-  return $ castStablePtrToPtr ptr_methodmap
+emptyMateCtx :: MateCtx
+emptyMateCtx = MateCtx M.empty M.empty M.empty M.empty M.empty M.empty M.empty
 
-ptr2methodmap :: Ptr () -> IO MethodMap
-ptr2methodmap methodmap = deRefStablePtr $ ((castPtrToStablePtr methodmap) :: StablePtr MethodMap)
+mateCtx :: IORef MateCtx
+{-# NOINLINE mateCtx #-}
+mateCtx = unsafePerformIO $ newIORef emptyMateCtx
 
-trapmap2ptr :: TrapMap -> IO (Ptr ())
-trapmap2ptr trapmap = do
-  ptr_trapmap <- newStablePtr trapmap
-  return $ castStablePtrToPtr ptr_trapmap
+-- 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 };
 
-ptr2trapmap :: Ptr () -> IO TrapMap
-ptr2trapmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr trapmap)
+#define GETMAP(name) get##name :: IO name ; \
+  get##name = do ctx <- readIORef mateCtx; \
+  return $ ctx##name ctx;
 
-classmap2ptr :: ClassMap -> IO (Ptr ())
-classmap2ptr cmap = do
-  ptr_cmap <- newStablePtr cmap
-  return $ castStablePtrToPtr ptr_cmap
+SETMAP(MethodMap);
+GETMAP(MethodMap)
 
-ptr2classmap :: Ptr () -> IO ClassMap
-ptr2classmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
+SETMAP(TrapMap)
+GETMAP(TrapMap)
 
-virtualmap2ptr :: VirtualMap -> IO (Ptr ())
-virtualmap2ptr cmap = do
-  ptr_cmap <- newStablePtr cmap
-  return $ castStablePtrToPtr ptr_cmap
+SETMAP(ClassMap)
+GETMAP(ClassMap)
 
-ptr2virtualmap :: Ptr () -> IO VirtualMap
-ptr2virtualmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
+SETMAP(VirtualMap)
+GETMAP(VirtualMap)
 
+SETMAP(StringMap)
+GETMAP(StringMap)
 
-stringsmap2ptr :: StringsMap -> IO (Ptr ())
-stringsmap2ptr cmap = do
-  ptr_cmap <- newStablePtr cmap
-  return $ castStablePtrToPtr ptr_cmap
+SETMAP(InterfaceMap)
+GETMAP(InterfaceMap)
 
-ptr2stringsmap :: Ptr () -> IO StringsMap
-ptr2stringsmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
+SETMAP(InterfaceMethodMap)
+GETMAP(InterfaceMethodMap)