X-Git-Url: http://wien.tomnetworks.com/gitweb/?p=mate.git;a=blobdiff_plain;f=Mate%2FTypes.hs;h=7de8493a8523dddf9c8b6084e42e238a26d0fe22;hp=69180847de5bc8f16f6e8c894a42d24bf5c5afd9;hb=918821897ac5548ea57e4d2630325e324de09d03;hpb=ac25b64148468f9268f99e35c0e99a1cf59dd6d2 diff --git a/Mate/Types.hs b/Mate/Types.hs index 6918084..7de8493 100644 --- a/Mate/Types.hs +++ b/Mate/Types.hs @@ -1,132 +1,202 @@ {-# 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 Foreign.Ptr -import Foreign.StablePtr +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 TMap = 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 | SFI StaticFieldInfo +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 } + sfiFieldName :: B.ByteString } deriving Show --- 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 -data ClassInfo = ClassInfo { - clName :: B.ByteString, - clFile :: Class Resolved, - clField :: Ptr Int32, - clFieldMap :: FieldMap } +-- 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} - -instance Eq MethodInfo where - (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 - 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) (MethodInfo m_b c_b s_b) - | cmp_m /= EQ = cmp_m - | cmp_c /= EQ = cmp_c - | otherwise = s_a `compare` s_b - where - cmp_m = m_a `compare` m_b - cmp_c = c_a `compare` c_b + methClassName :: B.ByteString, + methSignature :: MethodSignature + } deriving (Eq, Ord) instance Show MethodInfo where show (MethodInfo method c sig) = - (toString c) ++ "." ++ (toString method) ++ "." ++ (show 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 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 --- global map hax -foreign import ccall "get_trapmap" - get_trapmap :: IO (Ptr ()) +setTrapMap :: TrapMap -> IO () +setTrapMap m = setMap (\x -> x {ctxTrapMap = m}) -foreign import ccall "set_trapmap" - set_trapmap :: Ptr () -> IO () +getTrapMap :: IO TrapMap +getTrapMap = ctxTrapMap <$> readIORef mateCtx -foreign import ccall "get_methodmap" - get_methodmap :: IO (Ptr ()) +setClassMap :: ClassMap -> IO () +setClassMap m = setMap (\x -> x {ctxClassMap = m}) -foreign import ccall "set_methodmap" - set_methodmap :: Ptr () -> IO () +getClassMap :: IO ClassMap +getClassMap = ctxClassMap <$> readIORef mateCtx -foreign import ccall "get_classmap" - get_classmap :: IO (Ptr ()) +setVirtualMap :: VirtualMap -> IO () +setVirtualMap m = setMap (\x -> x {ctxVirtualMap = m}) -foreign import ccall "set_classmap" - set_classmap :: Ptr () -> IO () +getVirtualMap :: IO VirtualMap +getVirtualMap = ctxVirtualMap <$> readIORef mateCtx --- TODO(bernhard): make some typeclass magic 'n stuff -mmap2ptr :: MMap -> IO (Ptr ()) -mmap2ptr mmap = do - ptr_mmap <- newStablePtr mmap - return $ castStablePtrToPtr ptr_mmap +setStringMap :: StringMap -> IO () +setStringMap m = setMap (\x -> x {ctxStringMap = m}) -ptr2mmap :: Ptr () -> IO MMap -ptr2mmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr MMap) +getStringMap :: IO StringMap +getStringMap = ctxStringMap <$> readIORef mateCtx -tmap2ptr :: TMap -> IO (Ptr ()) -tmap2ptr tmap = do - ptr_tmap <- newStablePtr tmap - return $ castStablePtrToPtr ptr_tmap +setInterfaceMap :: InterfaceMap -> IO () +setInterfaceMap m = setMap (\x -> x {ctxInterfaceMap = m}) -ptr2tmap :: Ptr () -> IO TMap -ptr2tmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr tmap) +getInterfaceMap :: IO InterfaceMap +getInterfaceMap = ctxInterfaceMap <$> readIORef mateCtx -classmap2ptr :: ClassMap -> IO (Ptr ()) -classmap2ptr cmap = do - ptr_cmap <- newStablePtr cmap - return $ castStablePtrToPtr ptr_cmap +setInterfaceMethodMap :: InterfaceMethodMap -> IO () +setInterfaceMethodMap m = setMap (\x -> x {ctxInterfaceMethodMap = m}) -ptr2classmap :: Ptr () -> IO ClassMap -ptr2classmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap) +getInterfaceMethodMap :: IO InterfaceMethodMap +getInterfaceMethodMap = ctxInterfaceMethodMap <$> readIORef mateCtx