637d4d150c129cd81bbf28b12cc95e1f742d82a1
[mate.git] / Mate / Utilities.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 module Mate.Utilities where
3
4 import Data.Char
5 import Data.Word
6 import Data.Binary
7 import qualified Data.Map as M
8 import qualified Data.ByteString.Lazy as B
9 -- import qualified Data.ByteString.Lazy.Char8 as B8
10 import Codec.Binary.UTF8.String hiding (encode,decode)
11
12 import JVM.ClassFile
13
14
15 -- TODO: actually this function already exists in hs-java-0.3!
16 lookupMethod :: B.ByteString -> Class Resolved -> Maybe (Method Resolved)
17 lookupMethod name cls = look (classMethods cls)
18   where
19     look [] = Nothing
20     look (f:fs)
21       | methodName f == name = Just f
22       | otherwise  = look fs
23
24 toString :: B.ByteString -> String
25 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
26
27 buildMethodID :: Class Resolved -> Word16 -> B.ByteString
28 buildMethodID cls idx = (rc `B.append` dot) `B.append` (ntName nt) `B.append` nt'
29   where
30   (CMethod rc nt) = (constsPool cls) M.! idx
31   nt' = encode $ ntSignature nt
32   dot :: B.ByteString
33   -- TODO(bernhard): WTF? why -XOverloadedStrings doesn't apply here?
34   dot = B.pack $ map (fromIntegral . ord) "."
35
36 methodGetArgsCount :: Class Resolved -> Word16 -> Word32
37 methodGetArgsCount cls idx = fromIntegral $ length args
38   where
39   (CMethod _ nt) = (constsPool cls) M.! idx
40   (MethodSignature args _) = ntSignature nt
41
42 -- TODO(bernhard): Extend it to more than just int, and provide typeinformation
43 methodHaveReturnValue :: Class Resolved -> Word16 -> Bool
44 methodHaveReturnValue cls idx = case ret of
45     ReturnsVoid -> False;
46     (Returns IntType) -> True;
47     _ -> error "methodHaveReturnValue: todo"
48   where
49   (CMethod _ nt) = (constsPool cls) M.! idx
50   (MethodSignature _ ret) = ntSignature nt