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