Revert "globalmaphack: use old school CPP"
[mate.git] / Mate / Types.hs
index f49e0408e1a57cec351fb0952297523ce4b88995..2f4ef6d245edd0501ee30a6c7f377bb1f6641bba 100644 (file)
@@ -1,8 +1,6 @@
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ForeignFunctionInterface #-}
 module Mate.Types where
 
-import Data.Word
 import Data.Int
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
@@ -13,6 +11,8 @@ import System.IO.Unsafe
 import JVM.ClassFile
 import JVM.Assembler
 
+import Mate.NativeSizes
+
 
 type BlockID = Int
 -- Represents a CFG node
@@ -21,21 +21,33 @@ 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
 
-data TrapInfo =
-  MI MethodInfo | -- for static calls
-  VI Bool MethodInfo | -- for virtual calls
-  II Bool MethodInfo | -- for interface calls
-  SFI StaticFieldInfo deriving Show
+data TrapCause
+  = StaticMethod MethodInfo -- for static calls
+  | VirtualCall Bool MethodInfo (IO NativeWord) -- for invoke{interface,virtual}
+  | InstanceOf B.ByteString -- class name
+  | NewObject B.ByteString -- class name
+  | StaticField StaticFieldInfo
 
 data StaticFieldInfo = StaticFieldInfo {
   sfiClassName :: B.ByteString,
@@ -44,8 +56,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,
@@ -53,14 +65,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
@@ -76,7 +80,7 @@ data ClassInfo = ClassInfo {
   ciStaticMap  :: FieldMap,
   ciFieldMap :: FieldMap,
   ciMethodMap :: FieldMap,
-  ciMethodBase :: Word32,
+  ciMethodBase :: NativeWord,
   ciInitDone :: Bool }
 
 
@@ -86,20 +90,20 @@ 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 Direct)
 
 -- store offset for each <Interface><Method><Signature> pair
-type InterfaceMethodMap = M.Map B.ByteString Word32
+type InterfaceMethodMap = M.Map B.ByteString NativeWord
 
 
 {-