modules: move (public) datatypes into a new module
[mate.git] / Mate / Utilities.hs
index 637d4d150c129cd81bbf28b12cc95e1f742d82a1..7002d19a9708526094ec6e6b0f9295093a20df3a 100644 (file)
@@ -1,16 +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 JVM.ClassFile
 
+import Mate.Types
+
 
 -- TODO: actually this function already exists in hs-java-0.3!
 lookupMethod :: B.ByteString -> Class Resolved -> Maybe (Method Resolved)
@@ -21,17 +19,10 @@ lookupMethod name cls = look (classMethods cls)
       | 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'
+buildMethodID :: Class Resolved -> Word16 -> MethodInfo
+buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt) idx
   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) "."
 
 methodGetArgsCount :: Class Resolved -> Word16 -> Word32
 methodGetArgsCount cls idx = fromIntegral $ length args