Merge branch 'master' of wien.tomnetworks.com:mate
[mate.git] / Mate / Utilities.hs
index 8733ca398506b5c8b14ac704f7139cb9f9e484e3..ed92530ff70f1c36229dbb301474a95669c5ecf1 100644 (file)
@@ -1,10 +1,14 @@
+{-# LANGUAGE OverloadedStrings #-}
 module Mate.Utilities where
 
+import Data.Char
+import Data.Word
+import Data.Binary
+import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
+-- import qualified Data.ByteString.Lazy.Char8 as B8
+import Codec.Binary.UTF8.String hiding (encode,decode)
 
-import qualified JVM.Assembler as J
-import JVM.Assembler hiding (Instruction)
-import JVM.Common
 import JVM.ClassFile
 
 
@@ -16,3 +20,15 @@ lookupMethod name cls = look (classMethods cls)
     look (f:fs)
       | methodName f == name = Just f
       | otherwise  = look fs
+
+toString :: B.ByteString -> String
+toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
+
+buildMethodID :: Class Resolved -> Word16 -> B.ByteString
+buildMethodID cls idx = (rc `B.append` dot) `B.append` (ntName nt) `B.append` nt'
+  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) "."