X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=Mate%2FUtilities.hs;h=da07ecf18eb95d860ce266f8ce3a927445d3ece1;hb=03ddf0056a8ebae7ce10d694bbf906c276677a33;hp=a73d60ca196c97204d64df261a0afc3f57488427;hpb=e9bbf51a0b41aee0b904936c4f1b69ca555d2648;p=mate.git diff --git a/Mate/Utilities.hs b/Mate/Utilities.hs index a73d60c..da07ecf 100644 --- a/Mate/Utilities.hs +++ b/Mate/Utilities.hs @@ -1,81 +1,74 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} module Mate.Utilities where -import Data.Char import Data.Word import qualified Data.Map as M +import qualified Data.Set as S import qualified Data.ByteString.Lazy as B --- import qualified Data.ByteString.Lazy.Char8 as B8 -import Codec.Binary.UTF8.String hiding (encode,decode) +import Data.List +import Data.Maybe import JVM.ClassFile -import Debug.Trace +import Mate.Types -data MethodInfo = MethodInfo { - methodname :: B.ByteString, - classname :: B.ByteString, - signature :: MethodSignature, - index :: Word16 } - -instance Eq MethodInfo where - (MethodInfo m_a c_a s_a i_a) == (MethodInfo m_b c_b s_b i_b) = - (m_a == m_b) && (c_a == c_b) && (s_a == s_b) && (i_a == i_b) - --- TODO(bernhard): not really efficient. also, outsource that to hs-java -instance Ord MethodSignature where - compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b) - | cmp_args /= EQ = cmp_args - | otherwise = (show ret_a) `compare` (show ret_b) - where - cmp_args = (show args_a) `compare` (show args_b) - -instance Ord MethodInfo where - compare (MethodInfo m_a c_a s_a i_a) (MethodInfo m_b c_b s_b i_b) - | cmp_m /= EQ = cmp_m - | cmp_c /= EQ = cmp_c - | cmp_s /= EQ = cmp_s - | otherwise = i_a `compare` i_b - where - cmp_m = m_a `compare` m_b - cmp_c = c_a `compare` c_b - cmp_s = s_a `compare` s_b +buildMethodID :: Class Direct -> Word16 -> MethodInfo +buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt) + where + (rc, nt) = case constsPool cls M.! idx of + (CMethod rc' nt') -> (rc', nt') + (CIfaceMethod rc' nt') -> (rc', nt') + _ -> error "buildMethodID: something wrong. abort." -instance Show MethodInfo where - show (MethodInfo method c sig idx) = - (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig) ++ "@" ++ (show idx) +buildStaticFieldID :: Class Direct -> Word16 -> StaticFieldInfo +buildStaticFieldID cls idx = StaticFieldInfo rc (ntName fnt) + where (CField rc fnt) = constsPool cls M.! idx +buildFieldOffset :: Class Direct -> Word16 -> (B.ByteString, B.ByteString) +buildFieldOffset cls idx = (rc, ntName fnt) + where (CField rc fnt) = constsPool cls M.! idx --- 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 +buildClassID :: Class Direct -> Word16 -> B.ByteString +buildClassID cls idx = cl + where (CClass cl) = constsPool cls M.! idx -toString :: B.ByteString -> String -toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr -buildMethodID :: Class Resolved -> Word16 -> MethodInfo -buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt) idx - where - (CMethod rc nt) = (constsPool cls) M.! idx +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 :: Class Resolved -> Word16 -> Word32 -methodGetArgsCount cls idx = fromIntegral $ length args - where - (CMethod _ nt) = (constsPool cls) M.! idx - (MethodSignature args _) = ntSignature nt +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 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; - _ -> error "methodHaveReturnValue: todo" + (Returns (Array _ _)) -> True + (Returns (ObjectType _)) -> True; + _ -> error $ "methodHaveReturnValue: todo: " ++ show ret where - (CMethod _ nt) = (constsPool cls) M.! idx - (MethodSignature _ ret) = ntSignature nt + nt = case constsPool cls M.! idx of + (CMethod _ nt') -> nt' + (CIfaceMethod _ nt') -> nt' + _ -> 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