modules: move (public) datatypes into a new module
authorBernhard Urban <lewurm@gmail.com>
Sun, 22 Apr 2012 18:42:50 +0000 (20:42 +0200)
committerBernhard Urban <lewurm@gmail.com>
Sun, 22 Apr 2012 18:42:50 +0000 (20:42 +0200)
Mate.hs
Mate/BasicBlocks.hs
Mate/MethodPool.hs
Mate/Types.hs [new file with mode: 0644]
Mate/Utilities.hs
Mate/X86CodeGen.hs

diff --git a/Mate.hs b/Mate.hs
index 1acc64d48940fef9221a1745bd9016e517e03735..05754bed7277a7242a159e9415710c10ab650f5e 100644 (file)
--- a/Mate.hs
+++ b/Mate.hs
@@ -16,7 +16,7 @@ import JVM.Dump
 import Mate.BasicBlocks
 import Mate.X86CodeGen
 import Mate.MethodPool
-import Mate.Utilities
+import Mate.Types
 
 main ::  IO ()
 main = do
index 59e30521b5b33937262059169ea653d5b12dfd43..229325d6a36423514d95f29dee312746a215854b 100644 (file)
@@ -21,22 +21,10 @@ import JVM.Converter
 import JVM.Assembler
 
 import Mate.Utilities
+import Mate.Types
 
 
-type BlockID = Int
--- Represents a CFG node
-data BasicBlock = BasicBlock {
-                     -- inputs  :: [Variable],
-                     -- outputs :: [Variable],
-                     code    :: [Instruction],
-                     successor :: BBEnd }
-
--- describes (leaving) edges of a CFG node
-data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
-
-type MapBB = M.Map BlockID BasicBlock
-
--- for immediate representation for determine BBs
+-- for immediate representation to determine BBs
 type Offset = (Int, Maybe BBEnd) -- (offset in bytecode, offset to jump target)
 type OffIns = (Offset, Instruction)
 
index 2cd739e54f383a5e719d9b9af68e5a51cdf19b67..762e787f609dc8b76bd675e0821aebbc755bc6fe 100644 (file)
@@ -19,8 +19,8 @@ import Harpy
 import Harpy.X86Disassembler
 
 import Mate.BasicBlocks
+import Mate.Types
 import Mate.X86CodeGen
-import Mate.Utilities
 
 
 foreign import ccall "get_mmap"
@@ -29,11 +29,6 @@ foreign import ccall "get_mmap"
 foreign import ccall "set_mmap"
   set_mmap :: Ptr () -> IO ()
 
-
--- B.ByteString = name of method
--- Word32 = entrypoint of method
-type MMap = M.Map MethodInfo Word32
-
 foreign export ccall getMethodEntry :: CUInt -> Ptr () -> Ptr () -> IO CUInt
 getMethodEntry :: CUInt -> Ptr () -> Ptr () -> IO CUInt
 getMethodEntry signal_from ptr_mmap ptr_cmap = do
@@ -41,7 +36,7 @@ getMethodEntry signal_from ptr_mmap ptr_cmap = do
   cmap <- ptr2cmap ptr_cmap
 
   let w32_from = fromIntegral signal_from
-  let mi@(MethodInfo method cm sig cpidx) = cmap M.! w32_from
+  let mi@(MethodInfo method cm _ cpidx) = cmap M.! w32_from
   -- TODO(bernhard): replace parsing with some kind of classpool
   cls <- parseClassFile $ toString $ cm `B.append` ".class"
   case M.lookup mi mmap of
@@ -79,7 +74,7 @@ compileBB hmap methodinfo = do
   cmap <- get_cmap >>= ptr2cmap
 
   -- TODO(bernhard): replace parsing with some kind of classpool
-  cls <- parseClassFile $ toString $ (classname methodinfo) `B.append` ".class"
+  cls <- parseClassFile $ toString $ (cName methodinfo) `B.append` ".class"
   let ebb = emitFromBB cls hmap
   (_, Right ((entry, _, _, new_cmap), disasm)) <- runCodeGen ebb () ()
   let w32_entry = ((fromIntegral $ ptrToIntPtr entry) :: Word32)
diff --git a/Mate/Types.hs b/Mate/Types.hs
new file mode 100644 (file)
index 0000000..95ae4e4
--- /dev/null
@@ -0,0 +1,70 @@
+module Mate.Types where
+
+import Data.Char
+import Data.Word
+import qualified Data.Map as M
+import qualified Data.ByteString.Lazy as B
+import Codec.Binary.UTF8.String hiding (encode,decode)
+
+import JVM.ClassFile
+import JVM.Assembler
+
+
+type BlockID = Int
+-- Represents a CFG node
+data BasicBlock = BasicBlock {
+                     code    :: [Instruction],
+                     successor :: BBEnd }
+
+-- describes (leaving) edges of a CFG node
+data BBEnd = Return | FallThrough BlockID | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
+
+type MapBB = M.Map BlockID BasicBlock
+
+
+-- Word32 = point of method call in generated code
+-- MethodInfo = relevant information about callee
+type CMap = M.Map Word32 MethodInfo
+
+-- B.ByteString = name of method
+-- Word32 = entrypoint of method
+type MMap = M.Map MethodInfo Word32
+
+
+
+data MethodInfo = MethodInfo {
+  methName :: B.ByteString,
+  cName :: B.ByteString,
+  mSignature :: MethodSignature,
+  cpIndex :: Word16 }
+
+instance Eq MethodInfo where
+  (MethodInfo m_a c_a s_a i_a) == (MethodInfo m_b c_b s_b i_b) =
+    (m_a == m_b) && (c_a == c_b) && (s_a == s_b) && (i_a == i_b)
+
+-- TODO(bernhard): not really efficient. also, outsource that to hs-java
+instance Ord MethodSignature where
+  compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
+    | cmp_args /= EQ = cmp_args
+    | otherwise = (show ret_a) `compare` (show ret_b)
+    where
+    cmp_args = (show args_a) `compare` (show args_b)
+
+instance Ord MethodInfo where
+  compare (MethodInfo m_a c_a s_a i_a) (MethodInfo m_b c_b s_b i_b)
+    | cmp_m /= EQ = cmp_m
+    | cmp_c /= EQ = cmp_c
+    | cmp_s /= EQ = cmp_s
+    | otherwise = i_a `compare` i_b
+    where
+    cmp_m = m_a `compare` m_b
+    cmp_c = c_a `compare` c_b
+    cmp_s = s_a `compare` s_b
+
+instance Show MethodInfo where
+  show (MethodInfo method c sig idx) =
+    (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig) ++ "@" ++ (show idx)
+
+
+toString :: B.ByteString -> String
+toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
index a73d60ca196c97204d64df261a0afc3f57488427..7002d19a9708526094ec6e6b0f9295093a20df3a 100644 (file)
@@ -1,50 +1,13 @@
 {-# LANGUAGE OverloadedStrings #-}
 module Mate.Utilities where
 
-import Data.Char
 import Data.Word
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
--- import qualified Data.ByteString.Lazy.Char8 as B8
-import Codec.Binary.UTF8.String hiding (encode,decode)
 
 import JVM.ClassFile
 
-import Debug.Trace
-
-
-data MethodInfo = MethodInfo {
-  methodname :: B.ByteString,
-  classname :: B.ByteString,
-  signature :: MethodSignature,
-  index :: Word16 }
-
-instance Eq MethodInfo where
-  (MethodInfo m_a c_a s_a i_a) == (MethodInfo m_b c_b s_b i_b) =
-    (m_a == m_b) && (c_a == c_b) && (s_a == s_b) && (i_a == i_b)
-
--- TODO(bernhard): not really efficient. also, outsource that to hs-java
-instance Ord MethodSignature where
-  compare (MethodSignature args_a ret_a) (MethodSignature args_b ret_b)
-    | cmp_args /= EQ = cmp_args
-    | otherwise = (show ret_a) `compare` (show ret_b)
-    where
-    cmp_args = (show args_a) `compare` (show args_b)
-
-instance Ord MethodInfo where
-  compare (MethodInfo m_a c_a s_a i_a) (MethodInfo m_b c_b s_b i_b)
-    | cmp_m /= EQ = cmp_m
-    | cmp_c /= EQ = cmp_c
-    | cmp_s /= EQ = cmp_s
-    | otherwise = i_a `compare` i_b
-    where
-    cmp_m = m_a `compare` m_b
-    cmp_c = c_a `compare` c_b
-    cmp_s = s_a `compare` s_b
-
-instance Show MethodInfo where
-  show (MethodInfo method c sig idx) =
-    (toString c) ++ "." ++ (toString method) ++ "." ++ (show sig) ++ "@" ++ (show idx)
+import Mate.Types
 
 
 -- TODO: actually this function already exists in hs-java-0.3!
@@ -56,9 +19,6 @@ lookupMethod name cls = look (classMethods cls)
       | methodName f == name = Just f
       | otherwise  = look fs
 
-toString :: B.ByteString -> String
-toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
-
 buildMethodID :: Class Resolved -> Word16 -> MethodInfo
 buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt) idx
   where
index d2c9caf19d69cce0c19928b8ce542b9af8a4d90f..21d2b3c88db364fa3711d520d3ee1a3f858a3fc3 100644 (file)
@@ -23,6 +23,7 @@ import Harpy
 import Harpy.X86Disassembler
 
 import Mate.BasicBlocks
+import Mate.Types
 import Mate.Utilities
 
 foreign import ccall "dynamic"
@@ -119,10 +120,6 @@ type BBStarts = M.Map BlockID Int
 
 type CompileInfo = (EntryPoint, BBStarts, Int, CMap)
 
--- Word32 = point of method call in generated code
--- MethodInfo = relevant information about callee
-type CMap = M.Map Word32 MethodInfo
-
 
 emitFromBB :: Class Resolved -> MapBB -> CodeGen e s (CompileInfo, [Instruction])
 emitFromBB cls hmap =  do