25a418e4b64077fb55e19ec03d9ea043c1e7ce21
[mate.git] / Mate / BasicBlocks.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 module Mate.BasicBlocks(
3   BlockID,
4   BasicBlock (..),
5   BBEnd (..),
6   MapBB,
7   printMapBB,
8   parseMethod
9   )where
10
11 import Data.Binary
12 import Data.Int
13 import qualified Data.Map as H
14 import System.Environment
15 import qualified Data.Map as M
16 import qualified Data.ByteString.Lazy as B
17
18 import JVM.Common
19 import JVM.ClassFile
20 import JVM.Converter
21 import JVM.Dump
22 import JVM.Assembler
23
24 import Debug.Trace
25
26 import Mate.Utilities
27
28 type Name       = String -- use "virtual register id" instead?
29 data Type       = JInt | JFloat -- add more
30 type Variable   = (Type,Name)
31
32 type BlockID = Int
33 -- Represents a CFG node
34 data BasicBlock = BasicBlock {
35                      -- inputs  :: [Variable],
36                      -- outputs :: [Variable],
37                      code    :: [Instruction],
38                      successor :: BBEnd }
39
40 -- describes (leaving) edges of a CFG node
41 data BBEnd = Return | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
42
43 type MapBB = H.Map BlockID BasicBlock
44
45 -- for immediate representation for determine BBs
46 type Offset = (Int, Maybe BBEnd) -- (offset in bytecode, offset to jump target)
47 type OffIns = (Offset, Instruction)
48
49
50 printMapBB :: Maybe MapBB -> IO ()
51 printMapBB Nothing = putStrLn "No BasicBlock"
52 printMapBB (Just hmap) = do
53                      putStr "BlockIDs: "
54                      let keys = fst $ unzip $ H.toList hmap
55                      mapM_ (putStr . (flip (++)) ", " . show) keys
56                      putStrLn "\n\nBasicBlocks:"
57                      printMapBB' keys hmap
58   where
59   printMapBB' :: [BlockID] -> MapBB -> IO ()
60   printMapBB' [] _ = return ()
61   printMapBB' (i:is) hmap = case H.lookup i hmap of
62                   Just bb -> do
63                              putStrLn $ "Block " ++ (show i)
64                              mapM_ putStrLn (map ((++) "\t" . show) $ code bb)
65                              case successor bb of
66                                Return -> putStrLn ""
67                                OneTarget t1 -> putStrLn $ "Sucessor: " ++ (show t1) ++ "\n"
68                                TwoTarget t1 t2 -> putStrLn $ "Sucessor: " ++ (show t1) ++ ", " ++ (show t2) ++ "\n"
69                              printMapBB' is hmap
70                   Nothing -> error $ "BlockID " ++ show i ++ " not found."
71
72 testInstance :: String -> B.ByteString -> IO ()
73 testInstance cf method = do
74                       hmap <- parseMethod cf method
75                       printMapBB hmap
76
77 test_01 = testInstance "./tests/Fib.class" "fib"
78 test_02 = testInstance "./tests/While.class" "f"
79 test_03 = testInstance "./tests/While.class" "g"
80
81
82 parseMethod :: String -> B.ByteString -> IO (Maybe MapBB)
83 parseMethod clspath method = do
84                      cls <- parseClassFile clspath
85                      return $ testCFG $ lookupMethod method cls
86
87
88 testCFG :: Maybe (Method Resolved) -> Maybe MapBB
89 testCFG (Just m) = case attrByName m "Code" of
90                      Nothing       -> Nothing
91                      Just bytecode -> let code = decodeMethod bytecode
92                                           instructions = codeInstructions code
93                                       in Just $ buildCFG instructions
94 testCFG _        = Nothing
95
96
97 buildCFG :: [Instruction] -> MapBB
98 buildCFG xs = buildCFG' H.empty xs' xs'
99   where
100   xs' :: [OffIns]
101   xs' = calculateInstructionOffset xs
102
103 buildCFG' :: MapBB -> [OffIns] -> [OffIns] -> MapBB
104 buildCFG' hmap [] _ = hmap
105 buildCFG' hmap (((off, entry), _):xs) insns = buildCFG' (insertlist entryi hmap) xs insns
106   where
107   insertlist :: [BlockID] -> MapBB -> MapBB
108   insertlist [] hmap = hmap
109   insertlist (x:xs) hmap = insertlist xs newhmap
110     where
111     newhmap = if H.member x hmap then hmap else H.insert x value hmap
112     value = parseBasicBlock x insns
113
114   entryi :: [BlockID]
115   entryi = (if off == 0 then [0] else []) ++ -- also consider the entrypoint
116         case entry of
117         Just (TwoTarget t1 t2) -> [t1, t2]
118         Just (OneTarget t) -> [t]
119         Just (Return) -> []
120         Nothing -> []
121
122
123 parseBasicBlock :: Int -> [OffIns] -> BasicBlock
124 parseBasicBlock i insns = BasicBlock insonly endblock
125   where
126   startlist = dropWhile (\((x,_),_) -> x < i) insns
127   (Just ((_,(Just endblock)),_), is) = takeWhilePlusOne validins startlist
128   insonly = snd $ unzip is
129
130   -- also take last (non-matched) element and return it
131   takeWhilePlusOne :: (a -> Bool) -> [a] -> (Maybe a,[a])
132   takeWhilePlusOne _ [] = (Nothing,[])
133   takeWhilePlusOne p (x:xs)
134     | p x       =  let (lastins, list) = takeWhilePlusOne p xs in (lastins, (x:list))
135     | otherwise =  (Just x,[x])
136
137   validins :: ((Int, Maybe BBEnd), Instruction) -> Bool
138   validins ((_,x),_) = case x of Just _ -> False; Nothing -> True
139
140
141 calculateInstructionOffset :: [Instruction] -> [OffIns]
142 calculateInstructionOffset = cio' (0, Nothing)
143   where
144   newoffset :: Instruction -> Int -> Offset
145   newoffset x off = (off + (fromIntegral $ B.length $ encodeInstructions [x]), Nothing)
146
147   addW16Signed :: Int -> Word16 -> Int
148   addW16Signed i w16 = i + (fromIntegral s16)
149     where s16 = (fromIntegral w16) :: Int16
150
151   cio' :: Offset -> [Instruction] -> [OffIns]
152   cio' _ [] = []
153   -- TODO(bernhard): add more instruction with offset (IF_ACMP, JSR, ...)
154   cio' (off,_) (x:xs) = case x of
155       IF _ w16 -> twotargets w16
156       IF_ICMP _ w16 -> twotargets w16
157       GOTO w16 -> onetarget w16
158       IRETURN -> notarget
159       _ -> ((off, Nothing), x):next
160     where
161     notarget = ((off, Just Return), x):next
162     onetarget w16 = ((off, Just $ OneTarget $ (off `addW16Signed` w16)), x):next
163     twotargets w16 = ((off, Just $ TwoTarget (off + 3) (off `addW16Signed` w16)), x):next
164     next = cio' (newoffset x off) xs