global map hack: refactor
[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 qualified Data.Map as M
8 import qualified Data.ByteString.Lazy as B
9 import Codec.Binary.UTF8.String hiding (encode,decode)
10
11 import Foreign.Ptr
12 import Foreign.C.Types
13 import Foreign.C.String
14 import Foreign.StablePtr
15
16 import JVM.ClassFile
17 import JVM.Assembler
18
19
20 type BlockID = Int
21 -- Represents a CFG node
22 data BasicBlock = BasicBlock {
23                      code    :: [Instruction],
24                      successor :: BBEnd }
25
26 -- describes (leaving) edges of a CFG node
27 data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
28
29 type MapBB = M.Map BlockID BasicBlock
30
31
32 -- Word32 = point of method call in generated code
33 -- MethodInfo = relevant information about callee
34 type CMap = M.Map Word32 MethodInfo
35
36 -- B.ByteString = name of method
37 -- Word32 = entrypoint of method
38 type MMap = M.Map MethodInfo Word32
39
40 type ClassMap = M.Map B.ByteString ClassInfo
41
42 data ClassInfo = ClassInfo {
43   clName :: B.ByteString,
44   clFile :: Class Resolved }
45
46
47 data MethodInfo = MethodInfo {
48   methName :: B.ByteString,
49   cName :: B.ByteString,
50   mSignature :: MethodSignature}
51
52 instance Eq MethodInfo where
53   (MethodInfo m_a c_a s_a) == (MethodInfo m_b c_b s_b) =
54     (m_a == m_b) && (c_a == c_b) && (s_a == s_b)
55
56 -- TODO(bernhard): not really efficient. also, outsource that to hs-java
57 instance Ord MethodSignature where
58   compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
59     | cmp_args /= EQ = cmp_args
60     | otherwise = (show ret_a) `compare` (show ret_b)
61     where
62     cmp_args = (show args_a) `compare` (show args_b)
63
64 instance Ord MethodInfo where
65   compare (MethodInfo m_a c_a s_a) (MethodInfo m_b c_b s_b)
66     | cmp_m /= EQ = cmp_m
67     | cmp_c /= EQ = cmp_c
68     | otherwise = s_a `compare` s_b
69     where
70     cmp_m = m_a `compare` m_b
71     cmp_c = c_a `compare` c_b
72
73 instance Show MethodInfo where
74   show (MethodInfo method c sig) =
75     (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig)
76
77
78 toString :: B.ByteString -> String
79 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
80
81
82 -- global map hax
83 foreign import ccall "get_callermap"
84   get_callermap :: IO (Ptr ())
85
86 foreign import ccall "set_callermap"
87   set_callermap :: Ptr () -> IO ()
88
89 foreign import ccall "get_methodmap"
90   get_methodmap :: IO (Ptr ())
91
92 foreign import ccall "set_methodmap"
93   set_methodmap :: Ptr () -> IO ()
94
95 foreign import ccall "get_classmap"
96   get_classmap :: IO (Ptr ())
97
98 foreign import ccall "set_classmap"
99   set_classmap :: Ptr () -> IO ()
100
101 -- TODO(bernhard): make some typeclass magic 'n stuff
102 mmap2ptr :: MMap -> IO (Ptr ())
103 mmap2ptr mmap = do
104   ptr_mmap <- newStablePtr mmap
105   return $ castStablePtrToPtr ptr_mmap
106
107 ptr2mmap :: Ptr () -> IO MMap
108 ptr2mmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr MMap)
109
110 cmap2ptr :: CMap -> IO (Ptr ())
111 cmap2ptr cmap = do
112   ptr_cmap <- newStablePtr cmap
113   return $ castStablePtrToPtr ptr_cmap
114
115 ptr2cmap :: Ptr () -> IO CMap
116 ptr2cmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)
117
118 classmap2ptr :: ClassMap -> IO (Ptr ())
119 classmap2ptr cmap = do
120   ptr_cmap <- newStablePtr cmap
121   return $ castStablePtrToPtr ptr_cmap
122
123 ptr2classmap :: Ptr () -> IO ClassMap
124 ptr2classmap vmap = deRefStablePtr $ ((castPtrToStablePtr vmap) :: StablePtr cmap)