refactor: rename types (more consistent style)
[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   SFI StaticFieldInfo
40
41 data StaticFieldInfo = StaticFieldInfo {
42   sfiClassName :: B.ByteString,
43   sfiFieldName :: B.ByteString }
44
45
46
47 -- B.ByteString = name of method
48 -- Word32 = entrypoint of method
49 type MethodMap = M.Map MethodInfo Word32
50
51 data MethodInfo = MethodInfo {
52   methName :: B.ByteString,
53   methClassName :: B.ByteString,
54   methSignature :: MethodSignature
55   } deriving (Eq, Ord)
56
57 -- TODO(bernhard): not really efficient. also, outsource that to hs-java
58 --                 deriving should be enough?
59 instance Ord MethodSignature where
60   compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
61     | cmp_args /= EQ = cmp_args
62     | otherwise = (show ret_a) `compare` (show ret_b)
63     where
64     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 StringsMap = 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 toString :: B.ByteString -> String
101 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
102
103
104 -- those functions are for the "global map hax"
105 -- TODO(bernhard): other solution please
106 foreign import ccall "get_trapmap"
107   get_trapmap :: IO (Ptr ())
108
109 foreign import ccall "set_trapmap"
110   set_trapmap :: Ptr () -> IO ()
111
112 foreign import ccall "get_methodmap"
113   get_methodmap :: IO (Ptr ())
114
115 foreign import ccall "set_methodmap"
116   set_methodmap :: Ptr () -> IO ()
117
118 foreign import ccall "get_classmap"
119   get_classmap :: IO (Ptr ())
120
121 foreign import ccall "set_classmap"
122   set_classmap :: Ptr () -> IO ()
123
124 foreign import ccall "get_virtualmap"
125   get_virtualmap :: IO (Ptr ())
126
127 foreign import ccall "set_virtualmap"
128   set_virtualmap :: Ptr () -> IO ()
129
130 foreign import ccall "get_stringsmap"
131   get_stringsmap :: IO (Ptr ())
132
133 foreign import ccall "set_stringsmap"
134   set_stringsmap :: Ptr () -> IO ()
135
136 -- TODO(bernhard): make some typeclass magic 'n stuff
137 --                 or remove that sh**
138 methodmap2ptr :: MethodMap -> IO (Ptr ())
139 methodmap2ptr methodmap = do
140   ptr_methodmap <- newStablePtr methodmap
141   return $ castStablePtrToPtr ptr_methodmap
142
143 ptr2methodmap :: Ptr () -> IO MethodMap
144 ptr2methodmap methodmap = deRefStablePtr $ ((castPtrToStablePtr methodmap) :: StablePtr MethodMap)
145
146 trapmap2ptr :: TrapMap -> IO (Ptr ())
147 trapmap2ptr trapmap = do
148   ptr_trapmap <- newStablePtr trapmap
149   return $ castStablePtrToPtr ptr_trapmap
150
151 ptr2trapmap :: Ptr () -> IO TrapMap
152 ptr2trapmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr trapmap)
153
154 classmap2ptr :: ClassMap -> IO (Ptr ())
155 classmap2ptr cmap = do
156   ptr_cmap <- newStablePtr cmap
157   return $ castStablePtrToPtr ptr_cmap
158
159 ptr2classmap :: Ptr () -> IO ClassMap
160 ptr2classmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
161
162 virtualmap2ptr :: VirtualMap -> IO (Ptr ())
163 virtualmap2ptr cmap = do
164   ptr_cmap <- newStablePtr cmap
165   return $ castStablePtrToPtr ptr_cmap
166
167 ptr2virtualmap :: Ptr () -> IO VirtualMap
168 ptr2virtualmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
169
170
171 stringsmap2ptr :: StringsMap -> IO (Ptr ())
172 stringsmap2ptr cmap = do
173   ptr_cmap <- newStablePtr cmap
174   return $ castStablePtrToPtr ptr_cmap
175
176 ptr2stringsmap :: Ptr () -> IO StringsMap
177 ptr2stringsmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)