types: remove dirty Ord instance of MethodSignature
[mate.git] / Mate / Types.hs
index 2cdad11970d731afad72661936c44eae36f3171c..5405a43a4f708df4a3be729fbf12983768c29711 100644 (file)
@@ -1,16 +1,13 @@
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ForeignFunctionInterface #-}
 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
@@ -31,13 +28,13 @@ type MapBB = M.Map BlockID BasicBlock
 
 -- 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
+  StaticField StaticFieldInfo deriving Show
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
@@ -55,14 +52,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 +63,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,24 +87,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 <Interface><Method><Signature> 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 ())
-
 data MateCtx = MateCtx {
   ctxMethodMap :: MethodMap,
   ctxTrapMap :: TrapMap,
@@ -128,87 +111,83 @@ 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)
+mateCtx :: IORef MateCtx
+{-# NOINLINE mateCtx #-}
+mateCtx = unsafePerformIO $ newIORef emptyMateCtx
 
 
 setMethodMap :: MethodMap -> IO ()
 setMethodMap m = do
-  ctx <- get_mate_context >>= ptr2ctx
-  ctx2ptr ctx { ctxMethodMap = m } >>= set_mate_context
+  ctx <- readIORef mateCtx
+  writeIORef mateCtx $ ctx { ctxMethodMap = m }
 
 getMethodMap :: IO MethodMap
 getMethodMap = do
-  ctx <- get_mate_context >>= ptr2ctx
+  ctx <- readIORef mateCtx
   return $ ctxMethodMap ctx
 
 
 setTrapMap :: TrapMap -> IO ()
 setTrapMap m = do
-  ctx <- get_mate_context >>= ptr2ctx
-  ctx2ptr ctx { ctxTrapMap = m } >>= set_mate_context
+  ctx <- readIORef mateCtx
+  writeIORef mateCtx $ ctx { ctxTrapMap = m }
 
 getTrapMap :: IO TrapMap
 getTrapMap = do
-  ctx <- get_mate_context >>= ptr2ctx
+  ctx <- readIORef mateCtx
   return $ ctxTrapMap ctx
 
 
 setClassMap :: ClassMap -> IO ()
 setClassMap m = do
-  ctx <- get_mate_context >>= ptr2ctx
-  ctx2ptr ctx { ctxClassMap = m } >>= set_mate_context
+  ctx <- readIORef mateCtx
+  writeIORef mateCtx $ ctx { ctxClassMap = m }
 
 getClassMap :: IO ClassMap
 getClassMap = do
-  ctx <- get_mate_context >>= ptr2ctx
+  ctx <- readIORef mateCtx
   return $ ctxClassMap ctx
 
 
 setVirtualMap :: VirtualMap -> IO ()
 setVirtualMap m = do
-  ctx <- get_mate_context >>= ptr2ctx
-  ctx2ptr ctx { ctxVirtualMap = m } >>= set_mate_context
+  ctx <- readIORef mateCtx
+  writeIORef mateCtx $ ctx { ctxVirtualMap = m }
 
 getVirtualMap :: IO VirtualMap
 getVirtualMap = do
-  ctx <- get_mate_context >>= ptr2ctx
+  ctx <- readIORef mateCtx
   return $ ctxVirtualMap ctx
 
 
 setStringMap :: StringMap -> IO ()
 setStringMap m = do
-  ctx <- get_mate_context >>= ptr2ctx
-  ctx2ptr ctx { ctxStringMap = m } >>= set_mate_context
+  ctx <- readIORef mateCtx
+  writeIORef mateCtx $ ctx { ctxStringMap = m }
 
 getStringMap :: IO StringMap
 getStringMap = do
-  ctx <- get_mate_context >>= ptr2ctx
+  ctx <- readIORef mateCtx
   return $ ctxStringMap ctx
 
 
 setInterfaceMap :: InterfaceMap -> IO ()
 setInterfaceMap m = do
-  ctx <- get_mate_context >>= ptr2ctx
-  ctx2ptr ctx { ctxInterfaceMap = m } >>= set_mate_context
+  ctx <- readIORef mateCtx
+  writeIORef mateCtx $ ctx { ctxInterfaceMap = m }
 
 getInterfaceMap :: IO InterfaceMap
 getInterfaceMap = do
-  ctx <- get_mate_context >>= ptr2ctx
+  ctx <- readIORef mateCtx
   return $ ctxInterfaceMap ctx
 
 
 setInterfaceMethodMap :: InterfaceMethodMap -> IO ()
 setInterfaceMethodMap m = do
-  ctx <- get_mate_context >>= ptr2ctx
-  ctx2ptr ctx { ctxInterfaceMethodMap = m } >>= set_mate_context
+  ctx <- readIORef mateCtx
+  writeIORef mateCtx $ ctx { ctxInterfaceMethodMap = m }
 
 getInterfaceMethodMap :: IO InterfaceMethodMap
 getInterfaceMethodMap = do
-  ctx <- get_mate_context >>= ptr2ctx
+  ctx <- readIORef mateCtx
   return $ ctxInterfaceMethodMap ctx