X-Git-Url: http://wien.tomnetworks.com/gitweb/?a=blobdiff_plain;f=JVM%2FClassFile.hs;h=6171c1bdecffd3854bc85f5c1c7259dc63cc2f52;hb=fe123653d0ba6155561a0c73726a505b360df194;hp=0359320592a9ab1cf10aa464f795423ade56ebf4;hpb=d47b4af2d4cf72352782e8c88a6e03670ca15737;p=hs-java.git diff --git a/JVM/ClassFile.hs b/JVM/ClassFile.hs index 0359320..6171c1b 100644 --- a/JVM/ClassFile.hs +++ b/JVM/ClassFile.hs @@ -19,22 +19,29 @@ module JVM.ClassFile Constant (..), AccessFlag (..), AccessFlags, Attributes (..), + defaultClass, -- * Misc HasSignature (..), HasAttributes (..), NameType (..), + fieldNameType, methodNameType, + lookupField, lookupMethod, + toString, className, apsize, arsize, arlist ) where import Control.Monad +import Control.Monad.Trans (lift) import Control.Applicative +import qualified Control.Monad.State as St import Data.Binary import Data.Binary.IEEE754 import Data.Binary.Get import Data.Binary.Put import Data.Char import Data.List +import Data.Default import qualified Data.Set as S import qualified Data.Map as M import qualified Data.ByteString.Lazy as B @@ -96,10 +103,16 @@ data family Attributes stage data instance Attributes File = AP {attributesList :: [Attribute]} deriving (Eq, Show) +instance Default (Attributes File) where + def = AP [] + -- | At Direct stage, attributes are represented as a Map. data instance Attributes Direct = AR (M.Map B.ByteString B.ByteString) deriving (Eq, Show) +instance Default (Attributes Direct) where + def = AR M.empty + -- | Size of attributes set at Direct stage arsize :: Attributes Direct -> Int arsize (AR m) = M.size m @@ -128,7 +141,8 @@ data AccessFlag = deriving (Eq, Show, Ord, Enum) -- | Fields and methods have signatures. -class HasSignature a where +class (Binary (Signature a), Show (Signature a), Eq (Signature a)) + => HasSignature a where type Signature a instance HasSignature Field where @@ -142,12 +156,12 @@ data NameType a = NameType { ntName :: B.ByteString, ntSignature :: Signature a } -instance Show (Signature a) => Show (NameType a) where +instance (HasSignature a) => Show (NameType a) where show (NameType n t) = toString n ++ ": " ++ show t -deriving instance Eq (Signature a) => Eq (NameType a) +deriving instance HasSignature a => Eq (NameType a) -instance (Binary (Signature a)) => Binary (NameType a) where +instance HasSignature a => Binary (NameType a) where put (NameType n t) = putLazyByteString n >> put t get = NameType <$> get <*> get @@ -155,13 +169,13 @@ instance (Binary (Signature a)) => Binary (NameType a) where -- | Constant pool item data Constant stage = CClass (Link stage B.ByteString) - | CField {refClass :: Link stage B.ByteString, fieldNameType :: Link stage (NameType Field)} - | CMethod {refClass :: Link stage B.ByteString, nameType :: Link stage (NameType Method)} - | CIfaceMethod {refClass :: Link stage B.ByteString, nameType :: Link stage (NameType Method)} + | CField (Link stage B.ByteString) (Link stage (NameType Field)) + | CMethod (Link stage B.ByteString) (Link stage (NameType Method)) + | CIfaceMethod (Link stage B.ByteString) (Link stage (NameType Method)) | CString (Link stage B.ByteString) | CInteger Word32 | CFloat Float - | CLong Integer + | CLong Word64 | CDouble Double | CNameType (Link stage B.ByteString) (Link stage B.ByteString) | CUTF8 {getString :: B.ByteString} @@ -209,17 +223,42 @@ data Class stage = Class { classAttributes :: Attributes stage -- ^ Class attributes } +deriving instance Eq (Class File) +deriving instance Eq (Class Direct) +deriving instance Show (Class File) +deriving instance Show (Class Direct) + deriving instance Eq (Constant File) deriving instance Eq (Constant Direct) deriving instance Show (Constant File) +-- | Default (empty) class file definition. +defaultClass :: (Default (AccessFlags stage), Default (Link stage B.ByteString), Default (Attributes stage)) + => Class stage +defaultClass = Class { + magic = 0xCAFEBABE, + minorVersion = 0, + majorVersion = 50, + constsPoolSize = 0, + constsPool = def, + accessFlags = def, + thisClass = def, + superClass = def, + interfacesCount = 0, + interfaces = [], + classFieldsCount = 0, + classFields = [], + classMethodsCount = 0, + classMethods = [], + classAttributesCount = 0, + classAttributes = def } + instance Binary (Class File) where put (Class {..}) = do put magic put minorVersion put majorVersion - put constsPoolSize - forM_ (M.elems constsPool) put + putPool constsPool put accessFlags put thisClass put superClass @@ -234,23 +273,26 @@ instance Binary (Class File) where get = do magic <- get + when (magic /= 0xCAFEBABE) $ + fail $ "Invalid .class file MAGIC value: " ++ show magic minor <- get major <- get - poolsize <- get - pool <- replicateM (fromIntegral poolsize - 1) get - af <- get + when (major > 50) $ + fail $ "Too new .class file format: " ++ show major + poolsize <- getWord16be + pool <- getPool (poolsize - 1) + af <- get this <- get super <- get interfacesCount <- get ifaces <- replicateM (fromIntegral interfacesCount) get - classFieldsCount <- get + classFieldsCount <- getWord16be classFields <- replicateM (fromIntegral classFieldsCount) get classMethodsCount <- get classMethods <- replicateM (fromIntegral classMethodsCount) get asCount <- get as <- replicateM (fromIntegral $ asCount) get - let pool' = M.fromList $ zip [1..] pool - return $ Class magic minor major poolsize pool' af this super + return $ Class magic minor major poolsize pool af this super interfacesCount ifaces classFieldsCount classFields classMethodsCount classMethods asCount (AP as) @@ -417,49 +459,79 @@ whileJust m = do return (x: next) Nothing -> return [] -instance Binary (Constant File) where - put (CClass i) = putWord8 7 >> put i - put (CField i j) = putWord8 9 >> put i >> put j - put (CMethod i j) = putWord8 10 >> put i >> put j - put (CIfaceMethod i j) = putWord8 11 >> put i >> put j - put (CString i) = putWord8 8 >> put i - put (CInteger x) = putWord8 3 >> put x - put (CFloat x) = putWord8 4 >> putFloat32be x - put (CLong x) = putWord8 5 >> put x - put (CDouble x) = putWord8 6 >> putFloat64be x - put (CNameType i j) = putWord8 12 >> put i >> put j - put (CUTF8 bs) = do - putWord8 1 - put (fromIntegral (B.length bs) :: Word16) - putLazyByteString bs - put (CUnicode bs) = do - putWord8 2 - put (fromIntegral (B.length bs) :: Word16) - putLazyByteString bs +long (CLong _) = True +long (CDouble _) = True +long _ = False - get = do - !offset <- bytesRead - tag <- getWord8 - case tag of - 1 -> do - l <- get - bs <- getLazyByteString (fromIntegral (l :: Word16)) - return $ CUTF8 bs - 2 -> do - l <- get - bs <- getLazyByteString (fromIntegral (l :: Word16)) - return $ CUnicode bs - 3 -> CInteger <$> get - 4 -> CFloat <$> getFloat32be - 5 -> CLong <$> get - 6 -> CDouble <$> getFloat64be - 7 -> CClass <$> get - 8 -> CString <$> get - 9 -> CField <$> get <*> get - 10 -> CMethod <$> get <*> get - 11 -> CIfaceMethod <$> get <*> get - 12 -> CNameType <$> get <*> get - _ -> fail $ "Unknown constants pool entry tag: " ++ show tag +putPool :: Pool File -> Put +putPool pool = do + let list = M.elems pool + d = length $ filter long list + putWord16be $ fromIntegral (M.size pool + d + 1) + forM_ list putC + where + putC (CClass i) = putWord8 7 >> put i + putC (CField i j) = putWord8 9 >> put i >> put j + putC (CMethod i j) = putWord8 10 >> put i >> put j + putC (CIfaceMethod i j) = putWord8 11 >> put i >> put j + putC (CString i) = putWord8 8 >> put i + putC (CInteger x) = putWord8 3 >> put x + putC (CFloat x) = putWord8 4 >> putFloat32be x + putC (CLong x) = putWord8 5 >> put x + putC (CDouble x) = putWord8 6 >> putFloat64be x + putC (CNameType i j) = putWord8 12 >> put i >> put j + putC (CUTF8 bs) = do + putWord8 1 + put (fromIntegral (B.length bs) :: Word16) + putLazyByteString bs + putC (CUnicode bs) = do + putWord8 2 + put (fromIntegral (B.length bs) :: Word16) + putLazyByteString bs + +getPool :: Word16 -> Get (Pool File) +getPool n = do + items <- St.evalStateT go 1 + return $ M.fromList items + where + go :: St.StateT Word16 Get [(Word16, Constant File)] + go = do + i <- St.get + if i > n + then return [] + else do + c <- lift getC + let i' = if long c + then i+2 + else i+1 + St.put i' + next <- go + return $ (i,c): next + + getC = do + !offset <- bytesRead + tag <- getWord8 + case tag of + 1 -> do + l <- get + bs <- getLazyByteString (fromIntegral (l :: Word16)) + return $ CUTF8 bs + 2 -> do + l <- get + bs <- getLazyByteString (fromIntegral (l :: Word16)) + return $ CUnicode bs + 3 -> CInteger <$> get + 4 -> CFloat <$> getFloat32be + 5 -> CLong <$> get + 6 -> CDouble <$> getFloat64be + 7 -> CClass <$> get + 8 -> CString <$> get + 9 -> CField <$> get <*> get + 10 -> CMethod <$> get <*> get + 11 -> CIfaceMethod <$> get <*> get + 12 -> CNameType <$> get <*> get + _ -> fail $ "Unknown constants pool entry tag: " ++ show tag +-- _ -> return $ CInteger 0 -- | Class field format data Field stage = Field { @@ -474,6 +546,17 @@ deriving instance Eq (Field Direct) deriving instance Show (Field File) deriving instance Show (Field Direct) +lookupField :: B.ByteString -> Class Direct -> Maybe (Field Direct) +lookupField name cls = look (classFields cls) + where + look [] = Nothing + look (f:fs) + | fieldName f == name = Just f + | otherwise = look fs + +fieldNameType :: Field Direct -> NameType Field +fieldNameType f = NameType (fieldName f) (fieldSignature f) + instance Binary (Field File) where put (Field {..}) = do put fieldAccessFlags @@ -484,9 +567,9 @@ instance Binary (Field File) where get = do af <- get - ni <- get + ni <- getWord16be si <- get - n <- get + n <- getWord16be as <- replicateM (fromIntegral n) get return $ Field af ni si n (AP as) @@ -503,6 +586,17 @@ deriving instance Eq (Method Direct) deriving instance Show (Method File) deriving instance Show (Method Direct) +methodNameType :: Method Direct -> NameType Method +methodNameType m = NameType (methodName m) (methodSignature m) + +lookupMethod :: B.ByteString -> Class Direct -> Maybe (Method Direct) +lookupMethod name cls = look (classMethods cls) + where + look [] = Nothing + look (f:fs) + | methodName f == name = Just f + | otherwise = look fs + instance Binary (Method File) where put (Method {..}) = do put methodAccessFlags @@ -541,7 +635,7 @@ instance Binary Attribute where get = do offset <- bytesRead - name <- get + name <- getWord16be len <- getWord32be value <- getLazyByteString (fromIntegral len) return $ Attribute name len value