2f2f3a17808cd9eb6bddef9adbfbc58f73436362
[hs-java.git] / JVM / Types.hs
1 {-# LANGUAGE TypeFamilies, StandaloneDeriving, FlexibleInstances, FlexibleContexts, UndecidableInstances #-}
2 module JVM.Types where
3
4 import Codec.Binary.UTF8.String hiding (encode, decode)
5 import Data.Array
6 import qualified Data.ByteString.Lazy as B
7 import Data.Word
8 import Data.Char
9 import Data.String
10 import qualified Data.Set as S
11 import qualified Data.Map as M
12
13 import JVM.ClassFile
14
15 instance IsString B.ByteString where
16   fromString s = B.pack $ map (fromIntegral . ord) $ encodeString s
17
18 type Pool = Array Word16 Constant
19
20 class HasAttributes a where
21   attributes :: a -> Attributes
22
23 data Class = Class {
24   constantPool :: Pool,
25   classAccess :: Access,
26   this :: B.ByteString,        -- ^ this class name
27   super :: Maybe B.ByteString, -- ^ super class name
28   implements :: [B.ByteString], -- ^ implemented interfaces
29   fields :: [Field],
30   methods :: [Method],
31   classAttrs :: Attributes
32   }
33   deriving (Eq, Show)
34
35 instance HasAttributes Class where
36   attributes = classAttrs
37
38 class HasSignature a where
39   type Signature a
40
41 data NameType a = NameType {
42   ntName :: B.ByteString,
43   ntSignature :: Signature a }
44
45 deriving instance Show (Signature a) => Show (NameType a)
46 deriving instance Eq (Signature a) => Eq (NameType a)
47
48 data Constant =
49     CClass {className :: B.ByteString}
50   | CField {refClass :: B.ByteString, fieldNameType :: NameType Field}
51   | CMethod {refClass :: B.ByteString, nameType :: NameType Method}
52   | CIfaceMethod {refClass :: B.ByteString, nameType :: NameType Method}
53   | CString B.ByteString
54   | CInteger Word32
55   | CFloat Float
56   | CLong Integer
57   | CDouble Double
58   | CNameType B.ByteString B.ByteString
59   | CUTF8 {getString :: B.ByteString}
60   | CUnicode {getString :: B.ByteString}
61   deriving (Eq, Show)
62
63 data Field = Field {
64   fieldAccess :: Access,
65   fieldName :: B.ByteString,
66   fieldSignature :: FieldSignature,
67   fieldAttrs :: Attributes }
68   deriving (Eq, Show)
69
70 instance HasSignature Field where
71   type Signature Field = FieldSignature
72
73 instance HasAttributes Field where
74   attributes = fieldAttrs
75
76 data Method = Method {
77   methodAccess :: Access,
78   methodName :: B.ByteString,
79   methodSignature :: MethodSignature,
80   methodAttrs :: Attributes }
81   deriving (Eq, Show)
82
83 instance HasSignature Method where
84   type Signature Method = MethodSignature
85
86 instance HasAttributes Method where
87   attributes = methodAttrs
88
89 type Access = S.Set AccessFlag
90
91 data AccessFlag =
92     ACC_PUBLIC       -- 0x0001 Видимый для всех   Класс, Метод, Переменная
93   | ACC_PRIVATE            -- 0x0002 Видимый только для определяемого класса         Метод, Переменная
94   | ACC_PROTECTED        -- 0x0004 Видимый для подклассов   Метод, Переменная
95   | ACC_STATIC       -- 0x0008 Переменная или метод статические    Метод, Переменная
96   | ACC_FINAL        -- 0x0010 Нет дальнейшей подкласификации, обхода или присваивания после инициализации   Класс, Метод, Переменная
97   | ACC_SYNCHRONIZED -- 0x0020 Использует возврат в блокировке монитора     Метод
98   | ACC_VOLATILE           -- 0x0040 Не может помещать в кеш         Переменная
99   | ACC_TRANSIENT        -- 0x0080 Не может боть написан или прочитан постоянным объектом управления   Перемення
100   | ACC_NATIVE       -- 0x0100 Реализован в других языках        Метод
101   | ACC_INTERFACE        -- 0x0200 интерфейс   Класс
102   | ACC_ABSTRACT           -- 0x0400 Ничего не предусматривает   Класс, Метод
103   deriving (Eq, Show, Ord)
104
105 data Attribute = Attribute {
106   attrName :: B.ByteString,
107   attrValue :: B.ByteString }
108   deriving (Eq, Show)
109
110 class AttributeValue a where
111   decodeAttribute :: B.ByteString -> a
112   encodeAttribute :: a -> B.ByteString
113
114 type Attributes = M.Map B.ByteString B.ByteString
115