debug: use #ifdef guards
[mate.git] / Mate / Utilities.hs
index 8733ca398506b5c8b14ac704f7139cb9f9e484e3..05220fce5447d5ded8ae15e72e91d51c57293b03 100644 (file)
@@ -1,12 +1,15 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE OverloadedStrings #-}
 module Mate.Utilities where
 
+import Data.Word
+import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
 
-import qualified JVM.Assembler as J
-import JVM.Assembler hiding (Instruction)
-import JVM.Common
 import JVM.ClassFile
 
+import Mate.Types
+
 
 -- TODO: actually this function already exists in hs-java-0.3!
 lookupMethod :: B.ByteString -> Class Resolved -> Maybe (Method Resolved)
@@ -16,3 +19,37 @@ lookupMethod name cls = look (classMethods cls)
     look (f:fs)
       | methodName f == name = Just f
       | otherwise  = look fs
+
+buildMethodID :: Class Resolved -> Word16 -> MethodInfo
+buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt)
+  where
+  (CMethod rc nt) = (constsPool cls) M.! idx
+
+buildStaticFieldID :: Class Resolved -> Word16 -> StaticFieldInfo
+buildStaticFieldID cls idx = StaticFieldInfo rc (ntName fnt)
+  where (CField rc fnt) = (constsPool cls) M.! idx
+
+buildFieldOffset :: Class Resolved -> Word16 -> (B.ByteString, B.ByteString)
+buildFieldOffset cls idx = (rc, ntName fnt)
+  where (CField rc fnt) = (constsPool cls) M.! idx
+
+buildClassID :: Class Resolved -> Word16 -> B.ByteString
+buildClassID cls idx = cl
+  where (CClass cl) = (constsPool cls) M.! idx
+
+methodGetArgsCount :: Class Resolved -> Word16 -> Word32
+methodGetArgsCount cls idx = fromIntegral $ length args
+  where
+  (CMethod _ nt) = (constsPool cls) M.! idx
+  (MethodSignature args _) = ntSignature nt
+
+-- TODO(bernhard): Extend it to more than just int, and provide typeinformation
+methodHaveReturnValue :: Class Resolved -> Word16 -> Bool
+methodHaveReturnValue cls idx = case ret of
+    ReturnsVoid -> False;
+    (Returns IntType) -> True;
+    (Returns (ObjectType _)) -> True;
+    _ -> error "methodHaveReturnValue: todo"
+  where
+  (CMethod _ nt) = (constsPool cls) M.! idx
+  (MethodSignature _ ret) = ntSignature nt