types: remove dirty Ord instance of MethodSignature
[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 instance Show MethodInfo where
56   show (MethodInfo method c sig) =
57     toString c ++ "." ++ toString method ++ "." ++ show sig
58
59
60
61 -- store information of loaded classes
62 type ClassMap = M.Map B.ByteString ClassInfo
63
64 data ClassInfo = ClassInfo {
65   ciName :: B.ByteString,
66   ciFile :: Class Direct,
67   ciStaticMap  :: FieldMap,
68   ciFieldMap :: FieldMap,
69   ciMethodMap :: FieldMap,
70   ciMethodBase :: Word32,
71   ciInitDone :: Bool }
72
73
74 -- store field offsets in a map
75 type FieldMap = M.Map B.ByteString Int32
76
77
78 -- java strings are allocated only once, therefore we
79 -- use a hashmap to store the address for a String
80 type StringMap = M.Map B.ByteString Word32
81
82
83 -- map "methodtable addr" to "classname"
84 -- we need that to identify the actual type
85 -- on the invokevirtual insn
86 type VirtualMap = M.Map Word32 B.ByteString
87
88
89 -- store each parsed Interface upon first loading
90 type InterfaceMap = M.Map B.ByteString (Class Direct)
91
92 -- store offset for each <Interface><Method><Signature> pair
93 type InterfaceMethodMap = M.Map B.ByteString Word32
94
95
96 {-
97 toString :: B.ByteString -> String
98 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
99 -}
100
101
102 data MateCtx = MateCtx {
103   ctxMethodMap :: MethodMap,
104   ctxTrapMap :: TrapMap,
105   ctxClassMap :: ClassMap,
106   ctxVirtualMap :: VirtualMap,
107   ctxStringMap :: StringMap,
108   ctxInterfaceMap :: InterfaceMap,
109   ctxInterfaceMethodMap :: InterfaceMethodMap }
110
111 emptyMateCtx :: MateCtx
112 emptyMateCtx = MateCtx M.empty M.empty M.empty M.empty M.empty M.empty M.empty
113
114 mateCtx :: IORef MateCtx
115 {-# NOINLINE mateCtx #-}
116 mateCtx = unsafePerformIO $ newIORef emptyMateCtx
117
118
119 setMethodMap :: MethodMap -> IO ()
120 setMethodMap m = do
121   ctx <- readIORef mateCtx
122   writeIORef mateCtx $ ctx { ctxMethodMap = m }
123
124 getMethodMap :: IO MethodMap
125 getMethodMap = do
126   ctx <- readIORef mateCtx
127   return $ ctxMethodMap ctx
128
129
130 setTrapMap :: TrapMap -> IO ()
131 setTrapMap m = do
132   ctx <- readIORef mateCtx
133   writeIORef mateCtx $ ctx { ctxTrapMap = m }
134
135 getTrapMap :: IO TrapMap
136 getTrapMap = do
137   ctx <- readIORef mateCtx
138   return $ ctxTrapMap ctx
139
140
141 setClassMap :: ClassMap -> IO ()
142 setClassMap m = do
143   ctx <- readIORef mateCtx
144   writeIORef mateCtx $ ctx { ctxClassMap = m }
145
146 getClassMap :: IO ClassMap
147 getClassMap = do
148   ctx <- readIORef mateCtx
149   return $ ctxClassMap ctx
150
151
152 setVirtualMap :: VirtualMap -> IO ()
153 setVirtualMap m = do
154   ctx <- readIORef mateCtx
155   writeIORef mateCtx $ ctx { ctxVirtualMap = m }
156
157 getVirtualMap :: IO VirtualMap
158 getVirtualMap = do
159   ctx <- readIORef mateCtx
160   return $ ctxVirtualMap ctx
161
162
163 setStringMap :: StringMap -> IO ()
164 setStringMap m = do
165   ctx <- readIORef mateCtx
166   writeIORef mateCtx $ ctx { ctxStringMap = m }
167
168 getStringMap :: IO StringMap
169 getStringMap = do
170   ctx <- readIORef mateCtx
171   return $ ctxStringMap ctx
172
173
174 setInterfaceMap :: InterfaceMap -> IO ()
175 setInterfaceMap m = do
176   ctx <- readIORef mateCtx
177   writeIORef mateCtx $ ctx { ctxInterfaceMap = m }
178
179 getInterfaceMap :: IO InterfaceMap
180 getInterfaceMap = do
181   ctx <- readIORef mateCtx
182   return $ ctxInterfaceMap ctx
183
184
185 setInterfaceMethodMap :: InterfaceMethodMap -> IO ()
186 setInterfaceMethodMap m = do
187   ctx <- readIORef mateCtx
188   writeIORef mateCtx $ ctx { ctxInterfaceMethodMap = m }
189
190 getInterfaceMethodMap :: IO InterfaceMethodMap
191 getInterfaceMethodMap = do
192   ctx <- readIORef mateCtx
193   return $ ctxInterfaceMethodMap ctx