module Bindings.Bfd.Disasm.I386.Term where import qualified Bindings.Bfd.Disasm.I386.Cell as C import Bindings.Bfd.Disasm.I386.Operand as O import Bindings.Bfd.Disasm.I386.Register as R data Term = Term `Add` Term | Term `BitAnd` Term | Term `BitExclOr` Term | Term `BitOr` Term | Term `BitTest` Term | Term `DivideIntQuotient` Term | Term `DivideIntRemainder` Term | Term `Subtract` Term | SignExtend Term | If Term Term Term -- cond; true; false | Flag Char Term -- source of Assign -- terminals | Opr Int Operand -- Operand: Int is width | OprA Int Operand -- same as Opr, except gets address instead of val (for lea) | Stk Int Int -- offset from rsp, width | Reg Register | Flg Char -- target of Assign | Con Int -- constant; assumed to be 64-bits | Udf -- undefined | Todo String -- FIXME deriving (Show) type Assign = (Term, Term) -- (read, write) {- restrictBits :: Int -> Int -> Term -> Term restrictBits a b (Reg r) = Reg $ R.restrictBits a b r restrictBits _ _ t = error $ "Term.restrictBits: " ++ show t -} defines :: Term -> [C.Cell] defines (Opr w op) = O.defines w op defines (Stk a b ) = [C.Stk b a] defines (Reg r ) = [C.Reg r ] defines (Flg f ) = [C.Flg f ] defines t = error $ "Term.defines: " ++ show t