invokevirtual: get the actual class at run-time
[mate.git] / Mate / Types.hs
index 95ae4e4b9167e10dc76c8e82ebf62ff2e177a15b..8977143ca1e2b540860e780fe14d17dc86a0518c 100644 (file)
@@ -1,11 +1,17 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ForeignFunctionInterface #-}
 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 JVM.ClassFile
 import JVM.Assembler
 
@@ -24,23 +30,47 @@ type MapBB = M.Map BlockID BasicBlock
 
 -- Word32 = point of method call in generated code
 -- MethodInfo = relevant information about callee
-type CMap = M.Map Word32 MethodInfo
+type TMap = M.Map Word32 TrapInfo
+
+data TrapInfo =
+  MI MethodInfo |
+  VI MethodInfo | -- for virtual calls
+  SFI StaticFieldInfo
+
+data StaticFieldInfo = StaticFieldInfo {
+  sfiClassName :: B.ByteString,
+  sfiFieldName :: B.ByteString }
 
 -- B.ByteString = name of method
 -- Word32 = entrypoint of method
 type MMap = M.Map MethodInfo Word32
 
+type ClassMap = M.Map B.ByteString ClassInfo
 
+type FieldMap = M.Map B.ByteString Int32
+
+-- map "methodtable addr" to "classname"
+-- we need that to identify the actual type
+-- on the invokevirtual insn
+type VirtualMap = M.Map Word32 B.ByteString
+
+data ClassInfo = ClassInfo {
+  clName :: B.ByteString,
+  clFile :: Class Resolved,
+  clStaticMap  :: FieldMap,
+  clFieldMap :: FieldMap,
+  clMethodMap :: FieldMap,
+  clMethodBase :: Word32,
+  clInitDone :: Bool }
 
 data MethodInfo = MethodInfo {
   methName :: B.ByteString,
   cName :: B.ByteString,
-  mSignature :: MethodSignature,
-  cpIndex :: Word16 }
+  mSignature :: MethodSignature}
 
 instance Eq MethodInfo where
-  (MethodInfo m_a c_a s_a i_a) == (MethodInfo m_b c_b s_b i_b) =
-    (m_a == m_b) && (c_a == c_b) && (s_a == s_b) && (i_a == i_b)
+  (MethodInfo m_a c_a s_a) == (MethodInfo m_b c_b s_b) =
+    (m_a == m_b) && (c_a == c_b) && (s_a == s_b)
 
 -- TODO(bernhard): not really efficient. also, outsource that to hs-java
 instance Ord MethodSignature where
@@ -51,20 +81,77 @@ instance Ord MethodSignature where
     cmp_args = (show args_a) `compare` (show args_b)
 
 instance Ord MethodInfo where
-  compare (MethodInfo m_a c_a s_a i_a) (MethodInfo m_b c_b s_b i_b)
+  compare (MethodInfo m_a c_a s_a) (MethodInfo m_b c_b s_b)
     | cmp_m /= EQ = cmp_m
     | cmp_c /= EQ = cmp_c
-    | cmp_s /= EQ = cmp_s
-    | otherwise = i_a `compare` i_b
+    | otherwise = s_a `compare` s_b
     where
     cmp_m = m_a `compare` m_b
     cmp_c = c_a `compare` c_b
-    cmp_s = s_a `compare` s_b
 
 instance Show MethodInfo where
-  show (MethodInfo method c sig idx) =
-    (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig) ++ "@" ++ (show idx)
+  show (MethodInfo method c sig) =
+    (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig)
 
 
 toString :: B.ByteString -> String
 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
+
+
+-- global map hax
+foreign import ccall "get_trapmap"
+  get_trapmap :: IO (Ptr ())
+
+foreign import ccall "set_trapmap"
+  set_trapmap :: Ptr () -> IO ()
+
+foreign import ccall "get_methodmap"
+  get_methodmap :: IO (Ptr ())
+
+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 ()
+
+-- TODO(bernhard): make some typeclass magic 'n stuff
+mmap2ptr :: MMap -> IO (Ptr ())
+mmap2ptr mmap = do
+  ptr_mmap <- newStablePtr mmap
+  return $ castStablePtrToPtr ptr_mmap
+
+ptr2mmap :: Ptr () -> IO MMap
+ptr2mmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr MMap)
+
+tmap2ptr :: TMap -> IO (Ptr ())
+tmap2ptr tmap = do
+  ptr_tmap <- newStablePtr tmap
+  return $ castStablePtrToPtr ptr_tmap
+
+ptr2tmap :: Ptr () -> IO TMap
+ptr2tmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr tmap)
+
+classmap2ptr :: ClassMap -> IO (Ptr ())
+classmap2ptr cmap = do
+  ptr_cmap <- newStablePtr cmap
+  return $ castStablePtrToPtr ptr_cmap
+
+ptr2classmap :: Ptr () -> IO ClassMap
+ptr2classmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
+
+virtualmap2ptr :: VirtualMap -> IO (Ptr ())
+virtualmap2ptr cmap = do
+  ptr_cmap <- newStablePtr cmap
+  return $ castStablePtrToPtr ptr_cmap
+
+ptr2virtualmap :: Ptr () -> IO VirtualMap
+ptr2virtualmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)