refactor: store amount of arguments of a method in RawMethod
[mate.git] / Mate / Utilities.hs
index fd4fc76307fea2bb66ba7dfc90843482c77c6beb..da07ecf18eb95d860ce266f8ce3a927445d3ece1 100644 (file)
@@ -4,8 +4,10 @@ module Mate.Utilities where
 
 import Data.Word
 import qualified Data.Map as M
+import qualified Data.Set as S
 import qualified Data.ByteString.Lazy as B
 import Data.List
+import Data.Maybe
 
 import JVM.ClassFile
 
@@ -32,14 +34,16 @@ buildClassID :: Class Direct -> Word16 -> B.ByteString
 buildClassID cls idx = cl
   where (CClass cl) = constsPool cls M.! idx
 
-methodGetArgsCount :: Class Direct -> Word16 -> Word32
-methodGetArgsCount cls idx = fromIntegral $ length args
-  where
-    nt = case constsPool cls M.! idx of
-      (CMethod _ nt') -> nt'
-      (CIfaceMethod _ nt') -> nt'
-      _ -> error "methodGetArgsCount: something wrong. abort."
-    (MethodSignature args _) = ntSignature nt
+
+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."
+
+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
@@ -58,6 +62,13 @@ methodHaveReturnValue cls idx = case ret of
       _ -> 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