cabal: bump data-default dependency to 0.5.0.
[hs-java.git] / JVM / ClassFile.hs
index 6171c1bdecffd3854bc85f5c1c7259dc63cc2f52..68ea764a338cc02f4a32e48f1167020400720da4 100644 (file)
@@ -5,6 +5,7 @@ module JVM.ClassFile
   (-- * About
    -- $about
    --
+   --
    -- * Internal class file structures
    Attribute (..),
    FieldType (..),
@@ -25,6 +26,7 @@ module JVM.ClassFile
    NameType (..),
    fieldNameType, methodNameType,
    lookupField, lookupMethod,
+   long,
    toString,
    className,
    apsize, arsize, arlist
@@ -145,11 +147,11 @@ class (Binary (Signature a), Show (Signature a), Eq (Signature a))
     => HasSignature a where
   type Signature a
 
-instance HasSignature Field where
-  type Signature Field = FieldSignature
+instance HasSignature (Field Direct) where
+  type Signature (Field Direct) = FieldSignature
 
-instance HasSignature Method where
-  type Signature Method = MethodSignature
+instance HasSignature (Method Direct) where
+  type Signature (Method Direct) = MethodSignature
 
 -- | Name and signature pair. Used for methods and fields.
 data NameType a = NameType {
@@ -169,9 +171,9 @@ instance HasSignature a => Binary (NameType a) where
 -- | Constant pool item
 data Constant stage =
     CClass (Link stage B.ByteString)
-  | 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))
+  | CField (Link stage B.ByteString) (Link stage (NameType (Field stage)))
+  | CMethod (Link stage B.ByteString) (Link stage (NameType (Method stage)))
+  | CIfaceMethod (Link stage B.ByteString) (Link stage (NameType (Method stage)))
   | CString (Link stage B.ByteString)
   | CInteger Word32
   | CFloat Float
@@ -205,22 +207,22 @@ type Pool stage = M.Map Word16 (Constant stage)
 
 -- | Generic .class file format
 data Class stage = Class {
-  magic :: Word32,                   -- ^ Magic value: 0xCAFEBABE
+  magic :: Word32,                         -- ^ Magic value: 0xCAFEBABE
   minorVersion :: Word16,
   majorVersion :: Word16,
-  constsPoolSize :: Word16,          -- ^ Number of items in constants pool
-  constsPool :: Pool stage,            -- ^ Constants pool itself
-  accessFlags :: AccessFlags stage,             -- ^ See @JVM.Types.AccessFlag@
-  thisClass :: Link stage B.ByteString,               -- ^ Constants pool item index for this class
-  superClass :: Link stage B.ByteString,              -- ^ --/-- for super class, zero for java.lang.Object
-  interfacesCount :: Word16,         -- ^ Number of implemented interfaces
-  interfaces :: [Link stage B.ByteString],            -- ^ Constants pool item indexes for implemented interfaces
-  classFieldsCount :: Word16,        -- ^ Number of class fileds
-  classFields :: [Field stage],        -- ^ Class fields
-  classMethodsCount :: Word16,       -- ^ Number of class methods
-  classMethods :: [Method stage],      -- ^ Class methods
-  classAttributesCount :: Word16,    -- ^ Number of class attributes
-  classAttributes :: Attributes stage -- ^ Class attributes
+  constsPoolSize :: Word16,                -- ^ Number of items in constants pool
+  constsPool :: Pool stage,                -- ^ Constants pool itself
+  accessFlags :: AccessFlags stage,        -- ^ See @JVM.Types.AccessFlag@
+  thisClass :: Link stage B.ByteString,    -- ^ Constants pool item index for this class
+  superClass :: Link stage B.ByteString,   -- ^ --/-- for super class, zero for java.lang.Object
+  interfacesCount :: Word16,               -- ^ Number of implemented interfaces
+  interfaces :: [Link stage B.ByteString], -- ^ Constants pool item indexes for implemented interfaces
+  classFieldsCount :: Word16,              -- ^ Number of class fileds
+  classFields :: [Field stage],            -- ^ Class fields
+  classMethodsCount :: Word16,             -- ^ Number of class methods
+  classMethods :: [Method stage],          -- ^ Class methods
+  classAttributesCount :: Word16,          -- ^ Number of class attributes
+  classAttributes :: Attributes stage      -- ^ Class attributes
   }
 
 deriving instance Eq (Class File)
@@ -308,7 +310,7 @@ data FieldType =
   | BoolType   -- ^ Z
   | ObjectType String -- ^ L @{class name}@
   | Array (Maybe Int) FieldType -- ^ @[{type}@
-  deriving (Eq)
+  deriving (Eq, Ord)
 
 instance Show FieldType where
   show SignedByte = "byte"
@@ -394,7 +396,7 @@ getToSemicolon = do
 data ReturnSignature =
     Returns FieldType
   | ReturnsVoid
-  deriving (Eq)
+  deriving (Eq, Ord)
 
 instance Show ReturnSignature where
   show (Returns t) = show t
@@ -416,7 +418,7 @@ type ArgumentSignature = FieldType
 -- | Class method argument signature
 data MethodSignature =
     MethodSignature [ArgumentSignature] ReturnSignature
-  deriving (Eq)
+  deriving (Eq, Ord)
 
 instance Show MethodSignature where
   show (MethodSignature args ret) = "(" ++ intercalate ", " (map show args) ++ ") returns " ++ show ret
@@ -459,6 +461,7 @@ whileJust m = do
               return (x: next)
     Nothing -> return []
 
+long :: Constant stage -> Bool
 long (CLong _)   = True
 long (CDouble _) = True
 long _           = False
@@ -554,7 +557,7 @@ lookupField name cls = look (classFields cls)
       | fieldName f == name = Just f
       | otherwise           = look fs
 
-fieldNameType :: Field Direct -> NameType Field
+fieldNameType :: Field Direct -> NameType (Field Direct)
 fieldNameType f = NameType (fieldName f) (fieldSignature f)
 
 instance Binary (Field File) where
@@ -586,7 +589,7 @@ deriving instance Eq (Method Direct)
 deriving instance Show (Method File)
 deriving instance Show (Method Direct)
 
-methodNameType :: Method Direct -> NameType Method
+methodNameType :: Method Direct -> NameType (Method Direct)
 methodNameType m = NameType (methodName m) (methodSignature m)
 
 lookupMethod :: B.ByteString -> Class Direct -> Maybe (Method Direct)