X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=Mate%2FUtilities.hs;h=8f234e5394ab5faba2ddc58cae9c019bc3845172;hb=08628062840ccf3730e239222c30e78b403dc6f4;hp=7a75466e9af87e8c8f1ee0b7051198779e3c7efc;hpb=b6e379114b45fca215e766816e9db94199bb4f00;p=mate.git diff --git a/Mate/Utilities.hs b/Mate/Utilities.hs index 7a75466..8f234e5 100644 --- a/Mate/Utilities.hs +++ b/Mate/Utilities.hs @@ -1,49 +1,90 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} module Mate.Utilities where import Data.Word import qualified Data.Map as M +import qualified Data.Set as S import qualified Data.ByteString.Lazy as B +import Data.List +import Data.Maybe import JVM.ClassFile import Mate.Types +import Mate.NativeSizes +#ifdef DEBUG +import Text.Printf +#endif --- 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 - (CMethod rc nt) = (constsPool cls) M.! idx + (rc, nt) = case constsPool cls M.! idx of + (CMethod rc' nt') -> (rc', nt') + (CIfaceMethod rc' nt') -> (rc', nt') + _ -> 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 cls idx = (thisClass cls, 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 -methodGetArgsCount :: Class Resolved -> Word16 -> Word32 -methodGetArgsCount cls idx = fromIntegral $ length args - where - (CMethod _ nt) = (constsPool cls) M.! idx - (MethodSignature args _) = ntSignature nt +buildClassID :: Class Direct -> Word16 -> B.ByteString +buildClassID cls idx = cl + where (CClass cl) = 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 :: NameType (Method Direct) -> NativeWord +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 + +hexDumpMap :: Integral v => String -> M.Map B.ByteString v -> IO () +#ifdef DEBUG +hexDumpMap header mmap = do + let printValue :: B.ByteString -> IO () + printValue key = printf "\t%-70s: 0x%08x\n" (toString key) val + where val = fromIntegral (mmap M.! key) :: NativeWord + printf "%s\n" header + mapM_ printValue (M.keys mmap) +#else +hexDumpMap _ _ = return () +#endif