invokevirtual: implemented. not very well tested though
[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 -- Word32 = point of method call in generated code
32 -- MethodInfo = relevant information about callee
33 type TMap = M.Map Word32 TrapInfo
34
35 data TrapInfo = MI MethodInfo | SFI StaticFieldInfo
36
37 data StaticFieldInfo = StaticFieldInfo {
38   sfiClassName :: B.ByteString,
39   sfiFieldName :: B.ByteString }
40
41 -- B.ByteString = name of method
42 -- Word32 = entrypoint of method
43 type MMap = M.Map MethodInfo Word32
44
45 type ClassMap = M.Map B.ByteString ClassInfo
46
47 type FieldMap = M.Map B.ByteString Int32
48
49 data ClassInfo = ClassInfo {
50   clName :: B.ByteString,
51   clFile :: Class Resolved,
52   clStaticMap  :: FieldMap,
53   clFieldMap :: FieldMap,
54   clMethodMap :: FieldMap,
55   clMethodBase :: Word32,
56   clInitDone :: Bool }
57
58 data MethodInfo = MethodInfo {
59   methName :: B.ByteString,
60   cName :: B.ByteString,
61   mSignature :: MethodSignature}
62
63 instance Eq MethodInfo where
64   (MethodInfo m_a c_a s_a) == (MethodInfo m_b c_b s_b) =
65     (m_a == m_b) && (c_a == c_b) && (s_a == s_b)
66
67 -- TODO(bernhard): not really efficient. also, outsource that to hs-java
68 instance Ord MethodSignature where
69   compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
70     | cmp_args /= EQ = cmp_args
71     | otherwise = (show ret_a) `compare` (show ret_b)
72     where
73     cmp_args = (show args_a) `compare` (show args_b)
74
75 instance Ord MethodInfo where
76   compare (MethodInfo m_a c_a s_a) (MethodInfo m_b c_b s_b)
77     | cmp_m /= EQ = cmp_m
78     | cmp_c /= EQ = cmp_c
79     | otherwise = s_a `compare` s_b
80     where
81     cmp_m = m_a `compare` m_b
82     cmp_c = c_a `compare` c_b
83
84 instance Show MethodInfo where
85   show (MethodInfo method c sig) =
86     (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig)
87
88
89 toString :: B.ByteString -> String
90 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
91
92
93 -- global map hax
94 foreign import ccall "get_trapmap"
95   get_trapmap :: IO (Ptr ())
96
97 foreign import ccall "set_trapmap"
98   set_trapmap :: Ptr () -> IO ()
99
100 foreign import ccall "get_methodmap"
101   get_methodmap :: IO (Ptr ())
102
103 foreign import ccall "set_methodmap"
104   set_methodmap :: Ptr () -> IO ()
105
106 foreign import ccall "get_classmap"
107   get_classmap :: IO (Ptr ())
108
109 foreign import ccall "set_classmap"
110   set_classmap :: Ptr () -> IO ()
111
112 -- TODO(bernhard): make some typeclass magic 'n stuff
113 mmap2ptr :: MMap -> IO (Ptr ())
114 mmap2ptr mmap = do
115   ptr_mmap <- newStablePtr mmap
116   return $ castStablePtrToPtr ptr_mmap
117
118 ptr2mmap :: Ptr () -> IO MMap
119 ptr2mmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr MMap)
120
121 tmap2ptr :: TMap -> IO (Ptr ())
122 tmap2ptr tmap = do
123   ptr_tmap <- newStablePtr tmap
124   return $ castStablePtrToPtr ptr_tmap
125
126 ptr2tmap :: Ptr () -> IO TMap
127 ptr2tmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr tmap)
128
129 classmap2ptr :: ClassMap -> IO (Ptr ())
130 classmap2ptr cmap = do
131   ptr_cmap <- newStablePtr cmap
132   return $ castStablePtrToPtr ptr_cmap
133
134 ptr2classmap :: Ptr () -> IO ClassMap
135 ptr2classmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)