{-# LANGUAGE DerivingStrategies #-}
module Zydis.Operand
( Operand(..)
)
where
import Data.Int
import Data.Word
import Foreign.Storable
import qualified Foreign.Storable.Record as Store
import Zydis.ElementType
import Zydis.OperandEncoding
import Zydis.OperandMemoryType
import Zydis.OperandType
import Zydis.OperandVisibility
import Zydis.Register
data OperandImmediate =
OperandImmediate
{ OperandImmediate -> Word8
operandImmediateIsSigned :: !Word8
, OperandImmediate -> Word8
operandImmediateIsRelative :: !Word8
, OperandImmediate -> Word64
operandImmediateValue :: {-# UNPACK #-}!Word64
}
deriving stock (Int -> OperandImmediate -> ShowS
[OperandImmediate] -> ShowS
OperandImmediate -> String
(Int -> OperandImmediate -> ShowS)
-> (OperandImmediate -> String)
-> ([OperandImmediate] -> ShowS)
-> Show OperandImmediate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperandImmediate] -> ShowS
$cshowList :: [OperandImmediate] -> ShowS
show :: OperandImmediate -> String
$cshow :: OperandImmediate -> String
showsPrec :: Int -> OperandImmediate -> ShowS
$cshowsPrec :: Int -> OperandImmediate -> ShowS
Show, OperandImmediate -> OperandImmediate -> Bool
(OperandImmediate -> OperandImmediate -> Bool)
-> (OperandImmediate -> OperandImmediate -> Bool)
-> Eq OperandImmediate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperandImmediate -> OperandImmediate -> Bool
$c/= :: OperandImmediate -> OperandImmediate -> Bool
== :: OperandImmediate -> OperandImmediate -> Bool
$c== :: OperandImmediate -> OperandImmediate -> Bool
Eq)
decoderOperandImmediateStore :: Store.Dictionary OperandImmediate
decoderOperandImmediateStore :: Dictionary OperandImmediate
decoderOperandImmediateStore =
Access OperandImmediate OperandImmediate
-> Dictionary OperandImmediate
forall r. Access r r -> Dictionary r
Store.run
(Access OperandImmediate OperandImmediate
-> Dictionary OperandImmediate)
-> Access OperandImmediate OperandImmediate
-> Dictionary OperandImmediate
forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> Word64 -> OperandImmediate
OperandImmediate
(Word8 -> Word8 -> Word64 -> OperandImmediate)
-> Access OperandImmediate Word8
-> Access OperandImmediate (Word8 -> Word64 -> OperandImmediate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (OperandImmediate -> Word8) -> Access OperandImmediate Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandImmediate -> Word8
operandImmediateIsSigned
Access OperandImmediate (Word8 -> Word64 -> OperandImmediate)
-> Access OperandImmediate Word8
-> Access OperandImmediate (Word64 -> OperandImmediate)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandImmediate -> Word8) -> Access OperandImmediate Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandImmediate -> Word8
operandImmediateIsRelative
Access OperandImmediate (Word64 -> OperandImmediate)
-> Access OperandImmediate Word64
-> Access OperandImmediate OperandImmediate
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandImmediate -> Word64) -> Access OperandImmediate Word64
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandImmediate -> Word64
operandImmediateValue
instance Storable OperandImmediate where
alignment :: OperandImmediate -> Int
alignment = Dictionary OperandImmediate -> OperandImmediate -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary OperandImmediate
decoderOperandImmediateStore
sizeOf :: OperandImmediate -> Int
sizeOf = Dictionary OperandImmediate -> OperandImmediate -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary OperandImmediate
decoderOperandImmediateStore
peek :: Ptr OperandImmediate -> IO OperandImmediate
peek = Dictionary OperandImmediate
-> Ptr OperandImmediate -> IO OperandImmediate
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary OperandImmediate
decoderOperandImmediateStore
poke :: Ptr OperandImmediate -> OperandImmediate -> IO ()
poke = Dictionary OperandImmediate
-> Ptr OperandImmediate -> OperandImmediate -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary OperandImmediate
decoderOperandImmediateStore
data OperandPointer =
OperandPointer
{ OperandPointer -> Word16
operandPointerSegment :: {-# UNPACK #-}!Word16
, OperandPointer -> Word32
operandPointerOffset :: {-# UNPACK #-}!Word32
}
deriving stock (Int -> OperandPointer -> ShowS
[OperandPointer] -> ShowS
OperandPointer -> String
(Int -> OperandPointer -> ShowS)
-> (OperandPointer -> String)
-> ([OperandPointer] -> ShowS)
-> Show OperandPointer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperandPointer] -> ShowS
$cshowList :: [OperandPointer] -> ShowS
show :: OperandPointer -> String
$cshow :: OperandPointer -> String
showsPrec :: Int -> OperandPointer -> ShowS
$cshowsPrec :: Int -> OperandPointer -> ShowS
Show, OperandPointer -> OperandPointer -> Bool
(OperandPointer -> OperandPointer -> Bool)
-> (OperandPointer -> OperandPointer -> Bool) -> Eq OperandPointer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperandPointer -> OperandPointer -> Bool
$c/= :: OperandPointer -> OperandPointer -> Bool
== :: OperandPointer -> OperandPointer -> Bool
$c== :: OperandPointer -> OperandPointer -> Bool
Eq)
decoderOperandPointerStore :: Store.Dictionary OperandPointer
decoderOperandPointerStore :: Dictionary OperandPointer
decoderOperandPointerStore =
Access OperandPointer OperandPointer -> Dictionary OperandPointer
forall r. Access r r -> Dictionary r
Store.run
(Access OperandPointer OperandPointer -> Dictionary OperandPointer)
-> Access OperandPointer OperandPointer
-> Dictionary OperandPointer
forall a b. (a -> b) -> a -> b
$ Word16 -> Word32 -> OperandPointer
OperandPointer
(Word16 -> Word32 -> OperandPointer)
-> Access OperandPointer Word16
-> Access OperandPointer (Word32 -> OperandPointer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (OperandPointer -> Word16) -> Access OperandPointer Word16
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandPointer -> Word16
operandPointerSegment
Access OperandPointer (Word32 -> OperandPointer)
-> Access OperandPointer Word32
-> Access OperandPointer OperandPointer
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandPointer -> Word32) -> Access OperandPointer Word32
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandPointer -> Word32
operandPointerOffset
instance Storable OperandPointer where
alignment :: OperandPointer -> Int
alignment = Dictionary OperandPointer -> OperandPointer -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary OperandPointer
decoderOperandPointerStore
sizeOf :: OperandPointer -> Int
sizeOf = Dictionary OperandPointer -> OperandPointer -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary OperandPointer
decoderOperandPointerStore
peek :: Ptr OperandPointer -> IO OperandPointer
peek = Dictionary OperandPointer
-> Ptr OperandPointer -> IO OperandPointer
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary OperandPointer
decoderOperandPointerStore
poke :: Ptr OperandPointer -> OperandPointer -> IO ()
poke = Dictionary OperandPointer
-> Ptr OperandPointer -> OperandPointer -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary OperandPointer
decoderOperandPointerStore
data OperandMemoryDisplacement =
OperandMemoryDisplacement
{ OperandMemoryDisplacement -> Word8
operandMemoryDisplacementHasDisplacement :: !Word8
, OperandMemoryDisplacement -> Int64
operandMemoryDisplacementValue :: {-# UNPACK #-}!Int64
}
deriving stock (Int -> OperandMemoryDisplacement -> ShowS
[OperandMemoryDisplacement] -> ShowS
OperandMemoryDisplacement -> String
(Int -> OperandMemoryDisplacement -> ShowS)
-> (OperandMemoryDisplacement -> String)
-> ([OperandMemoryDisplacement] -> ShowS)
-> Show OperandMemoryDisplacement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperandMemoryDisplacement] -> ShowS
$cshowList :: [OperandMemoryDisplacement] -> ShowS
show :: OperandMemoryDisplacement -> String
$cshow :: OperandMemoryDisplacement -> String
showsPrec :: Int -> OperandMemoryDisplacement -> ShowS
$cshowsPrec :: Int -> OperandMemoryDisplacement -> ShowS
Show, OperandMemoryDisplacement -> OperandMemoryDisplacement -> Bool
(OperandMemoryDisplacement -> OperandMemoryDisplacement -> Bool)
-> (OperandMemoryDisplacement -> OperandMemoryDisplacement -> Bool)
-> Eq OperandMemoryDisplacement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperandMemoryDisplacement -> OperandMemoryDisplacement -> Bool
$c/= :: OperandMemoryDisplacement -> OperandMemoryDisplacement -> Bool
== :: OperandMemoryDisplacement -> OperandMemoryDisplacement -> Bool
$c== :: OperandMemoryDisplacement -> OperandMemoryDisplacement -> Bool
Eq)
decoderOperandMemoryDisplacementStore
:: Store.Dictionary OperandMemoryDisplacement
decoderOperandMemoryDisplacementStore :: Dictionary OperandMemoryDisplacement
decoderOperandMemoryDisplacementStore =
Access OperandMemoryDisplacement OperandMemoryDisplacement
-> Dictionary OperandMemoryDisplacement
forall r. Access r r -> Dictionary r
Store.run
(Access OperandMemoryDisplacement OperandMemoryDisplacement
-> Dictionary OperandMemoryDisplacement)
-> Access OperandMemoryDisplacement OperandMemoryDisplacement
-> Dictionary OperandMemoryDisplacement
forall a b. (a -> b) -> a -> b
$ Word8 -> Int64 -> OperandMemoryDisplacement
OperandMemoryDisplacement
(Word8 -> Int64 -> OperandMemoryDisplacement)
-> Access OperandMemoryDisplacement Word8
-> Access
OperandMemoryDisplacement (Int64 -> OperandMemoryDisplacement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (OperandMemoryDisplacement -> Word8)
-> Access OperandMemoryDisplacement Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemoryDisplacement -> Word8
operandMemoryDisplacementHasDisplacement
Access
OperandMemoryDisplacement (Int64 -> OperandMemoryDisplacement)
-> Access OperandMemoryDisplacement Int64
-> Access OperandMemoryDisplacement OperandMemoryDisplacement
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandMemoryDisplacement -> Int64)
-> Access OperandMemoryDisplacement Int64
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemoryDisplacement -> Int64
operandMemoryDisplacementValue
instance Storable OperandMemoryDisplacement where
alignment :: OperandMemoryDisplacement -> Int
alignment = Dictionary OperandMemoryDisplacement
-> OperandMemoryDisplacement -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary OperandMemoryDisplacement
decoderOperandMemoryDisplacementStore
sizeOf :: OperandMemoryDisplacement -> Int
sizeOf = Dictionary OperandMemoryDisplacement
-> OperandMemoryDisplacement -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary OperandMemoryDisplacement
decoderOperandMemoryDisplacementStore
peek :: Ptr OperandMemoryDisplacement -> IO OperandMemoryDisplacement
peek = Dictionary OperandMemoryDisplacement
-> Ptr OperandMemoryDisplacement -> IO OperandMemoryDisplacement
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary OperandMemoryDisplacement
decoderOperandMemoryDisplacementStore
poke :: Ptr OperandMemoryDisplacement -> OperandMemoryDisplacement -> IO ()
poke = Dictionary OperandMemoryDisplacement
-> Ptr OperandMemoryDisplacement
-> OperandMemoryDisplacement
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary OperandMemoryDisplacement
decoderOperandMemoryDisplacementStore
data OperandMemory =
OperandMemory
{ OperandMemory -> OperandMemoryType
operandMemoryType :: !OperandMemoryType
, OperandMemory -> Register
operandMemorySegment :: !Register
, OperandMemory -> Register
operandMemoryBase :: !Register
, OperandMemory -> Register
operandMemoryIndex :: !Register
, OperandMemory -> Word8
operandMemoryScale :: {-# UNPACK #-}!Word8
, OperandMemory -> OperandMemoryDisplacement
operandMemoryDisplacement :: !OperandMemoryDisplacement
}
deriving stock (Int -> OperandMemory -> ShowS
[OperandMemory] -> ShowS
OperandMemory -> String
(Int -> OperandMemory -> ShowS)
-> (OperandMemory -> String)
-> ([OperandMemory] -> ShowS)
-> Show OperandMemory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperandMemory] -> ShowS
$cshowList :: [OperandMemory] -> ShowS
show :: OperandMemory -> String
$cshow :: OperandMemory -> String
showsPrec :: Int -> OperandMemory -> ShowS
$cshowsPrec :: Int -> OperandMemory -> ShowS
Show, OperandMemory -> OperandMemory -> Bool
(OperandMemory -> OperandMemory -> Bool)
-> (OperandMemory -> OperandMemory -> Bool) -> Eq OperandMemory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperandMemory -> OperandMemory -> Bool
$c/= :: OperandMemory -> OperandMemory -> Bool
== :: OperandMemory -> OperandMemory -> Bool
$c== :: OperandMemory -> OperandMemory -> Bool
Eq)
decoderOperandMemoryStore :: Store.Dictionary OperandMemory
decoderOperandMemoryStore :: Dictionary OperandMemory
decoderOperandMemoryStore =
Access OperandMemory OperandMemory -> Dictionary OperandMemory
forall r. Access r r -> Dictionary r
Store.run
(Access OperandMemory OperandMemory -> Dictionary OperandMemory)
-> Access OperandMemory OperandMemory -> Dictionary OperandMemory
forall a b. (a -> b) -> a -> b
$ OperandMemoryType
-> Register
-> Register
-> Register
-> Word8
-> OperandMemoryDisplacement
-> OperandMemory
OperandMemory
(OperandMemoryType
-> Register
-> Register
-> Register
-> Word8
-> OperandMemoryDisplacement
-> OperandMemory)
-> Access OperandMemory OperandMemoryType
-> Access
OperandMemory
(Register
-> Register
-> Register
-> Word8
-> OperandMemoryDisplacement
-> OperandMemory)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (OperandMemory -> OperandMemoryType)
-> Access OperandMemory OperandMemoryType
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemory -> OperandMemoryType
operandMemoryType
Access
OperandMemory
(Register
-> Register
-> Register
-> Word8
-> OperandMemoryDisplacement
-> OperandMemory)
-> Access OperandMemory Register
-> Access
OperandMemory
(Register
-> Register -> Word8 -> OperandMemoryDisplacement -> OperandMemory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandMemory -> Register) -> Access OperandMemory Register
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemory -> Register
operandMemorySegment
Access
OperandMemory
(Register
-> Register -> Word8 -> OperandMemoryDisplacement -> OperandMemory)
-> Access OperandMemory Register
-> Access
OperandMemory
(Register -> Word8 -> OperandMemoryDisplacement -> OperandMemory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandMemory -> Register) -> Access OperandMemory Register
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemory -> Register
operandMemoryBase
Access
OperandMemory
(Register -> Word8 -> OperandMemoryDisplacement -> OperandMemory)
-> Access OperandMemory Register
-> Access
OperandMemory (Word8 -> OperandMemoryDisplacement -> OperandMemory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandMemory -> Register) -> Access OperandMemory Register
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemory -> Register
operandMemoryIndex
Access
OperandMemory (Word8 -> OperandMemoryDisplacement -> OperandMemory)
-> Access OperandMemory Word8
-> Access
OperandMemory (OperandMemoryDisplacement -> OperandMemory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandMemory -> Word8) -> Access OperandMemory Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemory -> Word8
operandMemoryScale
Access OperandMemory (OperandMemoryDisplacement -> OperandMemory)
-> Access OperandMemory OperandMemoryDisplacement
-> Access OperandMemory OperandMemory
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (OperandMemory -> OperandMemoryDisplacement)
-> Access OperandMemory OperandMemoryDisplacement
forall a r. Storable a => (r -> a) -> Access r a
Store.element OperandMemory -> OperandMemoryDisplacement
operandMemoryDisplacement
instance Storable OperandMemory where
alignment :: OperandMemory -> Int
alignment = Dictionary OperandMemory -> OperandMemory -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary OperandMemory
decoderOperandMemoryStore
sizeOf :: OperandMemory -> Int
sizeOf = Dictionary OperandMemory -> OperandMemory -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary OperandMemory
decoderOperandMemoryStore
peek :: Ptr OperandMemory -> IO OperandMemory
peek = Dictionary OperandMemory -> Ptr OperandMemory -> IO OperandMemory
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary OperandMemory
decoderOperandMemoryStore
poke :: Ptr OperandMemory -> OperandMemory -> IO ()
poke = Dictionary OperandMemory
-> Ptr OperandMemory -> OperandMemory -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary OperandMemory
decoderOperandMemoryStore
data Operand =
Operand
{ Operand -> Word8
operandId :: {-# UNPACK #-}!Word8
, Operand -> OperandType
operandType :: !OperandType
, Operand -> OperandVisibility
operandVisibility :: !OperandVisibility
, Operand -> Word8
operandActions :: {-# UNPACK #-}!Word8
, Operand -> OperandEncoding
operandEncoding :: !OperandEncoding
, Operand -> Word16
operandSize :: {-# UNPACK #-}!Word16
, Operand -> ElementType
operandElementType :: !ElementType
, Operand -> Word16
operandElementSize :: {-# UNPACK #-}!Word16
, Operand -> Word16
operandElementCount :: {-# UNPACK #-}!Word16
, Operand -> Register
operandRegister :: !Register
, Operand -> OperandMemory
operandMemory :: !OperandMemory
, Operand -> OperandPointer
operandPointer :: !OperandPointer
, Operand -> OperandImmediate
operandImmediate :: !OperandImmediate
}
deriving stock (Int -> Operand -> ShowS
[Operand] -> ShowS
Operand -> String
(Int -> Operand -> ShowS)
-> (Operand -> String) -> ([Operand] -> ShowS) -> Show Operand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Operand] -> ShowS
$cshowList :: [Operand] -> ShowS
show :: Operand -> String
$cshow :: Operand -> String
showsPrec :: Int -> Operand -> ShowS
$cshowsPrec :: Int -> Operand -> ShowS
Show, Operand -> Operand -> Bool
(Operand -> Operand -> Bool)
-> (Operand -> Operand -> Bool) -> Eq Operand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Operand -> Operand -> Bool
$c/= :: Operand -> Operand -> Bool
== :: Operand -> Operand -> Bool
$c== :: Operand -> Operand -> Bool
Eq)
decoderOperandStore :: Store.Dictionary Operand
decoderOperandStore :: Dictionary Operand
decoderOperandStore =
Access Operand Operand -> Dictionary Operand
forall r. Access r r -> Dictionary r
Store.run
(Access Operand Operand -> Dictionary Operand)
-> Access Operand Operand -> Dictionary Operand
forall a b. (a -> b) -> a -> b
$ Word8
-> OperandType
-> OperandVisibility
-> Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand
Operand
(Word8
-> OperandType
-> OperandVisibility
-> Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand Word8
-> Access
Operand
(OperandType
-> OperandVisibility
-> Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Operand -> Word8) -> Access Operand Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> Word8
operandId
Access
Operand
(OperandType
-> OperandVisibility
-> Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand OperandType
-> Access
Operand
(OperandVisibility
-> Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> OperandType) -> Access Operand OperandType
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> OperandType
operandType
Access
Operand
(OperandVisibility
-> Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand OperandVisibility
-> Access
Operand
(Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> OperandVisibility) -> Access Operand OperandVisibility
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> OperandVisibility
operandVisibility
Access
Operand
(Word8
-> OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand Word8
-> Access
Operand
(OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> Word8) -> Access Operand Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> Word8
operandActions
Access
Operand
(OperandEncoding
-> Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand OperandEncoding
-> Access
Operand
(Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> OperandEncoding) -> Access Operand OperandEncoding
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> OperandEncoding
operandEncoding
Access
Operand
(Word16
-> ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand Word16
-> Access
Operand
(ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> Word16) -> Access Operand Word16
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> Word16
operandSize
Access
Operand
(ElementType
-> Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand ElementType
-> Access
Operand
(Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> ElementType) -> Access Operand ElementType
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> ElementType
operandElementType
Access
Operand
(Word16
-> Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand Word16
-> Access
Operand
(Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> Word16) -> Access Operand Word16
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> Word16
operandElementSize
Access
Operand
(Word16
-> Register
-> OperandMemory
-> OperandPointer
-> OperandImmediate
-> Operand)
-> Access Operand Word16
-> Access
Operand
(Register
-> OperandMemory -> OperandPointer -> OperandImmediate -> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> Word16) -> Access Operand Word16
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> Word16
operandElementCount
Access
Operand
(Register
-> OperandMemory -> OperandPointer -> OperandImmediate -> Operand)
-> Access Operand Register
-> Access
Operand
(OperandMemory -> OperandPointer -> OperandImmediate -> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> Register) -> Access Operand Register
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> Register
operandRegister
Access
Operand
(OperandMemory -> OperandPointer -> OperandImmediate -> Operand)
-> Access Operand OperandMemory
-> Access Operand (OperandPointer -> OperandImmediate -> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> OperandMemory) -> Access Operand OperandMemory
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> OperandMemory
operandMemory
Access Operand (OperandPointer -> OperandImmediate -> Operand)
-> Access Operand OperandPointer
-> Access Operand (OperandImmediate -> Operand)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> OperandPointer) -> Access Operand OperandPointer
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> OperandPointer
operandPointer
Access Operand (OperandImmediate -> Operand)
-> Access Operand OperandImmediate -> Access Operand Operand
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Operand -> OperandImmediate) -> Access Operand OperandImmediate
forall a r. Storable a => (r -> a) -> Access r a
Store.element Operand -> OperandImmediate
operandImmediate
instance Storable Operand where
alignment :: Operand -> Int
alignment = Dictionary Operand -> Operand -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary Operand
decoderOperandStore
sizeOf :: Operand -> Int
sizeOf = Dictionary Operand -> Operand -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary Operand
decoderOperandStore
peek :: Ptr Operand -> IO Operand
peek = Dictionary Operand -> Ptr Operand -> IO Operand
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary Operand
decoderOperandStore
poke :: Ptr Operand -> Operand -> IO ()
poke = Dictionary Operand -> Ptr Operand -> Operand -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary Operand
decoderOperandStore