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