refactor: store amount of arguments of a method in RawMethod
[mate.git] / Mate / Utilities.hs
index ed92530ff70f1c36229dbb301474a95669c5ecf1..da07ecf18eb95d860ce266f8ce3a927445d3ece1 100644 (file)
@@ -1,34 +1,74 @@
+{-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 module Mate.Utilities where
 
-import Data.Char
 import Data.Word
-import Data.Binary
 import qualified Data.Map as M
+import qualified Data.Set as S
 import qualified Data.ByteString.Lazy as B
--- import qualified Data.ByteString.Lazy.Char8 as B8
-import Codec.Binary.UTF8.String hiding (encode,decode)
+import Data.List
+import Data.Maybe
 
 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)
-lookupMethod name cls = look (classMethods cls)
+
+buildMethodID :: Class Direct -> Word16 -> MethodInfo
+buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt)
   where
-    look [] = Nothing
-    look (f:fs)
-      | methodName f == name = Just f
-      | otherwise  = look fs
+    (rc, nt) = case constsPool cls M.! idx of
+      (CMethod rc' nt') -> (rc', nt')
+      (CIfaceMethod rc' nt') -> (rc', nt')
+      _ -> error "buildMethodID: something wrong. abort."
+
+buildStaticFieldID :: Class Direct -> Word16 -> StaticFieldInfo
+buildStaticFieldID cls idx = StaticFieldInfo rc (ntName fnt)
+  where (CField rc fnt) = constsPool cls M.! idx
+
+buildFieldOffset :: Class Direct -> Word16 -> (B.ByteString, B.ByteString)
+buildFieldOffset cls idx = (rc, ntName fnt)
+  where (CField rc fnt) = constsPool cls M.! idx
+
+buildClassID :: Class Direct -> Word16 -> B.ByteString
+buildClassID cls idx = cl
+  where (CClass cl) = constsPool cls M.! idx
+
 
-toString :: B.ByteString -> String
-toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
+methodNameTypeByIdx :: Class Direct -> Word16 -> NameType (Method Direct)
+methodNameTypeByIdx cls idx = case constsPool cls M.! idx of
+  (CMethod _ nt') -> nt'
+  (CIfaceMethod _ nt') -> nt'
+  _ -> error "methodGetArgsCount: something wrong. abort."
 
-buildMethodID :: Class Resolved -> Word16 -> B.ByteString
-buildMethodID cls idx = (rc `B.append` dot) `B.append` (ntName nt) `B.append` nt'
+methodGetArgsCount :: NameType (Method Direct) -> Word32
+methodGetArgsCount nt = genericLength args
+  where (MethodSignature args _) = ntSignature nt
+
+-- TODO(bernhard): Extend it to more than just int, and provide typeinformation
+methodHaveReturnValue :: Class Direct -> Word16 -> Bool
+methodHaveReturnValue cls idx = case ret of
+    ReturnsVoid -> False;
+    (Returns BoolType) -> True
+    (Returns CharByte) -> True
+    (Returns IntType) -> True;
+    (Returns (Array _ _)) -> True
+    (Returns (ObjectType _)) -> True;
+    _ -> error $ "methodHaveReturnValue: todo: " ++ show ret
   where
-  (CMethod rc nt) = (constsPool cls) M.! idx
-  nt' = encode $ ntSignature nt
-  dot :: B.ByteString
-  -- TODO(bernhard): WTF? why -XOverloadedStrings doesn't apply here?
-  dot = B.pack $ map (fromIntegral . ord) "."
+    nt = case constsPool cls M.! idx of
+      (CMethod _ nt') -> nt'
+      (CIfaceMethod _ nt') -> nt'
+      _ -> error "methodHaveReturnValue: something wrong. abort."
+    (MethodSignature _ ret) = ntSignature nt
+
+methodInfoToMethod :: MethodInfo -> Class Direct -> Method Direct
+methodInfoToMethod mi cls =
+  fromJust $ lookupMethodSig (methName mi) (methSignature mi) cls
+
+methodIsStatic :: Method Direct -> Bool
+methodIsStatic = S.member ACC_STATIC . methodAccessFlags
+
+lookupMethodSig :: B.ByteString -> MethodSignature -> Class Direct -> Maybe (Method Direct)
+lookupMethodSig name sig cls =
+  find (\x -> methodName x == name && methodSignature x == sig) $ classMethods cls