332bd56a6c7aefbf1784a87b65c9241933ecd1f1
[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   test_main
10   )where
11
12 import Data.Binary
13 import Data.Int
14 import qualified Data.Map as M
15 import qualified Data.ByteString.Lazy as B
16
17 import JVM.ClassFile
18 import JVM.Converter
19 import JVM.Assembler
20
21 import Mate.Utilities
22
23
24 type BlockID = Int
25 -- Represents a CFG node
26 data BasicBlock = BasicBlock {
27                      -- inputs  :: [Variable],
28                      -- outputs :: [Variable],
29                      code    :: [Instruction],
30                      successor :: BBEnd }
31
32 -- describes (leaving) edges of a CFG node
33 data BBEnd = Return | OneTarget BlockID | TwoTarget BlockID BlockID deriving Show
34
35 type MapBB = M.Map BlockID BasicBlock
36
37 -- for immediate representation for determine BBs
38 type Offset = (Int, Maybe BBEnd) -- (offset in bytecode, offset to jump target)
39 type OffIns = (Offset, Instruction)
40
41
42 printMapBB :: Maybe MapBB -> IO ()
43 printMapBB Nothing = putStrLn "No BasicBlock"
44 printMapBB (Just hmap) = do
45                      putStr "BlockIDs: "
46                      let keys = fst $ unzip $ M.toList hmap
47                      mapM_ (putStr . (flip (++)) ", " . show) keys
48                      putStrLn "\n\nBasicBlocks:"
49                      printMapBB' keys hmap
50   where
51   printMapBB' :: [BlockID] -> MapBB -> IO ()
52   printMapBB' [] _ = return ()
53   printMapBB' (i:is) hmap' = case M.lookup i hmap' of
54                   Just bb -> do
55                              putStrLn $ "Block " ++ (show i)
56                              mapM_ putStrLn (map ((++) "\t" . show) $ code bb)
57                              case successor bb of
58                                Return -> putStrLn ""
59                                OneTarget t1 -> putStrLn $ "Sucessor: " ++ (show t1) ++ "\n"
60                                TwoTarget t1 t2 -> putStrLn $ "Sucessor: " ++ (show t1) ++ ", " ++ (show t2) ++ "\n"
61                              printMapBB' is hmap
62                   Nothing -> error $ "BlockID " ++ show i ++ " not found."
63
64 testInstance :: String -> B.ByteString -> IO ()
65 testInstance cf method = do
66                       cls <- parseClassFile cf
67                       hmap <- parseMethod cls method
68                       printMapBB hmap
69
70 test_main :: IO ()
71 test_main = do
72   test_01
73   test_02
74   test_03
75
76 test_01, test_02, test_03 :: IO ()
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 :: Class Resolved -> B.ByteString -> IO (Maybe MapBB)
83 parseMethod cls method = do
84                      -- TODO(bernhard): remove me! just playing around with
85                      --                 hs-java interface.
86                      -- we get that index at the INVOKESTATIC insn
87                      putStrLn "via constpool @2:"
88                      let cp = constsPool cls
89                      let (CMethod rc nt) = cp M.! (2 :: Word16)
90                      -- rc :: Link stage B.ByteString
91                      -- nt :: Link stage (NameType Method)
92                      B.putStrLn $ "rc: " `B.append` rc
93                      B.putStrLn $ "nt: " `B.append` (encode $ ntSignature nt)
94
95                      putStrLn "via methods:"
96                      let msig = methodSignature $ (classMethods cls) !! 1
97                      B.putStrLn (method `B.append` ": " `B.append` (encode msig))
98
99                      return $ testCFG $ lookupMethod method cls
100
101
102 testCFG :: Maybe (Method Resolved) -> Maybe MapBB
103 testCFG (Just m) = case attrByName m "Code" of
104        Nothing -> Nothing
105        Just bytecode -> Just $ buildCFG $ codeInstructions $ decodeMethod bytecode
106 testCFG _ = Nothing
107
108
109 buildCFG :: [Instruction] -> MapBB
110 buildCFG xs = buildCFG' M.empty xs' xs'
111   where
112   xs' :: [OffIns]
113   xs' = calculateInstructionOffset xs
114
115 buildCFG' :: MapBB -> [OffIns] -> [OffIns] -> MapBB
116 buildCFG' hmap [] _ = hmap
117 buildCFG' hmap (((off, entry), _):xs) insns = buildCFG' (insertlist entryi hmap) xs insns
118   where
119   insertlist :: [BlockID] -> MapBB -> MapBB
120   insertlist [] hmap' = hmap'
121   insertlist (y:ys) hmap' = insertlist ys newhmap
122     where
123     newhmap = if M.member y hmap' then hmap' else M.insert y value hmap'
124     value = parseBasicBlock y insns
125
126   entryi :: [BlockID]
127   entryi = (if off == 0 then [0] else []) ++ -- also consider the entrypoint
128         case entry of
129         Just (TwoTarget t1 t2) -> [t1, t2]
130         Just (OneTarget t) -> [t]
131         Just (Return) -> []
132         Nothing -> []
133
134
135 parseBasicBlock :: Int -> [OffIns] -> BasicBlock
136 parseBasicBlock i insns = BasicBlock insonly endblock
137   where
138   startlist = dropWhile (\((x,_),_) -> x < i) insns
139   (Just ((_,(Just endblock)),_), is) = takeWhilePlusOne validins startlist
140   insonly = snd $ unzip is
141
142   -- also take last (non-matched) element and return it
143   takeWhilePlusOne :: (a -> Bool) -> [a] -> (Maybe a,[a])
144   takeWhilePlusOne _ [] = (Nothing,[])
145   takeWhilePlusOne p (x:xs)
146     | p x       =  let (lastins, list) = takeWhilePlusOne p xs in (lastins, (x:list))
147     | otherwise =  (Just x,[x])
148
149   validins :: ((Int, Maybe BBEnd), Instruction) -> Bool
150   validins ((_,x),_) = case x of Just _ -> False; Nothing -> True
151
152
153 calculateInstructionOffset :: [Instruction] -> [OffIns]
154 calculateInstructionOffset = cio' (0, Nothing)
155   where
156   newoffset :: Instruction -> Int -> Offset
157   newoffset x off = (off + (fromIntegral $ B.length $ encodeInstructions [x]), Nothing)
158
159   addW16Signed :: Int -> Word16 -> Int
160   addW16Signed i w16 = i + (fromIntegral s16)
161     where s16 = (fromIntegral w16) :: Int16
162
163   cio' :: Offset -> [Instruction] -> [OffIns]
164   cio' _ [] = []
165   -- TODO(bernhard): add more instruction with offset (IF_ACMP, JSR, ...)
166   cio' (off,_) (x:xs) = case x of
167       IF _ w16 -> twotargets w16
168       IF_ICMP _ w16 -> twotargets w16
169       GOTO w16 -> onetarget w16
170       IRETURN -> notarget
171       RETURN -> notarget
172       _ -> ((off, Nothing), x):next
173     where
174     notarget = ((off, Just Return), x):next
175     onetarget w16 = ((off, Just $ OneTarget $ (off `addW16Signed` w16)), x):next
176     twotargets w16 = ((off, Just $ TwoTarget (off + 3) (off `addW16Signed` w16)), x):next
177     next = cio' (newoffset x off) xs