e685e7933a56dc0539709c0d429dbf636d957984
[hs-java.git] / JVM / Types.hs
1 {-# LANGUAGE TypeFamilies, StandaloneDeriving, FlexibleInstances, FlexibleContexts, UndecidableInstances #-}
2 -- | This module declares `high-level' data types for Java classes, methods etc.
3 module JVM.Types where
4
5 import Codec.Binary.UTF8.String hiding (encode, decode)
6 import Control.Applicative
7 import Data.Array
8 import Data.Binary
9 import Data.Binary.Put
10 import qualified Data.ByteString.Lazy as B
11 import Data.Char
12 import Data.String
13 import qualified Data.Set as S
14 import qualified Data.Map as M
15
16 import JVM.ClassFile
17
18 instance IsString B.ByteString where
19   fromString s = B.pack $ map (fromIntegral . ord) $ encodeString s
20
21 toString :: B.ByteString -> String
22 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
23
24 -- | Constant pool
25 type Pool = Array Word16 Constant
26
27 asize :: (Ix i) => Array i e -> Int
28 asize = length . elems
29
30 showListIx :: (Show a) => [a] -> String
31 showListIx list = unlines $ zipWith s [1..] list
32   where s i x = show i ++ ":\t" ++ show x
33
34 class HasAttributes a where
35   attributes :: a -> Attributes
36
37 -- | Java class
38 data Class = Class {
39   constantPool :: Pool,
40   classAccess :: Access,
41   this :: B.ByteString,        -- ^ this class name
42   super :: Maybe B.ByteString, -- ^ super class name
43   implements :: [B.ByteString], -- ^ implemented interfaces
44   fields :: [Field],
45   methods :: [Method],
46   classAttrs :: Attributes
47   }
48   deriving (Eq, Show)
49
50 instance HasAttributes Class where
51   attributes = classAttrs
52
53 class HasSignature a where
54   type Signature a
55
56 -- | Name and signature pair. Used for methods and fields.
57 data NameType a = NameType {
58   ntName :: B.ByteString,
59   ntSignature :: Signature a }
60
61 instance Show (Signature a) => Show (NameType a) where
62   show (NameType n t) = toString n ++ ": " ++ show t
63
64 deriving instance Eq (Signature a) => Eq (NameType a)
65
66 -- | Constant pool item
67 data Constant =
68     CClass B.ByteString
69   | CField {refClass :: B.ByteString, fieldNameType :: NameType Field}
70   | CMethod {refClass :: B.ByteString, nameType :: NameType Method}
71   | CIfaceMethod {refClass :: B.ByteString, nameType :: NameType Method}
72   | CString B.ByteString
73   | CInteger Word32
74   | CFloat Float
75   | CLong Integer
76   | CDouble Double
77   | CNameType B.ByteString B.ByteString
78   | CUTF8 {getString :: B.ByteString}
79   | CUnicode {getString :: B.ByteString}
80   deriving (Eq)
81
82 className ::  Constant -> B.ByteString
83 className (CClass s) = s
84 className x = error $ "Not a class: " ++ show x
85
86 instance Show Constant where
87   show (CClass name) = "class " ++ toString name
88   show (CField cls nt) = "field " ++ toString cls ++ "." ++ show nt
89   show (CMethod cls nt) = "method " ++ toString cls ++ "." ++ show nt
90   show (CIfaceMethod cls nt) = "interface method " ++ toString cls ++ "." ++ show nt
91   show (CString s) = "String \"" ++ toString s ++ "\""
92   show (CInteger x) = show x
93   show (CFloat x) = show x
94   show (CLong x) = show x
95   show (CDouble x) = show x
96   show (CNameType name tp) = toString name ++ ": " ++ toString tp
97   show (CUTF8 s) = "UTF8 \"" ++ toString s ++ "\""
98   show (CUnicode s) = "Unicode \"" ++ toString s ++ "\""
99
100 -- | Class field
101 data Field = Field {
102   fieldAccess :: Access,
103   fieldName :: B.ByteString,
104   fieldSignature :: FieldSignature,
105   fieldAttrs :: Attributes }
106   deriving (Eq, Show)
107
108 instance HasSignature Field where
109   type Signature Field = FieldSignature
110
111 instance HasAttributes Field where
112   attributes = fieldAttrs
113
114 -- | Class method
115 data Method = Method {
116   methodAccess :: Access,
117   methodName :: B.ByteString,
118   methodSignature :: MethodSignature,
119   methodAttrs :: Attributes }
120   deriving (Eq, Show)
121
122 instance HasSignature Method where
123   type Signature Method = MethodSignature
124
125 instance HasAttributes Method where
126   attributes = methodAttrs
127
128 -- | Set of access flags
129 type Access = S.Set AccessFlag
130
131 -- | Access flags. Used for classess, methods, variables.
132 data AccessFlag =
133     ACC_PUBLIC       -- ^ 0x0001 Visible for all
134   | ACC_PRIVATE            -- ^ 0x0002 Visible only for defined class
135   | ACC_PROTECTED        -- ^ 0x0004 Visible only for subclasses
136   | ACC_STATIC       -- ^ 0x0008 Static method or variable
137   | ACC_FINAL        -- ^ 0x0010 No further subclassing or assignments
138   | ACC_SYNCHRONIZED -- ^ 0x0020 Uses monitors
139   | ACC_VOLATILE           -- ^ 0x0040 Could not be cached
140   | ACC_TRANSIENT        -- ^ 0x0080 
141   | ACC_NATIVE       -- ^ 0x0100 Implemented in other language
142   | ACC_INTERFACE        -- ^ 0x0200 Class is interface
143   | ACC_ABSTRACT           -- ^ 0x0400 
144   deriving (Eq, Show, Ord, Enum)
145
146 -- | Generic attribute
147 data Attribute = Attribute {
148   attrName :: B.ByteString,
149   attrValue :: B.ByteString }
150   deriving (Eq, Show)
151
152 -- | Set of attributes
153 type Attributes = M.Map B.ByteString B.ByteString
154
155 instance (Binary (Signature a)) => Binary (NameType a) where
156   put (NameType n t) = putLazyByteString n >> put t
157
158   get = NameType <$> get <*> get
159
160 byteString ::  (Binary t) => t -> B.ByteString
161 byteString x = runPut (put x)
162