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