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