clean up unused imports.
[hs-java.git] / JVM / Types.hs
index f54a8ba3ac62a3db010fa03e9741d70e1ed604dc..e685e7933a56dc0539709c0d429dbf636d957984 100644 (file)
@@ -3,9 +3,11 @@
 module JVM.Types where
 
 import Codec.Binary.UTF8.String hiding (encode, decode)
+import Control.Applicative
 import Data.Array
+import Data.Binary
+import Data.Binary.Put
 import qualified Data.ByteString.Lazy as B
-import Data.Word
 import Data.Char
 import Data.String
 import qualified Data.Set as S
@@ -22,6 +24,13 @@ toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
 -- | Constant pool
 type Pool = Array Word16 Constant
 
+asize :: (Ix i) => Array i e -> Int
+asize = length . elems
+
+showListIx :: (Show a) => [a] -> String
+showListIx list = unlines $ zipWith s [1..] list
+  where s i x = show i ++ ":\t" ++ show x
+
 class HasAttributes a where
   attributes :: a -> Attributes
 
@@ -56,7 +65,7 @@ deriving instance Eq (Signature a) => Eq (NameType a)
 
 -- | Constant pool item
 data Constant =
-    CClass {className :: B.ByteString}
+    CClass B.ByteString
   | CField {refClass :: B.ByteString, fieldNameType :: NameType Field}
   | CMethod {refClass :: B.ByteString, nameType :: NameType Method}
   | CIfaceMethod {refClass :: B.ByteString, nameType :: NameType Method}
@@ -70,6 +79,10 @@ data Constant =
   | CUnicode {getString :: B.ByteString}
   deriving (Eq)
 
+className ::  Constant -> B.ByteString
+className (CClass s) = s
+className x = error $ "Not a class: " ++ show x
+
 instance Show Constant where
   show (CClass name) = "class " ++ toString name
   show (CField cls nt) = "field " ++ toString cls ++ "." ++ show nt
@@ -117,18 +130,18 @@ type Access = S.Set AccessFlag
 
 -- | Access flags. Used for classess, methods, variables.
 data AccessFlag =
-    ACC_PUBLIC              -- 0x0001 Visible for all
-  | ACC_PRIVATE           -- 0x0002 Visible only for defined class
-  | ACC_PROTECTED       -- 0x0004 Visible only for subclasses
-  | ACC_STATIC              -- 0x0008 Static method or variable
-  | ACC_FINAL       -- 0x0010 No further subclassing or assignments
-  | ACC_SYNCHRONIZED -- 0x0020 Uses monitors
-  | ACC_VOLATILE          -- 0x0040 Could not be cached
-  | ACC_TRANSIENT       -- 0x0080 
-  | ACC_NATIVE              -- 0x0100 Implemented in other language
-  | ACC_INTERFACE       -- 0x0200 Class is interface
-  | ACC_ABSTRACT          -- 0x0400 
-  deriving (Eq, Show, Ord)
+    ACC_PUBLIC              -- 0x0001 Visible for all
+  | ACC_PRIVATE           -- 0x0002 Visible only for defined class
+  | ACC_PROTECTED       -- 0x0004 Visible only for subclasses
+  | ACC_STATIC              -- 0x0008 Static method or variable
+  | ACC_FINAL       -- 0x0010 No further subclassing or assignments
+  | ACC_SYNCHRONIZED -- 0x0020 Uses monitors
+  | ACC_VOLATILE          -- 0x0040 Could not be cached
+  | ACC_TRANSIENT       -- 0x0080 
+  | ACC_NATIVE              -- 0x0100 Implemented in other language
+  | ACC_INTERFACE       -- 0x0200 Class is interface
+  | ACC_ABSTRACT          -- 0x0400 
+  deriving (Eq, Show, Ord, Enum)
 
 -- | Generic attribute
 data Attribute = Attribute {
@@ -139,3 +152,11 @@ data Attribute = Attribute {
 -- | Set of attributes
 type Attributes = M.Map B.ByteString B.ByteString
 
+instance (Binary (Signature a)) => Binary (NameType a) where
+  put (NameType n t) = putLazyByteString n >> put t
+
+  get = NameType <$> get <*> get
+
+byteString ::  (Binary t) => t -> B.ByteString
+byteString x = runPut (put x)
+