basicblock: get jump offsets from instructions
authorBernhard Urban <lewurm@gmail.com>
Mon, 2 Apr 2012 19:40:00 +0000 (21:40 +0200)
committerBernhard Urban <lewurm@gmail.com>
Mon, 2 Apr 2012 19:40:00 +0000 (21:40 +0200)
Mate/BasicBlocks.hs

index 68d8cb9a8f44c0c83528b83ade08728cba24a129..a15c5e98f4a900f2f408b3edf0a956f251b42abd 100644 (file)
@@ -2,6 +2,7 @@
 module Mate.BasicBlocks where
 
 import Data.Binary
+import Data.Int
 import System.Environment
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
@@ -64,11 +65,18 @@ buildCFG xs = map (\(x,y) -> show x ++ ", " ++ show y) xs'
   where
   xs' = calculateInstructionOffset xs
 
-type Offset = Int
+type Offset = (Int, Maybe Int16) -- (offset in bytecode, offset to jump target)
+
 calculateInstructionOffset :: [Instruction] -> [(Offset, Instruction)]
-calculateInstructionOffset = cio' 0
+calculateInstructionOffset = cio' (0, Nothing)
   where
+  newoffset :: Instruction -> Int -> Offset
+  newoffset x off = (off + (fromIntegral $ B.length $ encodeInstructions [x]), Nothing)
   cio' :: Offset -> [Instruction] -> [(Offset, Instruction)]
   cio' _ [] = []
-  cio' off (x:xs) = (off,x):(cio' newoffset xs)
-    where newoffset = off + (fromIntegral $ B.length $ encodeInstructions [x])
+  -- TODO(bernhard): add more instruction with offset (IF_ACMP, JSR, ...)
+  -- TODO(bernhard): beautiful code please (BCP)
+  cio' (off,_) (x@(IF _ w16):xs) = ((off, Just $ fromIntegral w16), x):(cio' (newoffset x off) xs)
+  cio' (off,_) (x@(IF_ICMP _ w16):xs) = ((off, Just $ fromIntegral w16), x):(cio' (newoffset x off) xs)
+  cio' (off,_) (x@(GOTO w16):xs) = ((off, Just $ fromIntegral w16), x):(cio' (newoffset x off) xs)
+  cio' (off,_) (x:xs) = ((off, Nothing), x):(cio' (newoffset x off) xs)