codegen: handle exceptions of a method
[mate.git] / scratch / Bench.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 module Main where
3
4 import Frontend
5 import Graph
6 import Data.Maybe
7 import Control.Monad.State
8 import Data.Set as S
9 import Control.Monad
10
11 import Mate.BasicBlocks
12
13 import JVM.ClassFile
14 import JVM.Converter
15 import JVM.Assembler
16
17 import Mate.Utilities
18 import qualified Data.ByteString.Lazy as B
19
20 printG' :: Ord k => G k -> [k]
21 printG' g = evalState (foldGM ((: []), (++)) (\node -> let (Just v) = value node in v) [] g) S.empty
22
23 value (Node val _ _) = Just val
24 value (Leaf val    ) = Just val
25 value Nil            = Nothing
26
27
28 main = do con@(Just (ins,cls)) <- getMethodIO "../tests/AbsurdlyHuge.class" "absurdlyHuge"
29           let perform' = do
30                           let method = "absurdlyHuge"
31                           let msig = methodSignature $ (classMethods cls) !! 1
32                           --B.putStrLn (method `B.append` ": " `B.append` (encode msig))
33                           let result = testCFG $ lookupMethod method cls
34                           printMapBB result
35           let perform = do
36                   let tagged = getInstructions ins
37                   let backRefs = splitBlocksBackRef tagged
38                   let splitted = splitBlocks backRefs tagged
39                   let transitions = getTransitions splitted
40                   let nodes       = getNodes splitted
41                   --print "nodes:"
42                   --print nodes
43                   --print "transitions"
44                   --print transitions
45                   let (Just finalCyclicStructure) = indirectCFGToG splitted
46                   print "Final result"
47                   print $ printG' finalCyclicStructure
48           forM_ [0..100] (\x -> do perform)
49
50