instanceOf: make decision at runtime
[mate.git] / Mate / Types.hs
index 95ae4e4b9167e10dc76c8e82ebf62ff2e177a15b..7de8493a8523dddf9c8b6084e42e238a26d0fe22 100644 (file)
-module Mate.Types where
-
-import Data.Char
-import Data.Word
+{-# LANGUAGE OverloadedStrings #-}
+module Mate.Types
+  ( BlockID
+  , BasicBlock(..)
+  , BBEnd(..)
+  , MapBB
+  , RawMethod(..)
+  , TrapMap, MethodMap, ClassMap, FieldMap
+  , StringMap, VirtualMap, InterfaceMap
+  , InterfaceMethodMap
+  , TrapCause(..)
+  , StaticFieldInfo(..)
+  , MethodInfo(..)
+  , ClassInfo(..)
+  , setTrapMap, getTrapMap
+  , setMethodMap, getMethodMap
+  , setClassMap, getClassMap
+  , setStringMap, getStringMap
+  , setVirtualMap, getVirtualMap
+  , setInterfaceMap, getInterfaceMap
+  , setInterfaceMethodMap, getInterfaceMethodMap
+  ) where
+
+import Data.Int
+import Data.Functor
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
-import Codec.Binary.UTF8.String hiding (encode,decode)
+
+import Data.IORef
+import System.IO.Unsafe
+
+import Harpy
+import Foreign.C.Types
 
 import JVM.ClassFile
 import JVM.Assembler
 
+import Mate.NativeSizes
+
 
 type BlockID = Int
 -- Represents a CFG node
 data BasicBlock = BasicBlock {
-                     code    :: [Instruction],
-                     successor :: BBEnd }
+  code :: [Instruction],
+  successor :: BBEnd }
 
 -- describes (leaving) edges of a CFG node
-data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
+data BBEnd
+  = Return
+  | FallThrough BlockID
+  | OneTarget BlockID
+  | TwoTarget BlockID BlockID
+  deriving Show
 
 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 CMap = M.Map Word32 MethodInfo
+type TrapMap = M.Map NativeWord TrapCause
 
--- B.ByteString = name of method
--- Word32 = entrypoint of method
-type MMap = M.Map MethodInfo Word32
+type TrapPatcher = CPtrdiff -> CodeGen () () CPtrdiff
+type TrapPatcherEax = CPtrdiff -> CPtrdiff -> CodeGen () () CPtrdiff
 
+data TrapCause
+  = StaticMethod TrapPatcher -- for static calls
+  | VirtualCall Bool MethodInfo (IO NativeWord) -- for invoke{interface,virtual}
+  | InstanceOf TrapPatcherEax
+  | NewObject TrapPatcher
+  | StaticField StaticFieldInfo
+  | ObjectField TrapPatcher
 
+data StaticFieldInfo = StaticFieldInfo {
+  sfiClassName :: B.ByteString,
+  sfiFieldName :: B.ByteString } deriving Show
+
+
+
+-- B.ByteString = name of method
+-- NativeWord = entrypoint of method
+type MethodMap = M.Map MethodInfo NativeWord
 
 data MethodInfo = MethodInfo {
   methName :: B.ByteString,
-  cName :: B.ByteString,
-  mSignature :: MethodSignature,
-  cpIndex :: Word16 }
-
-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)
-
--- TODO(bernhard): not really efficient. also, outsource that to hs-java
-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 Ord MethodInfo where
-  compare (MethodInfo m_a c_a s_a i_a) (MethodInfo m_b c_b s_b i_b)
-    | cmp_m /= EQ = cmp_m
-    | cmp_c /= EQ = cmp_c
-    | cmp_s /= EQ = cmp_s
-    | otherwise = i_a `compare` i_b
-    where
-    cmp_m = m_a `compare` m_b
-    cmp_c = c_a `compare` c_b
-    cmp_s = s_a `compare` s_b
+  methClassName :: B.ByteString,
+  methSignature :: MethodSignature
+  } deriving (Eq, Ord)
 
 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
+
+
+
+-- store information of loaded classes
+type ClassMap = M.Map B.ByteString ClassInfo
+
+data ClassInfo = ClassInfo {
+  ciName :: B.ByteString,
+  ciFile :: Class Direct,
+  ciStaticMap  :: FieldMap,
+  ciFieldMap :: FieldMap,
+  ciMethodMap :: FieldMap,
+  ciMethodBase :: NativeWord,
+  ciInitDone :: Bool }
+
+
+-- store field offsets in a map
+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 NativeWord
+
+
+-- map "methodtable addr" to "classname"
+-- we need that to identify the actual type
+-- on the invokevirtual insn
+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 NativeWord
+
+
+{-
 toString :: B.ByteString -> String
 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
+-}
+
+
+data MateCtx = MateCtx {
+  ctxMethodMap :: MethodMap,
+  ctxTrapMap :: TrapMap,
+  ctxClassMap :: ClassMap,
+  ctxVirtualMap :: VirtualMap,
+  ctxStringMap :: StringMap,
+  ctxInterfaceMap :: InterfaceMap,
+  ctxInterfaceMethodMap :: InterfaceMethodMap }
+
+emptyMateCtx :: MateCtx
+emptyMateCtx = MateCtx M.empty M.empty M.empty M.empty M.empty M.empty M.empty
+
+mateCtx :: IORef MateCtx
+{-# NOINLINE mateCtx #-}
+mateCtx = unsafePerformIO $ newIORef emptyMateCtx
+
+setMap :: (MateCtx -> MateCtx) -> IO ()
+setMap recordupdate = recordupdate <$> readIORef mateCtx >>= writeIORef mateCtx
+
+setMethodMap :: MethodMap -> IO ()
+setMethodMap m = setMap (\x -> x {ctxMethodMap = m})
+
+getMethodMap :: IO MethodMap
+getMethodMap = ctxMethodMap <$> readIORef mateCtx
+
+setTrapMap :: TrapMap -> IO ()
+setTrapMap m = setMap (\x -> x {ctxTrapMap = m})
+
+getTrapMap :: IO TrapMap
+getTrapMap = ctxTrapMap <$> readIORef mateCtx
+
+setClassMap :: ClassMap -> IO ()
+setClassMap m = setMap (\x -> x {ctxClassMap = m})
+
+getClassMap :: IO ClassMap
+getClassMap = ctxClassMap <$> readIORef mateCtx
+
+setVirtualMap :: VirtualMap -> IO ()
+setVirtualMap m = setMap (\x -> x {ctxVirtualMap = m})
+
+getVirtualMap :: IO VirtualMap
+getVirtualMap = ctxVirtualMap <$> readIORef mateCtx
+
+setStringMap :: StringMap -> IO ()
+setStringMap m = setMap (\x -> x {ctxStringMap = m})
+
+getStringMap :: IO StringMap
+getStringMap = ctxStringMap <$> readIORef mateCtx
+
+setInterfaceMap :: InterfaceMap -> IO ()
+setInterfaceMap m = setMap (\x -> x {ctxInterfaceMap = m})
+
+getInterfaceMap :: IO InterfaceMap
+getInterfaceMap = ctxInterfaceMap <$> readIORef mateCtx
+
+setInterfaceMethodMap :: InterfaceMethodMap -> IO ()
+setInterfaceMethodMap m = setMap (\x -> x {ctxInterfaceMethodMap = m})
+
+getInterfaceMethodMap :: IO InterfaceMethodMap
+getInterfaceMethodMap = ctxInterfaceMethodMap <$> readIORef mateCtx