codegen: handle exceptions of a method
[mate.git] / Mate / Types.hs
index 2f4ef6d245edd0501ee30a6c7f377bb1f6641bba..d3bc626300fbad81f692e75de8f9e78b8e470fd4 100644 (file)
@@ -1,13 +1,42 @@
 {-# LANGUAGE OverloadedStrings #-}
-module Mate.Types where
+module Mate.Types
+  ( BlockID
+  , BasicBlock(..)
+  , BBEnd(..)
+  , MapBB
+  , ExceptionMap
+  , JpcNpcMap
+  , RawMethod(..)
+  , TrapPatcher, TrapPatcherEax, TrapPatcherEaxEsp
+  , 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 Data.Word
 import qualified Data.Map as M
+import qualified Data.Bimap as BI
 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
 
@@ -17,7 +46,8 @@ import Mate.NativeSizes
 type BlockID = Int
 -- Represents a CFG node
 data BasicBlock = BasicBlock {
-  code :: [Instruction],
+  code :: [(Int, Instruction)],
+  bblength :: Int,
   successor :: BBEnd }
 
 -- describes (leaving) edges of a CFG node
@@ -29,9 +59,14 @@ data BBEnd
   deriving Show
 
 type MapBB = M.Map BlockID BasicBlock
+type ExceptionMap = M.Map (Word16, Word16) [(B.ByteString, Word16)]
+
+-- java byte code PC -> native PC
+type JpcNpcMap = BI.Bimap Int Word32
 
 data RawMethod = RawMethod {
   rawMapBB :: MapBB,
+  rawExcpMap :: ExceptionMap,
   rawLocals :: Int,
   rawStackSize :: Int,
   rawArgCount :: NativeWord,
@@ -42,12 +77,18 @@ data RawMethod = RawMethod {
 -- MethodInfo = relevant information about callee
 type TrapMap = M.Map NativeWord TrapCause
 
+type TrapPatcher = CPtrdiff -> CodeGen () () CPtrdiff
+type TrapPatcherEax = CPtrdiff -> TrapPatcher
+type TrapPatcherEaxEsp =  CPtrdiff -> TrapPatcherEax
+
 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
+  | ThrowException TrapPatcherEaxEsp
+  | NewObject TrapPatcher
   | StaticField StaticFieldInfo
+  | ObjectField TrapPatcher
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
@@ -57,7 +98,7 @@ data StaticFieldInfo = StaticFieldInfo {
 
 -- B.ByteString = name of method
 -- NativeWord = entrypoint of method
-type MethodMap = M.Map MethodInfo NativeWord
+type MethodMap = M.Map MethodInfo (NativeWord, JpcNpcMap)
 
 data MethodInfo = MethodInfo {
   methName :: B.ByteString,
@@ -128,79 +169,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