modules: move (public) datatypes into a new module
[mate.git] / Mate / Types.hs
1 module Mate.Types where
2
3 import Data.Char
4 import Data.Word
5 import qualified Data.Map as M
6 import qualified Data.ByteString.Lazy as B
7 import Codec.Binary.UTF8.String hiding (encode,decode)
8
9 import JVM.ClassFile
10 import JVM.Assembler
11
12
13 type BlockID = Int
14 -- Represents a CFG node
15 data BasicBlock = BasicBlock {
16                      code    :: [Instruction],
17                      successor :: BBEnd }
18
19 -- describes (leaving) edges of a CFG node
20 data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
21
22 type MapBB = M.Map BlockID BasicBlock
23
24
25 -- Word32 = point of method call in generated code
26 -- MethodInfo = relevant information about callee
27 type CMap = M.Map Word32 MethodInfo
28
29 -- B.ByteString = name of method
30 -- Word32 = entrypoint of method
31 type MMap = M.Map MethodInfo Word32
32
33
34
35 data MethodInfo = MethodInfo {
36   methName :: B.ByteString,
37   cName :: B.ByteString,
38   mSignature :: MethodSignature,
39   cpIndex :: Word16 }
40
41 instance Eq MethodInfo where
42   (MethodInfo m_a c_a s_a i_a) == (MethodInfo m_b c_b s_b i_b) =
43     (m_a == m_b) && (c_a == c_b) && (s_a == s_b) && (i_a == i_b)
44
45 -- TODO(bernhard): not really efficient. also, outsource that to hs-java
46 instance Ord MethodSignature where
47   compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
48     | cmp_args /= EQ = cmp_args
49     | otherwise = (show ret_a) `compare` (show ret_b)
50     where
51     cmp_args = (show args_a) `compare` (show args_b)
52
53 instance Ord MethodInfo where
54   compare (MethodInfo m_a c_a s_a i_a) (MethodInfo m_b c_b s_b i_b)
55     | cmp_m /= EQ = cmp_m
56     | cmp_c /= EQ = cmp_c
57     | cmp_s /= EQ = cmp_s
58     | otherwise = i_a `compare` i_b
59     where
60     cmp_m = m_a `compare` m_b
61     cmp_c = c_a `compare` c_b
62     cmp_s = s_a `compare` s_b
63
64 instance Show MethodInfo where
65   show (MethodInfo method c sig idx) =
66     (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig) ++ "@" ++ (show idx)
67
68
69 toString :: B.ByteString -> String
70 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr