dbf7e73806cc3fe0a3fd1d7531474732f3475ba6
[mate.git] / Mate / Types.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE CPP #-}
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 TrapCause
33
34 data TrapCause =
35   StaticMethod MethodInfo | -- for static calls
36   VirtualMethod Bool MethodInfo | -- for virtual calls
37   InterfaceMethod Bool MethodInfo | -- for interface calls
38   StaticField 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 instance Show MethodInfo where
57   show (MethodInfo method c sig) =
58     toString c ++ "." ++ toString method ++ "." ++ show sig
59
60
61
62 -- store information of loaded classes
63 type ClassMap = M.Map B.ByteString ClassInfo
64
65 data ClassInfo = ClassInfo {
66   ciName :: B.ByteString,
67   ciFile :: Class Direct,
68   ciStaticMap  :: FieldMap,
69   ciFieldMap :: FieldMap,
70   ciMethodMap :: FieldMap,
71   ciMethodBase :: Word32,
72   ciInitDone :: Bool }
73
74
75 -- store field offsets in a map
76 type FieldMap = M.Map B.ByteString Int32
77
78
79 -- java strings are allocated only once, therefore we
80 -- use a hashmap to store the address for a String
81 type StringMap = M.Map B.ByteString Word32
82
83
84 -- map "methodtable addr" to "classname"
85 -- we need that to identify the actual type
86 -- on the invokevirtual insn
87 type VirtualMap = M.Map Word32 B.ByteString
88
89
90 -- store each parsed Interface upon first loading
91 type InterfaceMap = M.Map B.ByteString (Class Direct)
92
93 -- store offset for each <Interface><Method><Signature> pair
94 type InterfaceMethodMap = M.Map B.ByteString Word32
95
96
97 {-
98 toString :: B.ByteString -> String
99 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
100 -}
101
102 -- better solutions for a global map hack are welcome! (typeclasses, TH, ...?)
103
104 data MateCtx = MateCtx {
105   ctxMethodMap :: MethodMap,
106   ctxTrapMap :: TrapMap,
107   ctxClassMap :: ClassMap,
108   ctxVirtualMap :: VirtualMap,
109   ctxStringMap :: StringMap,
110   ctxInterfaceMap :: InterfaceMap,
111   ctxInterfaceMethodMap :: InterfaceMethodMap }
112
113 emptyMateCtx :: MateCtx
114 emptyMateCtx = MateCtx M.empty M.empty M.empty M.empty M.empty M.empty M.empty
115
116 mateCtx :: IORef MateCtx
117 {-# NOINLINE mateCtx #-}
118 mateCtx = unsafePerformIO $ newIORef emptyMateCtx
119
120 -- TODO(bernhard): if we ever have thread support, don't forget MVars
121 #define SETMAP(name) set##name :: name -> IO (); \
122   set##name m = do ctx <- readIORef mateCtx; \
123   writeIORef mateCtx $ ctx { ctx##name = m };
124
125 #define GETMAP(name) get##name :: IO name ; \
126   get##name = do ctx <- readIORef mateCtx; \
127   return $ ctx##name ctx;
128
129 SETMAP(MethodMap);
130 GETMAP(MethodMap)
131
132 SETMAP(TrapMap)
133 GETMAP(TrapMap)
134
135 SETMAP(ClassMap)
136 GETMAP(ClassMap)
137
138 SETMAP(VirtualMap)
139 GETMAP(VirtualMap)
140
141 SETMAP(StringMap)
142 GETMAP(StringMap)
143
144 SETMAP(InterfaceMap)
145 GETMAP(InterfaceMap)
146
147 SETMAP(InterfaceMethodMap)
148 GETMAP(InterfaceMethodMap)