instanceOf: make decision at runtime
[mate.git] / Mate / Types.hs
index 5c5428ca8be81683e82dbc0a392bcce8b9e0db0f..7de8493a8523dddf9c8b6084e42e238a26d0fe22 100644 (file)
@@ -1,14 +1,37 @@
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE CPP #-}
-module Mate.Types where
+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 Data.IORef
 import System.IO.Unsafe
 
+import Harpy
+import Foreign.C.Types
+
 import JVM.ClassFile
 import JVM.Assembler
 
@@ -43,12 +66,16 @@ data RawMethod = RawMethod {
 -- MethodInfo = relevant information about callee
 type TrapMap = M.Map NativeWord TrapCause
 
+type TrapPatcher = CPtrdiff -> CodeGen () () CPtrdiff
+type TrapPatcherEax = CPtrdiff -> CPtrdiff -> CodeGen () () CPtrdiff
+
 data TrapCause
-  = StaticMethod MethodInfo -- for static calls
+  = StaticMethod TrapPatcher -- for static calls
   | VirtualCall Bool MethodInfo (IO NativeWord) -- for invoke{interface,virtual}
-  | InstanceOf B.ByteString -- class name
-  | NewObject B.ByteString -- class name
+  | InstanceOf TrapPatcherEax
+  | NewObject TrapPatcher
   | StaticField StaticFieldInfo
+  | ObjectField TrapPatcher
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
@@ -112,7 +139,6 @@ 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,
@@ -130,32 +156,47 @@ 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 };
+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
 
-#define GETMAP(name) get##name :: IO name ; \
-  get##name = do ctx <- readIORef mateCtx; \
-  return $ ctx##name ctx;
+setVirtualMap :: VirtualMap -> IO ()
+setVirtualMap m = setMap (\x -> x {ctxVirtualMap = m})
 
-SETMAP(MethodMap);
-GETMAP(MethodMap)
+getVirtualMap :: IO VirtualMap
+getVirtualMap = ctxVirtualMap <$> readIORef mateCtx
 
-SETMAP(TrapMap)
-GETMAP(TrapMap)
+setStringMap :: StringMap -> IO ()
+setStringMap m = setMap (\x -> x {ctxStringMap = m})
 
-SETMAP(ClassMap)
-GETMAP(ClassMap)
+getStringMap :: IO StringMap
+getStringMap = ctxStringMap <$> readIORef mateCtx
 
-SETMAP(VirtualMap)
-GETMAP(VirtualMap)
+setInterfaceMap :: InterfaceMap -> IO ()
+setInterfaceMap m = setMap (\x -> x {ctxInterfaceMap = m})
 
-SETMAP(StringMap)
-GETMAP(StringMap)
+getInterfaceMap :: IO InterfaceMap
+getInterfaceMap = ctxInterfaceMap <$> readIORef mateCtx
 
-SETMAP(InterfaceMap)
-GETMAP(InterfaceMap)
+setInterfaceMethodMap :: InterfaceMethodMap -> IO ()
+setInterfaceMethodMap m = setMap (\x -> x {ctxInterfaceMethodMap = m})
 
-SETMAP(InterfaceMethodMap)
-GETMAP(InterfaceMethodMap)
+getInterfaceMethodMap :: IO InterfaceMethodMap
+getInterfaceMethodMap = ctxInterfaceMethodMap <$> readIORef mateCtx