hs-java: upgrade to 0.3.1
[mate.git] / Mate / Types.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE ForeignFunctionInterface #-}
3 module Mate.Types where
4
5 import Data.Word
6 import Data.Int
7 import qualified Data.Map as M
8 import qualified Data.ByteString.Lazy as B
9
10 import Data.IORef
11 import System.IO.Unsafe
12
13 import JVM.ClassFile
14 import JVM.Assembler
15
16
17 type BlockID = Int
18 -- Represents a CFG node
19 data BasicBlock = BasicBlock {
20   code :: [Instruction],
21   successor :: BBEnd }
22
23 -- describes (leaving) edges of a CFG node
24 data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
25
26 type MapBB = M.Map BlockID BasicBlock
27
28
29
30 -- Word32 = point of method call in generated code
31 -- MethodInfo = relevant information about callee
32 type TrapMap = M.Map Word32 TrapInfo
33
34 data TrapInfo =
35   MI MethodInfo | -- for static calls
36   VI MethodInfo | -- for virtual calls
37   II MethodInfo | -- for interface calls
38   SFI StaticFieldInfo deriving Show
39
40 data StaticFieldInfo = StaticFieldInfo {
41   sfiClassName :: B.ByteString,
42   sfiFieldName :: B.ByteString } deriving Show
43
44
45
46 -- B.ByteString = name of method
47 -- Word32 = entrypoint of method
48 type MethodMap = M.Map MethodInfo Word32
49
50 data MethodInfo = MethodInfo {
51   methName :: B.ByteString,
52   methClassName :: B.ByteString,
53   methSignature :: MethodSignature
54   } deriving (Eq, Ord)
55
56 -- TODO(bernhard): not really efficient. also, outsource that to hs-java
57 --                 deriving should be enough?
58 instance Ord MethodSignature where
59   compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
60     | cmp_args /= EQ = cmp_args
61     | otherwise = show ret_a `compare` show ret_b
62     where cmp_args = show args_a `compare` show args_b
63
64 instance Show MethodInfo where
65   show (MethodInfo method c sig) =
66     toString c ++ "." ++ toString method ++ "." ++ show sig
67
68
69
70 -- store information of loaded classes
71 type ClassMap = M.Map B.ByteString ClassInfo
72
73 data ClassInfo = ClassInfo {
74   ciName :: B.ByteString,
75   ciFile :: Class Direct,
76   ciStaticMap  :: FieldMap,
77   ciFieldMap :: FieldMap,
78   ciMethodMap :: FieldMap,
79   ciMethodBase :: Word32,
80   ciInitDone :: Bool }
81
82
83 -- store field offsets in a map
84 type FieldMap = M.Map B.ByteString Int32
85
86
87 -- java strings are allocated only once, therefore we
88 -- use a hashmap to store the address for a String
89 type StringMap = M.Map B.ByteString Word32
90
91
92 -- map "methodtable addr" to "classname"
93 -- we need that to identify the actual type
94 -- on the invokevirtual insn
95 type VirtualMap = M.Map Word32 B.ByteString
96
97
98 -- store each parsed Interface upon first loading
99 type InterfaceMap = M.Map B.ByteString (Class Direct)
100
101 -- store offset for each <Interface><Method><Signature> pair
102 type InterfaceMethodMap = M.Map B.ByteString Word32
103
104
105 {-
106 toString :: B.ByteString -> String
107 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
108 -}
109
110
111 data MateCtx = MateCtx {
112   ctxMethodMap :: MethodMap,
113   ctxTrapMap :: TrapMap,
114   ctxClassMap :: ClassMap,
115   ctxVirtualMap :: VirtualMap,
116   ctxStringMap :: StringMap,
117   ctxInterfaceMap :: InterfaceMap,
118   ctxInterfaceMethodMap :: InterfaceMethodMap }
119
120 emptyMateCtx :: MateCtx
121 emptyMateCtx = MateCtx M.empty M.empty M.empty M.empty M.empty M.empty M.empty
122
123 mateCtx :: IORef MateCtx
124 {-# NOINLINE mateCtx #-}
125 mateCtx = unsafePerformIO $ newIORef emptyMateCtx
126
127
128 setMethodMap :: MethodMap -> IO ()
129 setMethodMap m = do
130   ctx <- readIORef mateCtx
131   writeIORef mateCtx $ ctx { ctxMethodMap = m }
132
133 getMethodMap :: IO MethodMap
134 getMethodMap = do
135   ctx <- readIORef mateCtx
136   return $ ctxMethodMap ctx
137
138
139 setTrapMap :: TrapMap -> IO ()
140 setTrapMap m = do
141   ctx <- readIORef mateCtx
142   writeIORef mateCtx $ ctx { ctxTrapMap = m }
143
144 getTrapMap :: IO TrapMap
145 getTrapMap = do
146   ctx <- readIORef mateCtx
147   return $ ctxTrapMap ctx
148
149
150 setClassMap :: ClassMap -> IO ()
151 setClassMap m = do
152   ctx <- readIORef mateCtx
153   writeIORef mateCtx $ ctx { ctxClassMap = m }
154
155 getClassMap :: IO ClassMap
156 getClassMap = do
157   ctx <- readIORef mateCtx
158   return $ ctxClassMap ctx
159
160
161 setVirtualMap :: VirtualMap -> IO ()
162 setVirtualMap m = do
163   ctx <- readIORef mateCtx
164   writeIORef mateCtx $ ctx { ctxVirtualMap = m }
165
166 getVirtualMap :: IO VirtualMap
167 getVirtualMap = do
168   ctx <- readIORef mateCtx
169   return $ ctxVirtualMap ctx
170
171
172 setStringMap :: StringMap -> IO ()
173 setStringMap m = do
174   ctx <- readIORef mateCtx
175   writeIORef mateCtx $ ctx { ctxStringMap = m }
176
177 getStringMap :: IO StringMap
178 getStringMap = do
179   ctx <- readIORef mateCtx
180   return $ ctxStringMap ctx
181
182
183 setInterfaceMap :: InterfaceMap -> IO ()
184 setInterfaceMap m = do
185   ctx <- readIORef mateCtx
186   writeIORef mateCtx $ ctx { ctxInterfaceMap = m }
187
188 getInterfaceMap :: IO InterfaceMap
189 getInterfaceMap = do
190   ctx <- readIORef mateCtx
191   return $ ctxInterfaceMap ctx
192
193
194 setInterfaceMethodMap :: InterfaceMethodMap -> IO ()
195 setInterfaceMethodMap m = do
196   ctx <- readIORef mateCtx
197   writeIORef mateCtx $ ctx { ctxInterfaceMethodMap = m }
198
199 getInterfaceMethodMap :: IO InterfaceMethodMap
200 getInterfaceMethodMap = do
201   ctx <- readIORef mateCtx
202   return $ ctxInterfaceMethodMap ctx