X-Git-Url: http://wien.tomnetworks.com/gitweb/?p=mate.git;a=blobdiff_plain;f=Mate%2FTypes.hs;h=7de8493a8523dddf9c8b6084e42e238a26d0fe22;hp=79b0396307e40c6abb4340d186025cee79cd0161;hb=918821897ac5548ea57e4d2630325e324de09d03;hpb=3160b1426c25340503b5ab216965e30509cd8416 diff --git a/Mate/Types.hs b/Mate/Types.hs index 79b0396..7de8493 100644 --- a/Mate/Types.hs +++ b/Mate/Types.hs @@ -1,20 +1,42 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ForeignFunctionInterface #-} -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.Char -import Data.Word 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 @@ -23,21 +45,37 @@ data BasicBlock = BasicBlock { 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 TrapMap = M.Map Word32 TrapInfo +type TrapMap = M.Map NativeWord TrapCause + +type TrapPatcher = CPtrdiff -> CodeGen () () CPtrdiff +type TrapPatcherEax = CPtrdiff -> CPtrdiff -> CodeGen () () CPtrdiff -data TrapInfo = - MI MethodInfo | -- for static calls - VI MethodInfo | -- for virtual calls - II MethodInfo | -- for interface calls - SFI StaticFieldInfo deriving Show +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, @@ -46,8 +84,8 @@ data StaticFieldInfo = StaticFieldInfo { -- B.ByteString = name of method --- Word32 = entrypoint of method -type MethodMap = M.Map MethodInfo Word32 +-- NativeWord = entrypoint of method +type MethodMap = M.Map MethodInfo NativeWord data MethodInfo = MethodInfo { methName :: B.ByteString, @@ -55,14 +93,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,11 +104,11 @@ 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, - ciMethodBase :: Word32, + ciMethodBase :: NativeWord, ciInitDone :: Bool } @@ -88,24 +118,26 @@ 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 Word32 +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 Word32 B.ByteString +type VirtualMap = M.Map NativeWord 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 +type InterfaceMethodMap = M.Map B.ByteString NativeWord +{- toString :: B.ByteString -> String toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr +-} data MateCtx = MateCtx { @@ -124,79 +156,47 @@ 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 = do - ctx <- readIORef mateCtx - writeIORef mateCtx $ ctx { ctxMethodMap = m } +setMethodMap m = setMap (\x -> x {ctxMethodMap = m}) getMethodMap :: IO MethodMap -getMethodMap = do - ctx <- readIORef mateCtx - return $ ctxMethodMap ctx - +getMethodMap = ctxMethodMap <$> readIORef mateCtx setTrapMap :: TrapMap -> IO () -setTrapMap m = do - ctx <- readIORef mateCtx - writeIORef mateCtx $ ctx { ctxTrapMap = m } +setTrapMap m = setMap (\x -> x {ctxTrapMap = m}) getTrapMap :: IO TrapMap -getTrapMap = do - ctx <- readIORef mateCtx - return $ ctxTrapMap ctx - +getTrapMap = ctxTrapMap <$> readIORef mateCtx setClassMap :: ClassMap -> IO () -setClassMap m = do - ctx <- readIORef mateCtx - writeIORef mateCtx $ ctx { ctxClassMap = m } +setClassMap m = setMap (\x -> x {ctxClassMap = m}) getClassMap :: IO ClassMap -getClassMap = do - ctx <- readIORef mateCtx - return $ ctxClassMap ctx - +getClassMap = ctxClassMap <$> readIORef mateCtx setVirtualMap :: VirtualMap -> IO () -setVirtualMap m = do - ctx <- readIORef mateCtx - writeIORef mateCtx $ ctx { ctxVirtualMap = m } +setVirtualMap m = setMap (\x -> x {ctxVirtualMap = m}) getVirtualMap :: IO VirtualMap -getVirtualMap = do - ctx <- readIORef mateCtx - return $ ctxVirtualMap ctx - +getVirtualMap = ctxVirtualMap <$> readIORef mateCtx setStringMap :: StringMap -> IO () -setStringMap m = do - ctx <- readIORef mateCtx - writeIORef mateCtx $ ctx { ctxStringMap = m } +setStringMap m = setMap (\x -> x {ctxStringMap = m}) getStringMap :: IO StringMap -getStringMap = do - ctx <- readIORef mateCtx - return $ ctxStringMap ctx - +getStringMap = ctxStringMap <$> readIORef mateCtx setInterfaceMap :: InterfaceMap -> IO () -setInterfaceMap m = do - ctx <- readIORef mateCtx - writeIORef mateCtx $ ctx { ctxInterfaceMap = m } +setInterfaceMap m = setMap (\x -> x {ctxInterfaceMap = m}) getInterfaceMap :: IO InterfaceMap -getInterfaceMap = do - ctx <- readIORef mateCtx - return $ ctxInterfaceMap ctx - +getInterfaceMap = ctxInterfaceMap <$> readIORef mateCtx setInterfaceMethodMap :: InterfaceMethodMap -> IO () -setInterfaceMethodMap m = do - ctx <- readIORef mateCtx - writeIORef mateCtx $ ctx { ctxInterfaceMethodMap = m } +setInterfaceMethodMap m = setMap (\x -> x {ctxInterfaceMethodMap = m}) getInterfaceMethodMap :: IO InterfaceMethodMap -getInterfaceMethodMap = do - ctx <- readIORef mateCtx - return $ ctxInterfaceMethodMap ctx +getInterfaceMethodMap = ctxInterfaceMethodMap <$> readIORef mateCtx