{-# LANGUAGE DeriveGeneric #-}
module Data.Indirection where
import Base
import Data.JumpTarget
import Data.X86.Instruction
import qualified Data.IntMap as IM
import qualified Data.IntSet as IS
import qualified Data.Set as S
import Data.Word
import qualified Data.Serialize as Cereal hiding (get,put)
import Control.DeepSeq
import GHC.Generics (Generic)
data JumpTable = JumpTable {
JumpTable -> Operand
jtbl_index :: Operand,
JumpTable -> Int
jtbl_bound :: Int,
JumpTable -> Operand
jtbl_target :: Operand,
JumpTable -> IntMap Word64
jtbl_table :: IM.IntMap Word64
}
deriving ((forall x. JumpTable -> Rep JumpTable x)
-> (forall x. Rep JumpTable x -> JumpTable) -> Generic JumpTable
forall x. Rep JumpTable x -> JumpTable
forall x. JumpTable -> Rep JumpTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. JumpTable -> Rep JumpTable x
from :: forall x. JumpTable -> Rep JumpTable x
$cto :: forall x. Rep JumpTable x -> JumpTable
to :: forall x. Rep JumpTable x -> JumpTable
Generic, JumpTable -> JumpTable -> Bool
(JumpTable -> JumpTable -> Bool)
-> (JumpTable -> JumpTable -> Bool) -> Eq JumpTable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JumpTable -> JumpTable -> Bool
== :: JumpTable -> JumpTable -> Bool
$c/= :: JumpTable -> JumpTable -> Bool
/= :: JumpTable -> JumpTable -> Bool
Eq,Eq JumpTable
Eq JumpTable =>
(JumpTable -> JumpTable -> Ordering)
-> (JumpTable -> JumpTable -> Bool)
-> (JumpTable -> JumpTable -> Bool)
-> (JumpTable -> JumpTable -> Bool)
-> (JumpTable -> JumpTable -> Bool)
-> (JumpTable -> JumpTable -> JumpTable)
-> (JumpTable -> JumpTable -> JumpTable)
-> Ord JumpTable
JumpTable -> JumpTable -> Bool
JumpTable -> JumpTable -> Ordering
JumpTable -> JumpTable -> JumpTable
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: JumpTable -> JumpTable -> Ordering
compare :: JumpTable -> JumpTable -> Ordering
$c< :: JumpTable -> JumpTable -> Bool
< :: JumpTable -> JumpTable -> Bool
$c<= :: JumpTable -> JumpTable -> Bool
<= :: JumpTable -> JumpTable -> Bool
$c> :: JumpTable -> JumpTable -> Bool
> :: JumpTable -> JumpTable -> Bool
$c>= :: JumpTable -> JumpTable -> Bool
>= :: JumpTable -> JumpTable -> Bool
$cmax :: JumpTable -> JumpTable -> JumpTable
max :: JumpTable -> JumpTable -> JumpTable
$cmin :: JumpTable -> JumpTable -> JumpTable
min :: JumpTable -> JumpTable -> JumpTable
Ord)
data Indirection = Indirection_JumpTable JumpTable | Indirection_Resolved ResolvedJumpTarget | Indirection_Unresolved
deriving ((forall x. Indirection -> Rep Indirection x)
-> (forall x. Rep Indirection x -> Indirection)
-> Generic Indirection
forall x. Rep Indirection x -> Indirection
forall x. Indirection -> Rep Indirection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Indirection -> Rep Indirection x
from :: forall x. Indirection -> Rep Indirection x
$cto :: forall x. Rep Indirection x -> Indirection
to :: forall x. Rep Indirection x -> Indirection
Generic, Indirection -> Indirection -> Bool
(Indirection -> Indirection -> Bool)
-> (Indirection -> Indirection -> Bool) -> Eq Indirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Indirection -> Indirection -> Bool
== :: Indirection -> Indirection -> Bool
$c/= :: Indirection -> Indirection -> Bool
/= :: Indirection -> Indirection -> Bool
Eq,Eq Indirection
Eq Indirection =>
(Indirection -> Indirection -> Ordering)
-> (Indirection -> Indirection -> Bool)
-> (Indirection -> Indirection -> Bool)
-> (Indirection -> Indirection -> Bool)
-> (Indirection -> Indirection -> Bool)
-> (Indirection -> Indirection -> Indirection)
-> (Indirection -> Indirection -> Indirection)
-> Ord Indirection
Indirection -> Indirection -> Bool
Indirection -> Indirection -> Ordering
Indirection -> Indirection -> Indirection
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Indirection -> Indirection -> Ordering
compare :: Indirection -> Indirection -> Ordering
$c< :: Indirection -> Indirection -> Bool
< :: Indirection -> Indirection -> Bool
$c<= :: Indirection -> Indirection -> Bool
<= :: Indirection -> Indirection -> Bool
$c> :: Indirection -> Indirection -> Bool
> :: Indirection -> Indirection -> Bool
$c>= :: Indirection -> Indirection -> Bool
>= :: Indirection -> Indirection -> Bool
$cmax :: Indirection -> Indirection -> Indirection
max :: Indirection -> Indirection -> Indirection
$cmin :: Indirection -> Indirection -> Indirection
min :: Indirection -> Indirection -> Indirection
Ord)
type Indirections = S.Set Indirection
instance Show JumpTable where
show :: JumpTable -> String
show (JumpTable Operand
idx Int
bnd Operand
trgt IntMap Word64
tbl) = String
"JumpTable: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Operand -> String
forall a. Show a => a -> String
show Operand
idx String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" < " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
bnd String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" --> " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Operand -> String
forall a. Show a => a -> String
show Operand
trgt String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" in " String -> ShowS
forall a. [a] -> [a] -> [a]
++ IntSet -> String
showHex_set ([Int] -> IntSet
IS.fromList ([Int] -> IntSet) -> [Int] -> IntSet
forall a b. (a -> b) -> a -> b
$ (Word64 -> Int) -> [Word64] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Word64] -> [Int]) -> [Word64] -> [Int]
forall a b. (a -> b) -> a -> b
$ IntMap Word64 -> [Word64]
forall a. IntMap a -> [a]
IM.elems IntMap Word64
tbl)
instance Show Indirection where
show :: Indirection -> String
show (Indirection_JumpTable JumpTable
tbl) = JumpTable -> String
forall a. Show a => a -> String
show JumpTable
tbl
show (Indirection_Resolved ResolvedJumpTarget
trgt) = ResolvedJumpTarget -> String
forall a. Show a => a -> String
show ResolvedJumpTarget
trgt
show (Indirection
Indirection_Unresolved) = String
"Unresolved"
instance Cereal.Serialize JumpTable
instance Cereal.Serialize Indirection
instance NFData JumpTable
instance NFData Indirection