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