refactor: style, fun, hlint, ...
[mate.git] / Mate / Utilities.hs
index 50e7a56e109d21165bc55ecc5a228bb3beca9648..565d4b1809528f786a88f57179bdddbf4d443484 100644 (file)
@@ -5,59 +5,58 @@ module Mate.Utilities where
 import Data.Word
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
+import Data.List
 
 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)
-  where
-    look [] = Nothing
-    look (f:fs)
-      | methodName f == name = Just f
-      | otherwise  = look fs
-
-buildMethodID :: Class Resolved -> Word16 -> MethodInfo
+buildMethodID :: Class Direct -> Word16 -> MethodInfo
 buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt)
-  where (rc, nt) = case (constsPool cls) M.! idx of
+  where (rc, nt) = case constsPool cls M.! idx of
                     (CMethod rc' nt') -> (rc', nt')
                     (CIfaceMethod rc' nt') -> (rc', nt')
-                    _ -> error "buildMethodID: something wrong. abort."
+                    _ -> error "buildMethodID: something wrong. abort."
 
-buildStaticFieldID :: Class Resolved -> Word16 -> StaticFieldInfo
+buildStaticFieldID :: Class Direct -> Word16 -> StaticFieldInfo
 buildStaticFieldID cls idx = StaticFieldInfo rc (ntName fnt)
-  where (CField rc fnt) = (constsPool cls) M.! idx
+  where (CField rc fnt) = constsPool cls M.! idx
 
-buildFieldOffset :: Class Resolved -> Word16 -> (B.ByteString, B.ByteString)
+buildFieldOffset :: Class Direct -> Word16 -> (B.ByteString, B.ByteString)
 buildFieldOffset cls idx = (rc, ntName fnt)
-  where (CField rc fnt) = (constsPool cls) M.! idx
+  where (CField rc fnt) = constsPool cls M.! idx
 
-buildClassID :: Class Resolved -> Word16 -> B.ByteString
+buildClassID :: Class Direct -> Word16 -> B.ByteString
 buildClassID cls idx = cl
-  where (CClass cl) = (constsPool cls) M.! idx
+  where (CClass cl) = constsPool cls M.! idx
 
-methodGetArgsCount :: Class Resolved -> Word16 -> Word32
+methodGetArgsCount :: Class Direct -> Word16 -> Word32
 methodGetArgsCount cls idx = fromIntegral $ length args
   where
-  nt = case (constsPool cls) M.! idx of
+  nt = case constsPool cls M.! idx of
     (CMethod _ nt') -> nt'
     (CIfaceMethod _ nt') -> nt'
-    _ -> error "methodGetArgsCount: something wrong. abort."
+    _ -> error "methodGetArgsCount: something wrong. abort."
   (MethodSignature args _) = ntSignature nt
 
 -- TODO(bernhard): Extend it to more than just int, and provide typeinformation
-methodHaveReturnValue :: Class Resolved -> Word16 -> Bool
+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"
+    _ -> error $ "methodHaveReturnValue: todo: " ++ show ret
   where
-  nt = case (constsPool cls) M.! idx of
+  nt = case constsPool cls M.! idx of
     (CMethod _ nt') -> nt'
     (CIfaceMethod _ nt') -> nt'
-    _ -> error "methodHaveReturnValue: something wrong. abort."
+    _ -> error "methodHaveReturnValue: something wrong. abort."
   (MethodSignature _ ret) = ntSignature nt
+
+lookupMethodSig :: B.ByteString -> MethodSignature -> Class Direct -> Maybe (Method Direct)
+lookupMethodSig name sig cls =
+  find (\x -> methodName x == name && methodSignature x == sig) $ classMethods cls