X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=Mate%2FTypes.hs;h=831744ab27e1c0d96e162cd16fe6de4707b86dc2;hb=094e3cea9aa9d638b071fb52a12f04f6ddd80dc1;hp=2cdad11970d731afad72661936c44eae36f3171c;hpb=55d3b7af8c3a1fdef0c5e470e649d180dc0a3911;p=mate.git diff --git a/Mate/Types.hs b/Mate/Types.hs index 2cdad11..831744a 100644 --- a/Mate/Types.hs +++ b/Mate/Types.hs @@ -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,17 +25,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 :: Word32 } -- 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 - II MethodInfo | -- for interface calls - SFI StaticFieldInfo deriving Show +data TrapCause = + StaticMethod MethodInfo | -- for static calls + VirtualMethod Bool MethodInfo | -- for virtual calls + InterfaceMethod Bool MethodInfo | -- for interface calls + InstanceOf B.ByteString | -- class name + NewObject B.ByteString | -- class name + StaticField StaticFieldInfo deriving Show data StaticFieldInfo = StaticFieldInfo { sfiClassName :: B.ByteString, @@ -55,14 +60,6 @@ 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 @@ -74,7 +71,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, @@ -98,23 +95,18 @@ type VirtualMap = M.Map Word32 B.ByteString -- store each parsed Interface upon first loading -type InterfaceMap = M.Map B.ByteString (Class Resolved) +type InterfaceMap = M.Map B.ByteString (Class Direct) -- store offset for each pair type InterfaceMethodMap = M.Map B.ByteString Word32 +{- 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 "set_mate_context" - set_mate_context :: Ptr () -> IO () - -foreign import ccall "get_mate_context" - get_mate_context :: IO (Ptr ()) +-- better solutions for a global map hack are welcome! (typeclasses, TH, ...?) data MateCtx = MateCtx { ctxMethodMap :: MethodMap, @@ -128,87 +120,36 @@ data MateCtx = MateCtx { emptyMateCtx :: MateCtx emptyMateCtx = MateCtx M.empty M.empty M.empty M.empty M.empty M.empty M.empty -ctx2ptr :: MateCtx -> IO (Ptr ()) -ctx2ptr ctx = do - ptr <- newStablePtr ctx - return $ castStablePtrToPtr ptr - -ptr2ctx :: Ptr () -> IO MateCtx -ptr2ctx ptr = deRefStablePtr (castPtrToStablePtr ptr :: StablePtr MateCtx) - - -setMethodMap :: MethodMap -> IO () -setMethodMap m = do - ctx <- get_mate_context >>= ptr2ctx - ctx2ptr ctx { ctxMethodMap = m } >>= set_mate_context - -getMethodMap :: IO MethodMap -getMethodMap = do - ctx <- get_mate_context >>= ptr2ctx - return $ ctxMethodMap ctx - - -setTrapMap :: TrapMap -> IO () -setTrapMap m = do - ctx <- get_mate_context >>= ptr2ctx - ctx2ptr ctx { ctxTrapMap = m } >>= set_mate_context - -getTrapMap :: IO TrapMap -getTrapMap = do - ctx <- get_mate_context >>= ptr2ctx - return $ ctxTrapMap ctx - - -setClassMap :: ClassMap -> IO () -setClassMap m = do - ctx <- get_mate_context >>= ptr2ctx - ctx2ptr ctx { ctxClassMap = m } >>= set_mate_context - -getClassMap :: IO ClassMap -getClassMap = do - ctx <- get_mate_context >>= ptr2ctx - return $ ctxClassMap ctx - - -setVirtualMap :: VirtualMap -> IO () -setVirtualMap m = do - ctx <- get_mate_context >>= ptr2ctx - ctx2ptr ctx { ctxVirtualMap = m } >>= set_mate_context - -getVirtualMap :: IO VirtualMap -getVirtualMap = do - ctx <- get_mate_context >>= ptr2ctx - return $ ctxVirtualMap ctx +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 }; -setStringMap :: StringMap -> IO () -setStringMap m = do - ctx <- get_mate_context >>= ptr2ctx - ctx2ptr ctx { ctxStringMap = m } >>= set_mate_context +#define GETMAP(name) get##name :: IO name ; \ + get##name = do ctx <- readIORef mateCtx; \ + return $ ctx##name ctx; -getStringMap :: IO StringMap -getStringMap = do - ctx <- get_mate_context >>= ptr2ctx - return $ ctxStringMap ctx +SETMAP(MethodMap); +GETMAP(MethodMap) +SETMAP(TrapMap) +GETMAP(TrapMap) -setInterfaceMap :: InterfaceMap -> IO () -setInterfaceMap m = do - ctx <- get_mate_context >>= ptr2ctx - ctx2ptr ctx { ctxInterfaceMap = m } >>= set_mate_context +SETMAP(ClassMap) +GETMAP(ClassMap) -getInterfaceMap :: IO InterfaceMap -getInterfaceMap = do - ctx <- get_mate_context >>= ptr2ctx - return $ ctxInterfaceMap ctx +SETMAP(VirtualMap) +GETMAP(VirtualMap) +SETMAP(StringMap) +GETMAP(StringMap) -setInterfaceMethodMap :: InterfaceMethodMap -> IO () -setInterfaceMethodMap m = do - ctx <- get_mate_context >>= ptr2ctx - ctx2ptr ctx { ctxInterfaceMethodMap = m } >>= set_mate_context +SETMAP(InterfaceMap) +GETMAP(InterfaceMap) -getInterfaceMethodMap :: IO InterfaceMethodMap -getInterfaceMethodMap = do - ctx <- get_mate_context >>= ptr2ctx - return $ ctxInterfaceMethodMap ctx +SETMAP(InterfaceMethodMap) +GETMAP(InterfaceMethodMap)