{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
module Zydis.Types
( MachineMode(..)
, AddressWidth(..)
, Decoder(..)
, DecodedInstruction(..)
, DecodedInstructionRawImmediate(..)
, DecodedInstructionRawDisp(..)
, DecodedInstructionRawSib(..)
, DecodedInstructionModRm(..)
, DecodedInstructionRawMvex(..)
, DecodedInstructionRawEvex(..)
, DecodedInstructionRawVex(..)
, DecodedInstructionRawXop(..)
, DecodedInstructionRawRex(..)
, DecodedInstructionRawPrefix(..)
, DecodedInstructionRaw(..)
, DecodedInstructionMeta(..)
, DecodedInstructionAvxBroadcast(..)
, DecodedInstructionAvxMask(..)
, DecodedInstructionAvx(..)
, module Z
)
where
import Data.Int
import Data.Word
import Foreign.Storable
import qualified Foreign.Storable.Record as Store
import GHC.TypeLits
import Zydis.AddressWidth as Z
import Zydis.BranchType as Z
import Zydis.BroadcastMode as Z
import Zydis.Constants as Z
import Zydis.ConversionMode as Z
import Zydis.CPUFlagAction as Z
import Zydis.ExceptionClass as Z
import Zydis.InstructionCategory as Z
import Zydis.InstructionEncoding as Z
import Zydis.ISAExt as Z
import Zydis.ISASet as Z
import Zydis.MachineMode as Z
import Zydis.MaskMode as Z
import Zydis.Mnemonic as Z
import Zydis.OpcodeMap as Z
import Zydis.Operand as Z
import Zydis.PrefixType as Z
import Zydis.Register as Z
import Zydis.RoundingMode as Z
import Zydis.SwizzleMode as Z
import Zydis.Util
data DecodedInstructionRawImmediate =
DecodedInstructionRawImmediate
{ DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateIsSigned :: {-# UNPACK #-}!Word8
, DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateIsRelative :: {-# UNPACK #-}!Word8
, DecodedInstructionRawImmediate -> Word64
decodedInstructionRawImmediateValue :: {-# UNPACK #-}!Word64
, DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateSize :: {-# UNPACK #-}!Word8
, DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawImmediate -> ShowS
[DecodedInstructionRawImmediate] -> ShowS
DecodedInstructionRawImmediate -> String
(Int -> DecodedInstructionRawImmediate -> ShowS)
-> (DecodedInstructionRawImmediate -> String)
-> ([DecodedInstructionRawImmediate] -> ShowS)
-> Show DecodedInstructionRawImmediate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawImmediate] -> ShowS
$cshowList :: [DecodedInstructionRawImmediate] -> ShowS
show :: DecodedInstructionRawImmediate -> String
$cshow :: DecodedInstructionRawImmediate -> String
showsPrec :: Int -> DecodedInstructionRawImmediate -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawImmediate -> ShowS
Show, DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Bool
(DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Bool)
-> (DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Bool)
-> Eq DecodedInstructionRawImmediate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Bool
$c/= :: DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Bool
== :: DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Bool
$c== :: DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Bool
Eq)
decoderInstructionRawImmediateStore
:: Store.Dictionary DecodedInstructionRawImmediate
decoderInstructionRawImmediateStore :: Dictionary DecodedInstructionRawImmediate
decoderInstructionRawImmediateStore =
Access
DecodedInstructionRawImmediate DecodedInstructionRawImmediate
-> Dictionary DecodedInstructionRawImmediate
forall r. Access r r -> Dictionary r
Store.run
(Access
DecodedInstructionRawImmediate DecodedInstructionRawImmediate
-> Dictionary DecodedInstructionRawImmediate)
-> Access
DecodedInstructionRawImmediate DecodedInstructionRawImmediate
-> Dictionary DecodedInstructionRawImmediate
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8
-> Word64
-> Word8
-> Word8
-> DecodedInstructionRawImmediate
DecodedInstructionRawImmediate
(Word8
-> Word8
-> Word64
-> Word8
-> Word8
-> DecodedInstructionRawImmediate)
-> Access DecodedInstructionRawImmediate Word8
-> Access
DecodedInstructionRawImmediate
(Word8
-> Word64 -> Word8 -> Word8 -> DecodedInstructionRawImmediate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawImmediate -> Word8)
-> Access DecodedInstructionRawImmediate Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateIsSigned
Access
DecodedInstructionRawImmediate
(Word8
-> Word64 -> Word8 -> Word8 -> DecodedInstructionRawImmediate)
-> Access DecodedInstructionRawImmediate Word8
-> Access
DecodedInstructionRawImmediate
(Word64 -> Word8 -> Word8 -> DecodedInstructionRawImmediate)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawImmediate -> Word8)
-> Access DecodedInstructionRawImmediate Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateIsRelative
Access
DecodedInstructionRawImmediate
(Word64 -> Word8 -> Word8 -> DecodedInstructionRawImmediate)
-> Access DecodedInstructionRawImmediate Word64
-> Access
DecodedInstructionRawImmediate
(Word8 -> Word8 -> DecodedInstructionRawImmediate)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawImmediate -> Word64)
-> Access DecodedInstructionRawImmediate Word64
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawImmediate -> Word64
decodedInstructionRawImmediateValue
Access
DecodedInstructionRawImmediate
(Word8 -> Word8 -> DecodedInstructionRawImmediate)
-> Access DecodedInstructionRawImmediate Word8
-> Access
DecodedInstructionRawImmediate
(Word8 -> DecodedInstructionRawImmediate)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawImmediate -> Word8)
-> Access DecodedInstructionRawImmediate Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateSize
Access
DecodedInstructionRawImmediate
(Word8 -> DecodedInstructionRawImmediate)
-> Access DecodedInstructionRawImmediate Word8
-> Access
DecodedInstructionRawImmediate DecodedInstructionRawImmediate
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawImmediate -> Word8)
-> Access DecodedInstructionRawImmediate Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawImmediate -> Word8
decodedInstructionRawImmediateOffset
instance Storable DecodedInstructionRawImmediate where
alignment :: DecodedInstructionRawImmediate -> Int
alignment = Dictionary DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawImmediate
decoderInstructionRawImmediateStore
sizeOf :: DecodedInstructionRawImmediate -> Int
sizeOf = Dictionary DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawImmediate
decoderInstructionRawImmediateStore
peek :: Ptr DecodedInstructionRawImmediate
-> IO DecodedInstructionRawImmediate
peek = Dictionary DecodedInstructionRawImmediate
-> Ptr DecodedInstructionRawImmediate
-> IO DecodedInstructionRawImmediate
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawImmediate
decoderInstructionRawImmediateStore
poke :: Ptr DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate -> IO ()
poke = Dictionary DecodedInstructionRawImmediate
-> Ptr DecodedInstructionRawImmediate
-> DecodedInstructionRawImmediate
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawImmediate
decoderInstructionRawImmediateStore
data DecodedInstructionRawDisp =
DecodedInstructionRawDisp
{ DecodedInstructionRawDisp -> Int64
decodedInstructionRawDispValue :: {-# UNPACK #-}!Int64
, DecodedInstructionRawDisp -> Word8
decodedInstructionRawDispSize :: {-# UNPACK #-}!Word8
, DecodedInstructionRawDisp -> Word8
decodedInstructionRawDispOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawDisp -> ShowS
[DecodedInstructionRawDisp] -> ShowS
DecodedInstructionRawDisp -> String
(Int -> DecodedInstructionRawDisp -> ShowS)
-> (DecodedInstructionRawDisp -> String)
-> ([DecodedInstructionRawDisp] -> ShowS)
-> Show DecodedInstructionRawDisp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawDisp] -> ShowS
$cshowList :: [DecodedInstructionRawDisp] -> ShowS
show :: DecodedInstructionRawDisp -> String
$cshow :: DecodedInstructionRawDisp -> String
showsPrec :: Int -> DecodedInstructionRawDisp -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawDisp -> ShowS
Show, DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> Bool
(DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> Bool)
-> (DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> Bool)
-> Eq DecodedInstructionRawDisp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> Bool
$c/= :: DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> Bool
== :: DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> Bool
$c== :: DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> Bool
Eq)
decoderInstructionRawDispStore :: Store.Dictionary DecodedInstructionRawDisp
decoderInstructionRawDispStore :: Dictionary DecodedInstructionRawDisp
decoderInstructionRawDispStore =
Access DecodedInstructionRawDisp DecodedInstructionRawDisp
-> Dictionary DecodedInstructionRawDisp
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawDisp DecodedInstructionRawDisp
-> Dictionary DecodedInstructionRawDisp)
-> Access DecodedInstructionRawDisp DecodedInstructionRawDisp
-> Dictionary DecodedInstructionRawDisp
forall a b. (a -> b) -> a -> b
$ Int64 -> Word8 -> Word8 -> DecodedInstructionRawDisp
DecodedInstructionRawDisp
(Int64 -> Word8 -> Word8 -> DecodedInstructionRawDisp)
-> Access DecodedInstructionRawDisp Int64
-> Access
DecodedInstructionRawDisp
(Word8 -> Word8 -> DecodedInstructionRawDisp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawDisp -> Int64)
-> Access DecodedInstructionRawDisp Int64
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawDisp -> Int64
decodedInstructionRawDispValue
Access
DecodedInstructionRawDisp
(Word8 -> Word8 -> DecodedInstructionRawDisp)
-> Access DecodedInstructionRawDisp Word8
-> Access
DecodedInstructionRawDisp (Word8 -> DecodedInstructionRawDisp)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawDisp -> Word8)
-> Access DecodedInstructionRawDisp Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawDisp -> Word8
decodedInstructionRawDispSize
Access
DecodedInstructionRawDisp (Word8 -> DecodedInstructionRawDisp)
-> Access DecodedInstructionRawDisp Word8
-> Access DecodedInstructionRawDisp DecodedInstructionRawDisp
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawDisp -> Word8)
-> Access DecodedInstructionRawDisp Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawDisp -> Word8
decodedInstructionRawDispOffset
instance Storable DecodedInstructionRawDisp where
alignment :: DecodedInstructionRawDisp -> Int
alignment = Dictionary DecodedInstructionRawDisp
-> DecodedInstructionRawDisp -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawDisp
decoderInstructionRawDispStore
sizeOf :: DecodedInstructionRawDisp -> Int
sizeOf = Dictionary DecodedInstructionRawDisp
-> DecodedInstructionRawDisp -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawDisp
decoderInstructionRawDispStore
peek :: Ptr DecodedInstructionRawDisp -> IO DecodedInstructionRawDisp
peek = Dictionary DecodedInstructionRawDisp
-> Ptr DecodedInstructionRawDisp -> IO DecodedInstructionRawDisp
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawDisp
decoderInstructionRawDispStore
poke :: Ptr DecodedInstructionRawDisp -> DecodedInstructionRawDisp -> IO ()
poke = Dictionary DecodedInstructionRawDisp
-> Ptr DecodedInstructionRawDisp
-> DecodedInstructionRawDisp
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawDisp
decoderInstructionRawDispStore
data DecodedInstructionRawSib =
DecodedInstructionRawSib
{ DecodedInstructionRawSib -> Word8
decodedInstructionRawSibScale :: {-# UNPACK #-}!Word8
, DecodedInstructionRawSib -> Word8
decodedInstructionRawSibIndex :: {-# UNPACK #-}!Word8
, DecodedInstructionRawSib -> Word8
decodedInstructionRawSibBase :: {-# UNPACK #-}!Word8
, DecodedInstructionRawSib -> Word8
decodedInstructionRawSibOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawSib -> ShowS
[DecodedInstructionRawSib] -> ShowS
DecodedInstructionRawSib -> String
(Int -> DecodedInstructionRawSib -> ShowS)
-> (DecodedInstructionRawSib -> String)
-> ([DecodedInstructionRawSib] -> ShowS)
-> Show DecodedInstructionRawSib
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawSib] -> ShowS
$cshowList :: [DecodedInstructionRawSib] -> ShowS
show :: DecodedInstructionRawSib -> String
$cshow :: DecodedInstructionRawSib -> String
showsPrec :: Int -> DecodedInstructionRawSib -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawSib -> ShowS
Show, DecodedInstructionRawSib -> DecodedInstructionRawSib -> Bool
(DecodedInstructionRawSib -> DecodedInstructionRawSib -> Bool)
-> (DecodedInstructionRawSib -> DecodedInstructionRawSib -> Bool)
-> Eq DecodedInstructionRawSib
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawSib -> DecodedInstructionRawSib -> Bool
$c/= :: DecodedInstructionRawSib -> DecodedInstructionRawSib -> Bool
== :: DecodedInstructionRawSib -> DecodedInstructionRawSib -> Bool
$c== :: DecodedInstructionRawSib -> DecodedInstructionRawSib -> Bool
Eq)
decodedInstructionRawSibStore :: Store.Dictionary DecodedInstructionRawSib
decodedInstructionRawSibStore :: Dictionary DecodedInstructionRawSib
decodedInstructionRawSibStore =
Access DecodedInstructionRawSib DecodedInstructionRawSib
-> Dictionary DecodedInstructionRawSib
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawSib DecodedInstructionRawSib
-> Dictionary DecodedInstructionRawSib)
-> Access DecodedInstructionRawSib DecodedInstructionRawSib
-> Dictionary DecodedInstructionRawSib
forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawSib
DecodedInstructionRawSib
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawSib)
-> Access DecodedInstructionRawSib Word8
-> Access
DecodedInstructionRawSib
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawSib)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawSib -> Word8)
-> Access DecodedInstructionRawSib Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawSib -> Word8
decodedInstructionRawSibScale
Access
DecodedInstructionRawSib
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawSib)
-> Access DecodedInstructionRawSib Word8
-> Access
DecodedInstructionRawSib
(Word8 -> Word8 -> DecodedInstructionRawSib)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawSib -> Word8)
-> Access DecodedInstructionRawSib Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawSib -> Word8
decodedInstructionRawSibIndex
Access
DecodedInstructionRawSib
(Word8 -> Word8 -> DecodedInstructionRawSib)
-> Access DecodedInstructionRawSib Word8
-> Access
DecodedInstructionRawSib (Word8 -> DecodedInstructionRawSib)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawSib -> Word8)
-> Access DecodedInstructionRawSib Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawSib -> Word8
decodedInstructionRawSibBase
Access DecodedInstructionRawSib (Word8 -> DecodedInstructionRawSib)
-> Access DecodedInstructionRawSib Word8
-> Access DecodedInstructionRawSib DecodedInstructionRawSib
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawSib -> Word8)
-> Access DecodedInstructionRawSib Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawSib -> Word8
decodedInstructionRawSibOffset
instance Storable DecodedInstructionRawSib where
alignment :: DecodedInstructionRawSib -> Int
alignment = Dictionary DecodedInstructionRawSib
-> DecodedInstructionRawSib -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawSib
decodedInstructionRawSibStore
sizeOf :: DecodedInstructionRawSib -> Int
sizeOf = Dictionary DecodedInstructionRawSib
-> DecodedInstructionRawSib -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawSib
decodedInstructionRawSibStore
peek :: Ptr DecodedInstructionRawSib -> IO DecodedInstructionRawSib
peek = Dictionary DecodedInstructionRawSib
-> Ptr DecodedInstructionRawSib -> IO DecodedInstructionRawSib
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawSib
decodedInstructionRawSibStore
poke :: Ptr DecodedInstructionRawSib -> DecodedInstructionRawSib -> IO ()
poke = Dictionary DecodedInstructionRawSib
-> Ptr DecodedInstructionRawSib
-> DecodedInstructionRawSib
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawSib
decodedInstructionRawSibStore
data DecodedInstructionModRm =
DecodedInstructionModRm
{ DecodedInstructionModRm -> Word8
decodedInstructionModRmAddressingMode :: {-# UNPACK #-}!Word8
, DecodedInstructionModRm -> Word8
decodedInstructionModRmRegister :: {-# UNPACK #-}!Word8
, DecodedInstructionModRm -> Word8
decodedInstructionModRmRM :: {-# UNPACK #-}!Word8
, DecodedInstructionModRm -> Word8
decodedInstructionModRmOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionModRm -> ShowS
[DecodedInstructionModRm] -> ShowS
DecodedInstructionModRm -> String
(Int -> DecodedInstructionModRm -> ShowS)
-> (DecodedInstructionModRm -> String)
-> ([DecodedInstructionModRm] -> ShowS)
-> Show DecodedInstructionModRm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionModRm] -> ShowS
$cshowList :: [DecodedInstructionModRm] -> ShowS
show :: DecodedInstructionModRm -> String
$cshow :: DecodedInstructionModRm -> String
showsPrec :: Int -> DecodedInstructionModRm -> ShowS
$cshowsPrec :: Int -> DecodedInstructionModRm -> ShowS
Show, DecodedInstructionModRm -> DecodedInstructionModRm -> Bool
(DecodedInstructionModRm -> DecodedInstructionModRm -> Bool)
-> (DecodedInstructionModRm -> DecodedInstructionModRm -> Bool)
-> Eq DecodedInstructionModRm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionModRm -> DecodedInstructionModRm -> Bool
$c/= :: DecodedInstructionModRm -> DecodedInstructionModRm -> Bool
== :: DecodedInstructionModRm -> DecodedInstructionModRm -> Bool
$c== :: DecodedInstructionModRm -> DecodedInstructionModRm -> Bool
Eq)
decodedInstructionModRmStore :: Store.Dictionary DecodedInstructionModRm
decodedInstructionModRmStore :: Dictionary DecodedInstructionModRm
decodedInstructionModRmStore =
Access DecodedInstructionModRm DecodedInstructionModRm
-> Dictionary DecodedInstructionModRm
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionModRm DecodedInstructionModRm
-> Dictionary DecodedInstructionModRm)
-> Access DecodedInstructionModRm DecodedInstructionModRm
-> Dictionary DecodedInstructionModRm
forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionModRm
DecodedInstructionModRm
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionModRm)
-> Access DecodedInstructionModRm Word8
-> Access
DecodedInstructionModRm
(Word8 -> Word8 -> Word8 -> DecodedInstructionModRm)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionModRm -> Word8)
-> Access DecodedInstructionModRm Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionModRm -> Word8
decodedInstructionModRmAddressingMode
Access
DecodedInstructionModRm
(Word8 -> Word8 -> Word8 -> DecodedInstructionModRm)
-> Access DecodedInstructionModRm Word8
-> Access
DecodedInstructionModRm (Word8 -> Word8 -> DecodedInstructionModRm)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionModRm -> Word8)
-> Access DecodedInstructionModRm Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionModRm -> Word8
decodedInstructionModRmRegister
Access
DecodedInstructionModRm (Word8 -> Word8 -> DecodedInstructionModRm)
-> Access DecodedInstructionModRm Word8
-> Access
DecodedInstructionModRm (Word8 -> DecodedInstructionModRm)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionModRm -> Word8)
-> Access DecodedInstructionModRm Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionModRm -> Word8
decodedInstructionModRmRM
Access DecodedInstructionModRm (Word8 -> DecodedInstructionModRm)
-> Access DecodedInstructionModRm Word8
-> Access DecodedInstructionModRm DecodedInstructionModRm
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionModRm -> Word8)
-> Access DecodedInstructionModRm Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionModRm -> Word8
decodedInstructionModRmOffset
instance Storable DecodedInstructionModRm where
alignment :: DecodedInstructionModRm -> Int
alignment = Dictionary DecodedInstructionModRm
-> DecodedInstructionModRm -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionModRm
decodedInstructionModRmStore
sizeOf :: DecodedInstructionModRm -> Int
sizeOf = Dictionary DecodedInstructionModRm
-> DecodedInstructionModRm -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionModRm
decodedInstructionModRmStore
peek :: Ptr DecodedInstructionModRm -> IO DecodedInstructionModRm
peek = Dictionary DecodedInstructionModRm
-> Ptr DecodedInstructionModRm -> IO DecodedInstructionModRm
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionModRm
decodedInstructionModRmStore
poke :: Ptr DecodedInstructionModRm -> DecodedInstructionModRm -> IO ()
poke = Dictionary DecodedInstructionModRm
-> Ptr DecodedInstructionModRm -> DecodedInstructionModRm -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionModRm
decodedInstructionModRmStore
data DecodedInstructionRawMvex =
DecodedInstructionRawMvex
{ DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexR :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexX :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexB :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexR2 :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexMMMM :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexW :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexVVVV :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexPP :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexE :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexSSS :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexV2 :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexKKK :: {-# UNPACK #-}!Word8
, DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawMvex -> ShowS
[DecodedInstructionRawMvex] -> ShowS
DecodedInstructionRawMvex -> String
(Int -> DecodedInstructionRawMvex -> ShowS)
-> (DecodedInstructionRawMvex -> String)
-> ([DecodedInstructionRawMvex] -> ShowS)
-> Show DecodedInstructionRawMvex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawMvex] -> ShowS
$cshowList :: [DecodedInstructionRawMvex] -> ShowS
show :: DecodedInstructionRawMvex -> String
$cshow :: DecodedInstructionRawMvex -> String
showsPrec :: Int -> DecodedInstructionRawMvex -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawMvex -> ShowS
Show, DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> Bool
(DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> Bool)
-> (DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> Bool)
-> Eq DecodedInstructionRawMvex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> Bool
$c/= :: DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> Bool
== :: DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> Bool
$c== :: DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> Bool
Eq)
decodedInstructionRawMvexStore :: Store.Dictionary DecodedInstructionRawMvex
decodedInstructionRawMvexStore :: Dictionary DecodedInstructionRawMvex
decodedInstructionRawMvexStore =
Access DecodedInstructionRawMvex DecodedInstructionRawMvex
-> Dictionary DecodedInstructionRawMvex
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawMvex DecodedInstructionRawMvex
-> Dictionary DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex DecodedInstructionRawMvex
-> Dictionary DecodedInstructionRawMvex
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexR
Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexX
Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexB
Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexR2
Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexMMMM
Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexW
Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexVVVV
Access
DecodedInstructionRawMvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexPP
Access
DecodedInstructionRawMvex
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexE
Access
DecodedInstructionRawMvex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexSSS
Access
DecodedInstructionRawMvex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex
(Word8 -> Word8 -> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexV2
Access
DecodedInstructionRawMvex
(Word8 -> Word8 -> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access
DecodedInstructionRawMvex (Word8 -> DecodedInstructionRawMvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexKKK
Access
DecodedInstructionRawMvex (Word8 -> DecodedInstructionRawMvex)
-> Access DecodedInstructionRawMvex Word8
-> Access DecodedInstructionRawMvex DecodedInstructionRawMvex
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawMvex -> Word8)
-> Access DecodedInstructionRawMvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawMvex -> Word8
decodedInstructionRawMvexOffset
instance Storable DecodedInstructionRawMvex where
alignment :: DecodedInstructionRawMvex -> Int
alignment = Dictionary DecodedInstructionRawMvex
-> DecodedInstructionRawMvex -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawMvex
decodedInstructionRawMvexStore
sizeOf :: DecodedInstructionRawMvex -> Int
sizeOf = Dictionary DecodedInstructionRawMvex
-> DecodedInstructionRawMvex -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawMvex
decodedInstructionRawMvexStore
peek :: Ptr DecodedInstructionRawMvex -> IO DecodedInstructionRawMvex
peek = Dictionary DecodedInstructionRawMvex
-> Ptr DecodedInstructionRawMvex -> IO DecodedInstructionRawMvex
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawMvex
decodedInstructionRawMvexStore
poke :: Ptr DecodedInstructionRawMvex -> DecodedInstructionRawMvex -> IO ()
poke = Dictionary DecodedInstructionRawMvex
-> Ptr DecodedInstructionRawMvex
-> DecodedInstructionRawMvex
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawMvex
decodedInstructionRawMvexStore
data DecodedInstructionRawEvex =
DecodedInstructionRawEvex
{ DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexR :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexX :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexB :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexR2 :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexMM :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexW :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexVVVV :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexPP :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexZ :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexL2 :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexL :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexB' :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexV2 :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexAAA :: {-# UNPACK #-}!Word8
, DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawEvex -> ShowS
[DecodedInstructionRawEvex] -> ShowS
DecodedInstructionRawEvex -> String
(Int -> DecodedInstructionRawEvex -> ShowS)
-> (DecodedInstructionRawEvex -> String)
-> ([DecodedInstructionRawEvex] -> ShowS)
-> Show DecodedInstructionRawEvex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawEvex] -> ShowS
$cshowList :: [DecodedInstructionRawEvex] -> ShowS
show :: DecodedInstructionRawEvex -> String
$cshow :: DecodedInstructionRawEvex -> String
showsPrec :: Int -> DecodedInstructionRawEvex -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawEvex -> ShowS
Show, DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> Bool
(DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> Bool)
-> (DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> Bool)
-> Eq DecodedInstructionRawEvex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> Bool
$c/= :: DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> Bool
== :: DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> Bool
$c== :: DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> Bool
Eq)
decodedInstructionRawEvexStore :: Store.Dictionary DecodedInstructionRawEvex
decodedInstructionRawEvexStore :: Dictionary DecodedInstructionRawEvex
decodedInstructionRawEvexStore =
Access DecodedInstructionRawEvex DecodedInstructionRawEvex
-> Dictionary DecodedInstructionRawEvex
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawEvex DecodedInstructionRawEvex
-> Dictionary DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex DecodedInstructionRawEvex
-> Dictionary DecodedInstructionRawEvex
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexR
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexX
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexB
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexR2
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexMM
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexW
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexVVVV
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexPP
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexZ
Access
DecodedInstructionRawEvex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexL2
Access
DecodedInstructionRawEvex
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexL
Access
DecodedInstructionRawEvex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexB'
Access
DecodedInstructionRawEvex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex
(Word8 -> Word8 -> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexV2
Access
DecodedInstructionRawEvex
(Word8 -> Word8 -> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access
DecodedInstructionRawEvex (Word8 -> DecodedInstructionRawEvex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexAAA
Access
DecodedInstructionRawEvex (Word8 -> DecodedInstructionRawEvex)
-> Access DecodedInstructionRawEvex Word8
-> Access DecodedInstructionRawEvex DecodedInstructionRawEvex
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawEvex -> Word8)
-> Access DecodedInstructionRawEvex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawEvex -> Word8
decodedInstructionRawEvexOffset
instance Storable DecodedInstructionRawEvex where
alignment :: DecodedInstructionRawEvex -> Int
alignment = Dictionary DecodedInstructionRawEvex
-> DecodedInstructionRawEvex -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawEvex
decodedInstructionRawEvexStore
sizeOf :: DecodedInstructionRawEvex -> Int
sizeOf = Dictionary DecodedInstructionRawEvex
-> DecodedInstructionRawEvex -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawEvex
decodedInstructionRawEvexStore
peek :: Ptr DecodedInstructionRawEvex -> IO DecodedInstructionRawEvex
peek = Dictionary DecodedInstructionRawEvex
-> Ptr DecodedInstructionRawEvex -> IO DecodedInstructionRawEvex
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawEvex
decodedInstructionRawEvexStore
poke :: Ptr DecodedInstructionRawEvex -> DecodedInstructionRawEvex -> IO ()
poke = Dictionary DecodedInstructionRawEvex
-> Ptr DecodedInstructionRawEvex
-> DecodedInstructionRawEvex
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawEvex
decodedInstructionRawEvexStore
data DecodedInstructionRawVex =
DecodedInstructionRawVex
{ DecodedInstructionRawVex -> Word8
decodedInstructionRawVexR :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexX :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexB :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexMMMMM :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexW :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexVVVV :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexL :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexPP :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexOffset :: {-# UNPACK #-}!Word8
, DecodedInstructionRawVex -> Word8
decodedInstructionRawVexSize :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawVex -> ShowS
[DecodedInstructionRawVex] -> ShowS
DecodedInstructionRawVex -> String
(Int -> DecodedInstructionRawVex -> ShowS)
-> (DecodedInstructionRawVex -> String)
-> ([DecodedInstructionRawVex] -> ShowS)
-> Show DecodedInstructionRawVex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawVex] -> ShowS
$cshowList :: [DecodedInstructionRawVex] -> ShowS
show :: DecodedInstructionRawVex -> String
$cshow :: DecodedInstructionRawVex -> String
showsPrec :: Int -> DecodedInstructionRawVex -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawVex -> ShowS
Show, DecodedInstructionRawVex -> DecodedInstructionRawVex -> Bool
(DecodedInstructionRawVex -> DecodedInstructionRawVex -> Bool)
-> (DecodedInstructionRawVex -> DecodedInstructionRawVex -> Bool)
-> Eq DecodedInstructionRawVex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawVex -> DecodedInstructionRawVex -> Bool
$c/= :: DecodedInstructionRawVex -> DecodedInstructionRawVex -> Bool
== :: DecodedInstructionRawVex -> DecodedInstructionRawVex -> Bool
$c== :: DecodedInstructionRawVex -> DecodedInstructionRawVex -> Bool
Eq)
decodedInstructionRawVexStore :: Store.Dictionary DecodedInstructionRawVex
decodedInstructionRawVexStore :: Dictionary DecodedInstructionRawVex
decodedInstructionRawVexStore =
Access DecodedInstructionRawVex DecodedInstructionRawVex
-> Dictionary DecodedInstructionRawVex
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawVex DecodedInstructionRawVex
-> Dictionary DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex DecodedInstructionRawVex
-> Dictionary DecodedInstructionRawVex
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexR
Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexX
Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexB
Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexMMMMM
Access
DecodedInstructionRawVex
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexW
Access
DecodedInstructionRawVex
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexVVVV
Access
DecodedInstructionRawVex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexL
Access
DecodedInstructionRawVex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex
(Word8 -> Word8 -> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexPP
Access
DecodedInstructionRawVex
(Word8 -> Word8 -> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access
DecodedInstructionRawVex (Word8 -> DecodedInstructionRawVex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexOffset
Access DecodedInstructionRawVex (Word8 -> DecodedInstructionRawVex)
-> Access DecodedInstructionRawVex Word8
-> Access DecodedInstructionRawVex DecodedInstructionRawVex
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawVex -> Word8)
-> Access DecodedInstructionRawVex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawVex -> Word8
decodedInstructionRawVexSize
instance Storable DecodedInstructionRawVex where
alignment :: DecodedInstructionRawVex -> Int
alignment = Dictionary DecodedInstructionRawVex
-> DecodedInstructionRawVex -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawVex
decodedInstructionRawVexStore
sizeOf :: DecodedInstructionRawVex -> Int
sizeOf = Dictionary DecodedInstructionRawVex
-> DecodedInstructionRawVex -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawVex
decodedInstructionRawVexStore
peek :: Ptr DecodedInstructionRawVex -> IO DecodedInstructionRawVex
peek = Dictionary DecodedInstructionRawVex
-> Ptr DecodedInstructionRawVex -> IO DecodedInstructionRawVex
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawVex
decodedInstructionRawVexStore
poke :: Ptr DecodedInstructionRawVex -> DecodedInstructionRawVex -> IO ()
poke = Dictionary DecodedInstructionRawVex
-> Ptr DecodedInstructionRawVex
-> DecodedInstructionRawVex
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawVex
decodedInstructionRawVexStore
data DecodedInstructionRawXop =
DecodedInstructionRawXop
{ DecodedInstructionRawXop -> Word8
decodedInstructionRawXopR :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopX :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopB :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopMMMMM :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopW :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopVVVV :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopL :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopPP :: {-# UNPACK #-}!Word8
, DecodedInstructionRawXop -> Word8
decodedInstructionRawXopOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawXop -> ShowS
[DecodedInstructionRawXop] -> ShowS
DecodedInstructionRawXop -> String
(Int -> DecodedInstructionRawXop -> ShowS)
-> (DecodedInstructionRawXop -> String)
-> ([DecodedInstructionRawXop] -> ShowS)
-> Show DecodedInstructionRawXop
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawXop] -> ShowS
$cshowList :: [DecodedInstructionRawXop] -> ShowS
show :: DecodedInstructionRawXop -> String
$cshow :: DecodedInstructionRawXop -> String
showsPrec :: Int -> DecodedInstructionRawXop -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawXop -> ShowS
Show, DecodedInstructionRawXop -> DecodedInstructionRawXop -> Bool
(DecodedInstructionRawXop -> DecodedInstructionRawXop -> Bool)
-> (DecodedInstructionRawXop -> DecodedInstructionRawXop -> Bool)
-> Eq DecodedInstructionRawXop
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawXop -> DecodedInstructionRawXop -> Bool
$c/= :: DecodedInstructionRawXop -> DecodedInstructionRawXop -> Bool
== :: DecodedInstructionRawXop -> DecodedInstructionRawXop -> Bool
$c== :: DecodedInstructionRawXop -> DecodedInstructionRawXop -> Bool
Eq)
decodedInstructionRawXopStore :: Store.Dictionary DecodedInstructionRawXop
decodedInstructionRawXopStore :: Dictionary DecodedInstructionRawXop
decodedInstructionRawXopStore =
Access DecodedInstructionRawXop DecodedInstructionRawXop
-> Dictionary DecodedInstructionRawXop
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawXop DecodedInstructionRawXop
-> Dictionary DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop DecodedInstructionRawXop
-> Dictionary DecodedInstructionRawXop
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop
DecodedInstructionRawXop
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopR
Access
DecodedInstructionRawXop
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopX
Access
DecodedInstructionRawXop
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopB
Access
DecodedInstructionRawXop
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopMMMMM
Access
DecodedInstructionRawXop
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopW
Access
DecodedInstructionRawXop
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopVVVV
Access
DecodedInstructionRawXop
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop
(Word8 -> Word8 -> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopL
Access
DecodedInstructionRawXop
(Word8 -> Word8 -> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access
DecodedInstructionRawXop (Word8 -> DecodedInstructionRawXop)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopPP
Access DecodedInstructionRawXop (Word8 -> DecodedInstructionRawXop)
-> Access DecodedInstructionRawXop Word8
-> Access DecodedInstructionRawXop DecodedInstructionRawXop
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawXop -> Word8)
-> Access DecodedInstructionRawXop Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawXop -> Word8
decodedInstructionRawXopOffset
instance Storable DecodedInstructionRawXop where
alignment :: DecodedInstructionRawXop -> Int
alignment = Dictionary DecodedInstructionRawXop
-> DecodedInstructionRawXop -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawXop
decodedInstructionRawXopStore
sizeOf :: DecodedInstructionRawXop -> Int
sizeOf = Dictionary DecodedInstructionRawXop
-> DecodedInstructionRawXop -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawXop
decodedInstructionRawXopStore
peek :: Ptr DecodedInstructionRawXop -> IO DecodedInstructionRawXop
peek = Dictionary DecodedInstructionRawXop
-> Ptr DecodedInstructionRawXop -> IO DecodedInstructionRawXop
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawXop
decodedInstructionRawXopStore
poke :: Ptr DecodedInstructionRawXop -> DecodedInstructionRawXop -> IO ()
poke = Dictionary DecodedInstructionRawXop
-> Ptr DecodedInstructionRawXop
-> DecodedInstructionRawXop
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawXop
decodedInstructionRawXopStore
data DecodedInstructionRawRex =
DecodedInstructionRawRex
{ DecodedInstructionRawRex -> Word8
decodedInstructionRawRexW :: {-# UNPACK #-}!Word8
, DecodedInstructionRawRex -> Word8
decodedInstructionRawRexR :: {-# UNPACK #-}!Word8
, DecodedInstructionRawRex -> Word8
decodedInstructionRawRexX :: {-# UNPACK #-}!Word8
, DecodedInstructionRawRex -> Word8
decodedInstructionRawRexB :: {-# UNPACK #-}!Word8
, DecodedInstructionRawRex -> Word8
decodedInstructionRawRexOffset :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawRex -> ShowS
[DecodedInstructionRawRex] -> ShowS
DecodedInstructionRawRex -> String
(Int -> DecodedInstructionRawRex -> ShowS)
-> (DecodedInstructionRawRex -> String)
-> ([DecodedInstructionRawRex] -> ShowS)
-> Show DecodedInstructionRawRex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawRex] -> ShowS
$cshowList :: [DecodedInstructionRawRex] -> ShowS
show :: DecodedInstructionRawRex -> String
$cshow :: DecodedInstructionRawRex -> String
showsPrec :: Int -> DecodedInstructionRawRex -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawRex -> ShowS
Show, DecodedInstructionRawRex -> DecodedInstructionRawRex -> Bool
(DecodedInstructionRawRex -> DecodedInstructionRawRex -> Bool)
-> (DecodedInstructionRawRex -> DecodedInstructionRawRex -> Bool)
-> Eq DecodedInstructionRawRex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawRex -> DecodedInstructionRawRex -> Bool
$c/= :: DecodedInstructionRawRex -> DecodedInstructionRawRex -> Bool
== :: DecodedInstructionRawRex -> DecodedInstructionRawRex -> Bool
$c== :: DecodedInstructionRawRex -> DecodedInstructionRawRex -> Bool
Eq)
decodedInstructionRawRexStore :: Store.Dictionary DecodedInstructionRawRex
decodedInstructionRawRexStore :: Dictionary DecodedInstructionRawRex
decodedInstructionRawRexStore =
Access DecodedInstructionRawRex DecodedInstructionRawRex
-> Dictionary DecodedInstructionRawRex
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawRex DecodedInstructionRawRex
-> Dictionary DecodedInstructionRawRex)
-> Access DecodedInstructionRawRex DecodedInstructionRawRex
-> Dictionary DecodedInstructionRawRex
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawRex
DecodedInstructionRawRex
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawRex)
-> Access DecodedInstructionRawRex Word8
-> Access
DecodedInstructionRawRex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawRex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawRex -> Word8)
-> Access DecodedInstructionRawRex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawRex -> Word8
decodedInstructionRawRexW
Access
DecodedInstructionRawRex
(Word8 -> Word8 -> Word8 -> Word8 -> DecodedInstructionRawRex)
-> Access DecodedInstructionRawRex Word8
-> Access
DecodedInstructionRawRex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawRex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawRex -> Word8)
-> Access DecodedInstructionRawRex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawRex -> Word8
decodedInstructionRawRexR
Access
DecodedInstructionRawRex
(Word8 -> Word8 -> Word8 -> DecodedInstructionRawRex)
-> Access DecodedInstructionRawRex Word8
-> Access
DecodedInstructionRawRex
(Word8 -> Word8 -> DecodedInstructionRawRex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawRex -> Word8)
-> Access DecodedInstructionRawRex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawRex -> Word8
decodedInstructionRawRexX
Access
DecodedInstructionRawRex
(Word8 -> Word8 -> DecodedInstructionRawRex)
-> Access DecodedInstructionRawRex Word8
-> Access
DecodedInstructionRawRex (Word8 -> DecodedInstructionRawRex)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawRex -> Word8)
-> Access DecodedInstructionRawRex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawRex -> Word8
decodedInstructionRawRexB
Access DecodedInstructionRawRex (Word8 -> DecodedInstructionRawRex)
-> Access DecodedInstructionRawRex Word8
-> Access DecodedInstructionRawRex DecodedInstructionRawRex
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawRex -> Word8)
-> Access DecodedInstructionRawRex Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawRex -> Word8
decodedInstructionRawRexOffset
instance Storable DecodedInstructionRawRex where
alignment :: DecodedInstructionRawRex -> Int
alignment = Dictionary DecodedInstructionRawRex
-> DecodedInstructionRawRex -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawRex
decodedInstructionRawRexStore
sizeOf :: DecodedInstructionRawRex -> Int
sizeOf = Dictionary DecodedInstructionRawRex
-> DecodedInstructionRawRex -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawRex
decodedInstructionRawRexStore
peek :: Ptr DecodedInstructionRawRex -> IO DecodedInstructionRawRex
peek = Dictionary DecodedInstructionRawRex
-> Ptr DecodedInstructionRawRex -> IO DecodedInstructionRawRex
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawRex
decodedInstructionRawRexStore
poke :: Ptr DecodedInstructionRawRex -> DecodedInstructionRawRex -> IO ()
poke = Dictionary DecodedInstructionRawRex
-> Ptr DecodedInstructionRawRex
-> DecodedInstructionRawRex
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawRex
decodedInstructionRawRexStore
data DecodedInstructionRawPrefix =
DecodedInstructionRawPrefix
{ DecodedInstructionRawPrefix -> PrefixType
decodedInstructionRawPrefixType :: !PrefixType
, DecodedInstructionRawPrefix -> Word8
decodedInstructionRawPrefixValue :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionRawPrefix -> ShowS
[DecodedInstructionRawPrefix] -> ShowS
DecodedInstructionRawPrefix -> String
(Int -> DecodedInstructionRawPrefix -> ShowS)
-> (DecodedInstructionRawPrefix -> String)
-> ([DecodedInstructionRawPrefix] -> ShowS)
-> Show DecodedInstructionRawPrefix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRawPrefix] -> ShowS
$cshowList :: [DecodedInstructionRawPrefix] -> ShowS
show :: DecodedInstructionRawPrefix -> String
$cshow :: DecodedInstructionRawPrefix -> String
showsPrec :: Int -> DecodedInstructionRawPrefix -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRawPrefix -> ShowS
Show, DecodedInstructionRawPrefix -> DecodedInstructionRawPrefix -> Bool
(DecodedInstructionRawPrefix
-> DecodedInstructionRawPrefix -> Bool)
-> (DecodedInstructionRawPrefix
-> DecodedInstructionRawPrefix -> Bool)
-> Eq DecodedInstructionRawPrefix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRawPrefix -> DecodedInstructionRawPrefix -> Bool
$c/= :: DecodedInstructionRawPrefix -> DecodedInstructionRawPrefix -> Bool
== :: DecodedInstructionRawPrefix -> DecodedInstructionRawPrefix -> Bool
$c== :: DecodedInstructionRawPrefix -> DecodedInstructionRawPrefix -> Bool
Eq)
decodedInstructionRawPrefixStore :: Store.Dictionary DecodedInstructionRawPrefix
decodedInstructionRawPrefixStore :: Dictionary DecodedInstructionRawPrefix
decodedInstructionRawPrefixStore =
Access DecodedInstructionRawPrefix DecodedInstructionRawPrefix
-> Dictionary DecodedInstructionRawPrefix
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRawPrefix DecodedInstructionRawPrefix
-> Dictionary DecodedInstructionRawPrefix)
-> Access DecodedInstructionRawPrefix DecodedInstructionRawPrefix
-> Dictionary DecodedInstructionRawPrefix
forall a b. (a -> b) -> a -> b
$ PrefixType -> Word8 -> DecodedInstructionRawPrefix
DecodedInstructionRawPrefix
(PrefixType -> Word8 -> DecodedInstructionRawPrefix)
-> Access DecodedInstructionRawPrefix PrefixType
-> Access
DecodedInstructionRawPrefix (Word8 -> DecodedInstructionRawPrefix)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRawPrefix -> PrefixType)
-> Access DecodedInstructionRawPrefix PrefixType
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawPrefix -> PrefixType
decodedInstructionRawPrefixType
Access
DecodedInstructionRawPrefix (Word8 -> DecodedInstructionRawPrefix)
-> Access DecodedInstructionRawPrefix Word8
-> Access DecodedInstructionRawPrefix DecodedInstructionRawPrefix
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRawPrefix -> Word8)
-> Access DecodedInstructionRawPrefix Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRawPrefix -> Word8
decodedInstructionRawPrefixValue
instance Storable DecodedInstructionRawPrefix where
alignment :: DecodedInstructionRawPrefix -> Int
alignment = Dictionary DecodedInstructionRawPrefix
-> DecodedInstructionRawPrefix -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRawPrefix
decodedInstructionRawPrefixStore
sizeOf :: DecodedInstructionRawPrefix -> Int
sizeOf = Dictionary DecodedInstructionRawPrefix
-> DecodedInstructionRawPrefix -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRawPrefix
decodedInstructionRawPrefixStore
peek :: Ptr DecodedInstructionRawPrefix -> IO DecodedInstructionRawPrefix
peek = Dictionary DecodedInstructionRawPrefix
-> Ptr DecodedInstructionRawPrefix
-> IO DecodedInstructionRawPrefix
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRawPrefix
decodedInstructionRawPrefixStore
poke :: Ptr DecodedInstructionRawPrefix
-> DecodedInstructionRawPrefix -> IO ()
poke = Dictionary DecodedInstructionRawPrefix
-> Ptr DecodedInstructionRawPrefix
-> DecodedInstructionRawPrefix
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRawPrefix
decodedInstructionRawPrefixStore
data DecodedInstructionRaw =
DecodedInstructionRaw
{ DecodedInstructionRaw -> Word8
decodedInstructionRawPrefixCount :: {-# UNPACK #-}!Word8
, DecodedInstructionRaw
-> StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength
decodedInstructionRawPrefixes :: !(StorableFixedArray DecodedInstructionRawPrefix ZydisMaxInstructionLength)
, DecodedInstructionRaw -> DecodedInstructionRawRex
decodedInstructionRawRex :: !DecodedInstructionRawRex
, DecodedInstructionRaw -> DecodedInstructionRawXop
decodedInstructionRawXop :: !DecodedInstructionRawXop
, DecodedInstructionRaw -> DecodedInstructionRawVex
decodedInstructionRawVex :: !DecodedInstructionRawVex
, DecodedInstructionRaw -> DecodedInstructionRawEvex
decodedInstructionRawEvex :: !DecodedInstructionRawEvex
, DecodedInstructionRaw -> DecodedInstructionRawMvex
decodedInstructionRawMvex :: !DecodedInstructionRawMvex
, DecodedInstructionRaw -> DecodedInstructionModRm
decodedInstructionRawModRm :: !DecodedInstructionModRm
, DecodedInstructionRaw -> DecodedInstructionRawSib
decodedInstructionRawSib :: !DecodedInstructionRawSib
, DecodedInstructionRaw -> DecodedInstructionRawDisp
decodedInstructionRawDisp :: !DecodedInstructionRawDisp
, DecodedInstructionRaw
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
decodedInstructionRawImmediates :: !(StorableFixedArray DecodedInstructionRawImmediate ZydisRawImmediateCount)
}
deriving stock (Int -> DecodedInstructionRaw -> ShowS
[DecodedInstructionRaw] -> ShowS
DecodedInstructionRaw -> String
(Int -> DecodedInstructionRaw -> ShowS)
-> (DecodedInstructionRaw -> String)
-> ([DecodedInstructionRaw] -> ShowS)
-> Show DecodedInstructionRaw
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionRaw] -> ShowS
$cshowList :: [DecodedInstructionRaw] -> ShowS
show :: DecodedInstructionRaw -> String
$cshow :: DecodedInstructionRaw -> String
showsPrec :: Int -> DecodedInstructionRaw -> ShowS
$cshowsPrec :: Int -> DecodedInstructionRaw -> ShowS
Show, DecodedInstructionRaw -> DecodedInstructionRaw -> Bool
(DecodedInstructionRaw -> DecodedInstructionRaw -> Bool)
-> (DecodedInstructionRaw -> DecodedInstructionRaw -> Bool)
-> Eq DecodedInstructionRaw
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionRaw -> DecodedInstructionRaw -> Bool
$c/= :: DecodedInstructionRaw -> DecodedInstructionRaw -> Bool
== :: DecodedInstructionRaw -> DecodedInstructionRaw -> Bool
$c== :: DecodedInstructionRaw -> DecodedInstructionRaw -> Bool
Eq)
decodedInstructionRawStore :: Store.Dictionary DecodedInstructionRaw
decodedInstructionRawStore :: Dictionary DecodedInstructionRaw
decodedInstructionRawStore =
Access DecodedInstructionRaw DecodedInstructionRaw
-> Dictionary DecodedInstructionRaw
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionRaw DecodedInstructionRaw
-> Dictionary DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRaw
-> Dictionary DecodedInstructionRaw
forall a b. (a -> b) -> a -> b
$ Word8
-> StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength
-> DecodedInstructionRawRex
-> DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw
DecodedInstructionRaw
(Word8
-> StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength
-> DecodedInstructionRawRex
-> DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw Word8
-> Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength
-> DecodedInstructionRawRex
-> DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionRaw -> Word8)
-> Access DecodedInstructionRaw Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> Word8
decodedInstructionRawPrefixCount
Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength
-> DecodedInstructionRawRex
-> DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength)
-> Access
DecodedInstructionRaw
(DecodedInstructionRawRex
-> DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw
-> StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength)
-> Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength)
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw
-> StorableFixedArray
DecodedInstructionRawPrefix ZydisMaxInstructionLength
decodedInstructionRawPrefixes
Access
DecodedInstructionRaw
(DecodedInstructionRawRex
-> DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRawRex
-> Access
DecodedInstructionRaw
(DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionRawRex)
-> Access DecodedInstructionRaw DecodedInstructionRawRex
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionRawRex
decodedInstructionRawRex
Access
DecodedInstructionRaw
(DecodedInstructionRawXop
-> DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRawXop
-> Access
DecodedInstructionRaw
(DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionRawXop)
-> Access DecodedInstructionRaw DecodedInstructionRawXop
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionRawXop
decodedInstructionRawXop
Access
DecodedInstructionRaw
(DecodedInstructionRawVex
-> DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRawVex
-> Access
DecodedInstructionRaw
(DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionRawVex)
-> Access DecodedInstructionRaw DecodedInstructionRawVex
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionRawVex
decodedInstructionRawVex
Access
DecodedInstructionRaw
(DecodedInstructionRawEvex
-> DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRawEvex
-> Access
DecodedInstructionRaw
(DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionRawEvex)
-> Access DecodedInstructionRaw DecodedInstructionRawEvex
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionRawEvex
decodedInstructionRawEvex
Access
DecodedInstructionRaw
(DecodedInstructionRawMvex
-> DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRawMvex
-> Access
DecodedInstructionRaw
(DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionRawMvex)
-> Access DecodedInstructionRaw DecodedInstructionRawMvex
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionRawMvex
decodedInstructionRawMvex
Access
DecodedInstructionRaw
(DecodedInstructionModRm
-> DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionModRm
-> Access
DecodedInstructionRaw
(DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionModRm)
-> Access DecodedInstructionRaw DecodedInstructionModRm
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionModRm
decodedInstructionRawModRm
Access
DecodedInstructionRaw
(DecodedInstructionRawSib
-> DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRawSib
-> Access
DecodedInstructionRaw
(DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionRawSib)
-> Access DecodedInstructionRaw DecodedInstructionRawSib
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionRawSib
decodedInstructionRawSib
Access
DecodedInstructionRaw
(DecodedInstructionRawDisp
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access DecodedInstructionRaw DecodedInstructionRawDisp
-> Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw -> DecodedInstructionRawDisp)
-> Access DecodedInstructionRaw DecodedInstructionRawDisp
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw -> DecodedInstructionRawDisp
decodedInstructionRawDisp
Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
-> DecodedInstructionRaw)
-> Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount)
-> Access DecodedInstructionRaw DecodedInstructionRaw
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionRaw
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount)
-> Access
DecodedInstructionRaw
(StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount)
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionRaw
-> StorableFixedArray
DecodedInstructionRawImmediate ZydisRawImmediateCount
decodedInstructionRawImmediates
instance Storable DecodedInstructionRaw where
alignment :: DecodedInstructionRaw -> Int
alignment = Dictionary DecodedInstructionRaw -> DecodedInstructionRaw -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionRaw
decodedInstructionRawStore
sizeOf :: DecodedInstructionRaw -> Int
sizeOf = Dictionary DecodedInstructionRaw -> DecodedInstructionRaw -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionRaw
decodedInstructionRawStore
peek :: Ptr DecodedInstructionRaw -> IO DecodedInstructionRaw
peek = Dictionary DecodedInstructionRaw
-> Ptr DecodedInstructionRaw -> IO DecodedInstructionRaw
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionRaw
decodedInstructionRawStore
poke :: Ptr DecodedInstructionRaw -> DecodedInstructionRaw -> IO ()
poke = Dictionary DecodedInstructionRaw
-> Ptr DecodedInstructionRaw -> DecodedInstructionRaw -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionRaw
decodedInstructionRawStore
data DecodedInstructionMeta =
DecodedInstructionMeta
{ DecodedInstructionMeta -> InstructionCategory
decodedInstructionMetaCategory :: !InstructionCategory
, DecodedInstructionMeta -> ISASet
decodedInstructionMetaISASet :: !ISASet
, DecodedInstructionMeta -> ISAExt
decodedInstructionMetaISAExt :: !ISAExt
, DecodedInstructionMeta -> BranchType
decodedInstructionBranchType :: !BranchType
, DecodedInstructionMeta -> ExceptionClass
decodedInstructionExceptionClass :: !ExceptionClass
}
deriving stock (Int -> DecodedInstructionMeta -> ShowS
[DecodedInstructionMeta] -> ShowS
DecodedInstructionMeta -> String
(Int -> DecodedInstructionMeta -> ShowS)
-> (DecodedInstructionMeta -> String)
-> ([DecodedInstructionMeta] -> ShowS)
-> Show DecodedInstructionMeta
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionMeta] -> ShowS
$cshowList :: [DecodedInstructionMeta] -> ShowS
show :: DecodedInstructionMeta -> String
$cshow :: DecodedInstructionMeta -> String
showsPrec :: Int -> DecodedInstructionMeta -> ShowS
$cshowsPrec :: Int -> DecodedInstructionMeta -> ShowS
Show, DecodedInstructionMeta -> DecodedInstructionMeta -> Bool
(DecodedInstructionMeta -> DecodedInstructionMeta -> Bool)
-> (DecodedInstructionMeta -> DecodedInstructionMeta -> Bool)
-> Eq DecodedInstructionMeta
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionMeta -> DecodedInstructionMeta -> Bool
$c/= :: DecodedInstructionMeta -> DecodedInstructionMeta -> Bool
== :: DecodedInstructionMeta -> DecodedInstructionMeta -> Bool
$c== :: DecodedInstructionMeta -> DecodedInstructionMeta -> Bool
Eq)
decodedInstructionMetaStore :: Store.Dictionary DecodedInstructionMeta
decodedInstructionMetaStore :: Dictionary DecodedInstructionMeta
decodedInstructionMetaStore =
Access DecodedInstructionMeta DecodedInstructionMeta
-> Dictionary DecodedInstructionMeta
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionMeta DecodedInstructionMeta
-> Dictionary DecodedInstructionMeta)
-> Access DecodedInstructionMeta DecodedInstructionMeta
-> Dictionary DecodedInstructionMeta
forall a b. (a -> b) -> a -> b
$ InstructionCategory
-> ISASet
-> ISAExt
-> BranchType
-> ExceptionClass
-> DecodedInstructionMeta
DecodedInstructionMeta
(InstructionCategory
-> ISASet
-> ISAExt
-> BranchType
-> ExceptionClass
-> DecodedInstructionMeta)
-> Access DecodedInstructionMeta InstructionCategory
-> Access
DecodedInstructionMeta
(ISASet
-> ISAExt
-> BranchType
-> ExceptionClass
-> DecodedInstructionMeta)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionMeta -> InstructionCategory)
-> Access DecodedInstructionMeta InstructionCategory
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionMeta -> InstructionCategory
decodedInstructionMetaCategory
Access
DecodedInstructionMeta
(ISASet
-> ISAExt
-> BranchType
-> ExceptionClass
-> DecodedInstructionMeta)
-> Access DecodedInstructionMeta ISASet
-> Access
DecodedInstructionMeta
(ISAExt -> BranchType -> ExceptionClass -> DecodedInstructionMeta)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionMeta -> ISASet)
-> Access DecodedInstructionMeta ISASet
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionMeta -> ISASet
decodedInstructionMetaISASet
Access
DecodedInstructionMeta
(ISAExt -> BranchType -> ExceptionClass -> DecodedInstructionMeta)
-> Access DecodedInstructionMeta ISAExt
-> Access
DecodedInstructionMeta
(BranchType -> ExceptionClass -> DecodedInstructionMeta)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionMeta -> ISAExt)
-> Access DecodedInstructionMeta ISAExt
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionMeta -> ISAExt
decodedInstructionMetaISAExt
Access
DecodedInstructionMeta
(BranchType -> ExceptionClass -> DecodedInstructionMeta)
-> Access DecodedInstructionMeta BranchType
-> Access
DecodedInstructionMeta (ExceptionClass -> DecodedInstructionMeta)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionMeta -> BranchType)
-> Access DecodedInstructionMeta BranchType
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionMeta -> BranchType
decodedInstructionBranchType
Access
DecodedInstructionMeta (ExceptionClass -> DecodedInstructionMeta)
-> Access DecodedInstructionMeta ExceptionClass
-> Access DecodedInstructionMeta DecodedInstructionMeta
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionMeta -> ExceptionClass)
-> Access DecodedInstructionMeta ExceptionClass
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionMeta -> ExceptionClass
decodedInstructionExceptionClass
instance Storable DecodedInstructionMeta where
alignment :: DecodedInstructionMeta -> Int
alignment = Dictionary DecodedInstructionMeta -> DecodedInstructionMeta -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionMeta
decodedInstructionMetaStore
sizeOf :: DecodedInstructionMeta -> Int
sizeOf = Dictionary DecodedInstructionMeta -> DecodedInstructionMeta -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionMeta
decodedInstructionMetaStore
peek :: Ptr DecodedInstructionMeta -> IO DecodedInstructionMeta
peek = Dictionary DecodedInstructionMeta
-> Ptr DecodedInstructionMeta -> IO DecodedInstructionMeta
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionMeta
decodedInstructionMetaStore
poke :: Ptr DecodedInstructionMeta -> DecodedInstructionMeta -> IO ()
poke = Dictionary DecodedInstructionMeta
-> Ptr DecodedInstructionMeta -> DecodedInstructionMeta -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionMeta
decodedInstructionMetaStore
data DecodedInstructionAvxBroadcast =
DecodedInstructionAvxBroadcast
{ DecodedInstructionAvxBroadcast -> Word8
decodedInstructionAvxBroadcastIsStatic :: {-# UNPACK #-}!Word8
, DecodedInstructionAvxBroadcast -> BroadcastMode
decodedInstructionAvxBroadcastMode :: !BroadcastMode
}
deriving stock (Int -> DecodedInstructionAvxBroadcast -> ShowS
[DecodedInstructionAvxBroadcast] -> ShowS
DecodedInstructionAvxBroadcast -> String
(Int -> DecodedInstructionAvxBroadcast -> ShowS)
-> (DecodedInstructionAvxBroadcast -> String)
-> ([DecodedInstructionAvxBroadcast] -> ShowS)
-> Show DecodedInstructionAvxBroadcast
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionAvxBroadcast] -> ShowS
$cshowList :: [DecodedInstructionAvxBroadcast] -> ShowS
show :: DecodedInstructionAvxBroadcast -> String
$cshow :: DecodedInstructionAvxBroadcast -> String
showsPrec :: Int -> DecodedInstructionAvxBroadcast -> ShowS
$cshowsPrec :: Int -> DecodedInstructionAvxBroadcast -> ShowS
Show, DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Bool
(DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Bool)
-> (DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Bool)
-> Eq DecodedInstructionAvxBroadcast
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Bool
$c/= :: DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Bool
== :: DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Bool
$c== :: DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Bool
Eq)
decodedInstructionAvxBroadcastStore
:: Store.Dictionary DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcastStore :: Dictionary DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcastStore =
Access
DecodedInstructionAvxBroadcast DecodedInstructionAvxBroadcast
-> Dictionary DecodedInstructionAvxBroadcast
forall r. Access r r -> Dictionary r
Store.run
(Access
DecodedInstructionAvxBroadcast DecodedInstructionAvxBroadcast
-> Dictionary DecodedInstructionAvxBroadcast)
-> Access
DecodedInstructionAvxBroadcast DecodedInstructionAvxBroadcast
-> Dictionary DecodedInstructionAvxBroadcast
forall a b. (a -> b) -> a -> b
$ Word8 -> BroadcastMode -> DecodedInstructionAvxBroadcast
DecodedInstructionAvxBroadcast
(Word8 -> BroadcastMode -> DecodedInstructionAvxBroadcast)
-> Access DecodedInstructionAvxBroadcast Word8
-> Access
DecodedInstructionAvxBroadcast
(BroadcastMode -> DecodedInstructionAvxBroadcast)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionAvxBroadcast -> Word8)
-> Access DecodedInstructionAvxBroadcast Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvxBroadcast -> Word8
decodedInstructionAvxBroadcastIsStatic
Access
DecodedInstructionAvxBroadcast
(BroadcastMode -> DecodedInstructionAvxBroadcast)
-> Access DecodedInstructionAvxBroadcast BroadcastMode
-> Access
DecodedInstructionAvxBroadcast DecodedInstructionAvxBroadcast
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvxBroadcast -> BroadcastMode)
-> Access DecodedInstructionAvxBroadcast BroadcastMode
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvxBroadcast -> BroadcastMode
decodedInstructionAvxBroadcastMode
instance Storable DecodedInstructionAvxBroadcast where
alignment :: DecodedInstructionAvxBroadcast -> Int
alignment = Dictionary DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcastStore
sizeOf :: DecodedInstructionAvxBroadcast -> Int
sizeOf = Dictionary DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcastStore
peek :: Ptr DecodedInstructionAvxBroadcast
-> IO DecodedInstructionAvxBroadcast
peek = Dictionary DecodedInstructionAvxBroadcast
-> Ptr DecodedInstructionAvxBroadcast
-> IO DecodedInstructionAvxBroadcast
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcastStore
poke :: Ptr DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast -> IO ()
poke = Dictionary DecodedInstructionAvxBroadcast
-> Ptr DecodedInstructionAvxBroadcast
-> DecodedInstructionAvxBroadcast
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcastStore
data DecodedInstructionAvxMask =
DecodedInstructionAvxMask
{ DecodedInstructionAvxMask -> MaskMode
decodedInstructionAvxMaskMode :: !MaskMode
, DecodedInstructionAvxMask -> Register
decodedInstructionAvxRegister :: !Register
}
deriving stock (Int -> DecodedInstructionAvxMask -> ShowS
[DecodedInstructionAvxMask] -> ShowS
DecodedInstructionAvxMask -> String
(Int -> DecodedInstructionAvxMask -> ShowS)
-> (DecodedInstructionAvxMask -> String)
-> ([DecodedInstructionAvxMask] -> ShowS)
-> Show DecodedInstructionAvxMask
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionAvxMask] -> ShowS
$cshowList :: [DecodedInstructionAvxMask] -> ShowS
show :: DecodedInstructionAvxMask -> String
$cshow :: DecodedInstructionAvxMask -> String
showsPrec :: Int -> DecodedInstructionAvxMask -> ShowS
$cshowsPrec :: Int -> DecodedInstructionAvxMask -> ShowS
Show, DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> Bool
(DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> Bool)
-> (DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> Bool)
-> Eq DecodedInstructionAvxMask
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> Bool
$c/= :: DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> Bool
== :: DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> Bool
$c== :: DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> Bool
Eq)
decodedInstructionAvxMaskStore :: Store.Dictionary DecodedInstructionAvxMask
decodedInstructionAvxMaskStore :: Dictionary DecodedInstructionAvxMask
decodedInstructionAvxMaskStore =
Access DecodedInstructionAvxMask DecodedInstructionAvxMask
-> Dictionary DecodedInstructionAvxMask
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionAvxMask DecodedInstructionAvxMask
-> Dictionary DecodedInstructionAvxMask)
-> Access DecodedInstructionAvxMask DecodedInstructionAvxMask
-> Dictionary DecodedInstructionAvxMask
forall a b. (a -> b) -> a -> b
$ MaskMode -> Register -> DecodedInstructionAvxMask
DecodedInstructionAvxMask
(MaskMode -> Register -> DecodedInstructionAvxMask)
-> Access DecodedInstructionAvxMask MaskMode
-> Access
DecodedInstructionAvxMask (Register -> DecodedInstructionAvxMask)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionAvxMask -> MaskMode)
-> Access DecodedInstructionAvxMask MaskMode
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvxMask -> MaskMode
decodedInstructionAvxMaskMode
Access
DecodedInstructionAvxMask (Register -> DecodedInstructionAvxMask)
-> Access DecodedInstructionAvxMask Register
-> Access DecodedInstructionAvxMask DecodedInstructionAvxMask
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvxMask -> Register)
-> Access DecodedInstructionAvxMask Register
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvxMask -> Register
decodedInstructionAvxRegister
instance Storable DecodedInstructionAvxMask where
alignment :: DecodedInstructionAvxMask -> Int
alignment = Dictionary DecodedInstructionAvxMask
-> DecodedInstructionAvxMask -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionAvxMask
decodedInstructionAvxMaskStore
sizeOf :: DecodedInstructionAvxMask -> Int
sizeOf = Dictionary DecodedInstructionAvxMask
-> DecodedInstructionAvxMask -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionAvxMask
decodedInstructionAvxMaskStore
peek :: Ptr DecodedInstructionAvxMask -> IO DecodedInstructionAvxMask
peek = Dictionary DecodedInstructionAvxMask
-> Ptr DecodedInstructionAvxMask -> IO DecodedInstructionAvxMask
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionAvxMask
decodedInstructionAvxMaskStore
poke :: Ptr DecodedInstructionAvxMask -> DecodedInstructionAvxMask -> IO ()
poke = Dictionary DecodedInstructionAvxMask
-> Ptr DecodedInstructionAvxMask
-> DecodedInstructionAvxMask
-> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionAvxMask
decodedInstructionAvxMaskStore
data DecodedInstructionAvx =
DecodedInstructionAvx
{ DecodedInstructionAvx -> Word16
decodedInstructionAvxVectorLength :: {-# UNPACK #-}!Word16
, DecodedInstructionAvx -> DecodedInstructionAvxMask
decodedInstructionAvxMask :: !DecodedInstructionAvxMask
, DecodedInstructionAvx -> DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcast :: !DecodedInstructionAvxBroadcast
, DecodedInstructionAvx -> RoundingMode
decodedInstructionAvxRoundingMode :: !RoundingMode
, DecodedInstructionAvx -> SwizzleMode
decodedInstructionAvxSwizzleMode :: !SwizzleMode
, DecodedInstructionAvx -> ConversionMode
decodedInstructionAvxConversionMode :: !ConversionMode
, DecodedInstructionAvx -> Word8
decodedInstructionAvxHasSAE :: {-# UNPACK #-}!Word8
, DecodedInstructionAvx -> Word8
decodedInstructionAvxHasEvictionHint :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> DecodedInstructionAvx -> ShowS
[DecodedInstructionAvx] -> ShowS
DecodedInstructionAvx -> String
(Int -> DecodedInstructionAvx -> ShowS)
-> (DecodedInstructionAvx -> String)
-> ([DecodedInstructionAvx] -> ShowS)
-> Show DecodedInstructionAvx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstructionAvx] -> ShowS
$cshowList :: [DecodedInstructionAvx] -> ShowS
show :: DecodedInstructionAvx -> String
$cshow :: DecodedInstructionAvx -> String
showsPrec :: Int -> DecodedInstructionAvx -> ShowS
$cshowsPrec :: Int -> DecodedInstructionAvx -> ShowS
Show, DecodedInstructionAvx -> DecodedInstructionAvx -> Bool
(DecodedInstructionAvx -> DecodedInstructionAvx -> Bool)
-> (DecodedInstructionAvx -> DecodedInstructionAvx -> Bool)
-> Eq DecodedInstructionAvx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstructionAvx -> DecodedInstructionAvx -> Bool
$c/= :: DecodedInstructionAvx -> DecodedInstructionAvx -> Bool
== :: DecodedInstructionAvx -> DecodedInstructionAvx -> Bool
$c== :: DecodedInstructionAvx -> DecodedInstructionAvx -> Bool
Eq)
decodedInstructionAvxStore :: Store.Dictionary DecodedInstructionAvx
decodedInstructionAvxStore :: Dictionary DecodedInstructionAvx
decodedInstructionAvxStore =
Access DecodedInstructionAvx DecodedInstructionAvx
-> Dictionary DecodedInstructionAvx
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstructionAvx DecodedInstructionAvx
-> Dictionary DecodedInstructionAvx)
-> Access DecodedInstructionAvx DecodedInstructionAvx
-> Dictionary DecodedInstructionAvx
forall a b. (a -> b) -> a -> b
$ Word16
-> DecodedInstructionAvxMask
-> DecodedInstructionAvxBroadcast
-> RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx
DecodedInstructionAvx
(Word16
-> DecodedInstructionAvxMask
-> DecodedInstructionAvxBroadcast
-> RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx)
-> Access DecodedInstructionAvx Word16
-> Access
DecodedInstructionAvx
(DecodedInstructionAvxMask
-> DecodedInstructionAvxBroadcast
-> RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstructionAvx -> Word16)
-> Access DecodedInstructionAvx Word16
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> Word16
decodedInstructionAvxVectorLength
Access
DecodedInstructionAvx
(DecodedInstructionAvxMask
-> DecodedInstructionAvxBroadcast
-> RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx)
-> Access DecodedInstructionAvx DecodedInstructionAvxMask
-> Access
DecodedInstructionAvx
(DecodedInstructionAvxBroadcast
-> RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvx -> DecodedInstructionAvxMask)
-> Access DecodedInstructionAvx DecodedInstructionAvxMask
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> DecodedInstructionAvxMask
decodedInstructionAvxMask
Access
DecodedInstructionAvx
(DecodedInstructionAvxBroadcast
-> RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx)
-> Access DecodedInstructionAvx DecodedInstructionAvxBroadcast
-> Access
DecodedInstructionAvx
(RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvx -> DecodedInstructionAvxBroadcast)
-> Access DecodedInstructionAvx DecodedInstructionAvxBroadcast
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> DecodedInstructionAvxBroadcast
decodedInstructionAvxBroadcast
Access
DecodedInstructionAvx
(RoundingMode
-> SwizzleMode
-> ConversionMode
-> Word8
-> Word8
-> DecodedInstructionAvx)
-> Access DecodedInstructionAvx RoundingMode
-> Access
DecodedInstructionAvx
(SwizzleMode
-> ConversionMode -> Word8 -> Word8 -> DecodedInstructionAvx)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvx -> RoundingMode)
-> Access DecodedInstructionAvx RoundingMode
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> RoundingMode
decodedInstructionAvxRoundingMode
Access
DecodedInstructionAvx
(SwizzleMode
-> ConversionMode -> Word8 -> Word8 -> DecodedInstructionAvx)
-> Access DecodedInstructionAvx SwizzleMode
-> Access
DecodedInstructionAvx
(ConversionMode -> Word8 -> Word8 -> DecodedInstructionAvx)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvx -> SwizzleMode)
-> Access DecodedInstructionAvx SwizzleMode
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> SwizzleMode
decodedInstructionAvxSwizzleMode
Access
DecodedInstructionAvx
(ConversionMode -> Word8 -> Word8 -> DecodedInstructionAvx)
-> Access DecodedInstructionAvx ConversionMode
-> Access
DecodedInstructionAvx (Word8 -> Word8 -> DecodedInstructionAvx)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvx -> ConversionMode)
-> Access DecodedInstructionAvx ConversionMode
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> ConversionMode
decodedInstructionAvxConversionMode
Access
DecodedInstructionAvx (Word8 -> Word8 -> DecodedInstructionAvx)
-> Access DecodedInstructionAvx Word8
-> Access DecodedInstructionAvx (Word8 -> DecodedInstructionAvx)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvx -> Word8)
-> Access DecodedInstructionAvx Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> Word8
decodedInstructionAvxHasSAE
Access DecodedInstructionAvx (Word8 -> DecodedInstructionAvx)
-> Access DecodedInstructionAvx Word8
-> Access DecodedInstructionAvx DecodedInstructionAvx
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstructionAvx -> Word8)
-> Access DecodedInstructionAvx Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstructionAvx -> Word8
decodedInstructionAvxHasEvictionHint
instance Storable DecodedInstructionAvx where
alignment :: DecodedInstructionAvx -> Int
alignment = Dictionary DecodedInstructionAvx -> DecodedInstructionAvx -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstructionAvx
decodedInstructionAvxStore
sizeOf :: DecodedInstructionAvx -> Int
sizeOf = Dictionary DecodedInstructionAvx -> DecodedInstructionAvx -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstructionAvx
decodedInstructionAvxStore
peek :: Ptr DecodedInstructionAvx -> IO DecodedInstructionAvx
peek = Dictionary DecodedInstructionAvx
-> Ptr DecodedInstructionAvx -> IO DecodedInstructionAvx
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstructionAvx
decodedInstructionAvxStore
poke :: Ptr DecodedInstructionAvx -> DecodedInstructionAvx -> IO ()
poke = Dictionary DecodedInstructionAvx
-> Ptr DecodedInstructionAvx -> DecodedInstructionAvx -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstructionAvx
decodedInstructionAvxStore
data DecodedInstruction =
DecodedInstruction
{ DecodedInstruction -> MachineMode
decodedInstructionMachineMode :: !MachineMode
, DecodedInstruction -> Mnemonic
decodedInstructionMnemonic :: !Mnemonic
, DecodedInstruction -> Word8
decodedInstructionLength :: {-# UNPACK #-}!Word8
, DecodedInstruction -> InstructionEncoding
decodedInstructionEncoding :: !InstructionEncoding
, DecodedInstruction -> OpcodeMap
decodedInstructionOpcodeMap :: !OpcodeMap
, DecodedInstruction -> Word8
decodedInstructionOpcode :: {-# UNPACK #-}!Word8
, DecodedInstruction -> Word8
decodedInstructionStackWidth :: {-# UNPACK #-}!Word8
, DecodedInstruction -> Word8
decodedInstructionOperandWidth :: {-# UNPACK #-}!Word8
, DecodedInstruction -> Word8
decodedInstructionAddressWidth :: {-# UNPACK #-}!Word8
, DecodedInstruction -> Word8
decodedInstructionOperandCount :: {-# UNPACK #-}!Word8
, DecodedInstruction
-> StorableFixedArray Operand ZydisMaxOperandCount
decodedInstructionOperands :: !(StorableFixedArray Operand ZydisMaxOperandCount)
, DecodedInstruction -> Word64
decodedInstructionAttributes :: {-# UNPACK #-}!Word64
, DecodedInstruction
-> StorableFixedArray CPUFlagAction (ZydisCpuFlagMaxValue + 1)
decodedInstructionAccessedFlags :: !(StorableFixedArray CPUFlagAction (ZydisCpuFlagMaxValue + 1))
, DecodedInstruction -> DecodedInstructionAvx
decodedInstructionAvx :: !DecodedInstructionAvx
, DecodedInstruction -> DecodedInstructionMeta
decodedInstructionMeta :: !DecodedInstructionMeta
, DecodedInstruction -> DecodedInstructionRaw
decodedInstructionRaw :: !DecodedInstructionRaw
}
deriving stock (Int -> DecodedInstruction -> ShowS
[DecodedInstruction] -> ShowS
DecodedInstruction -> String
(Int -> DecodedInstruction -> ShowS)
-> (DecodedInstruction -> String)
-> ([DecodedInstruction] -> ShowS)
-> Show DecodedInstruction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecodedInstruction] -> ShowS
$cshowList :: [DecodedInstruction] -> ShowS
show :: DecodedInstruction -> String
$cshow :: DecodedInstruction -> String
showsPrec :: Int -> DecodedInstruction -> ShowS
$cshowsPrec :: Int -> DecodedInstruction -> ShowS
Show, DecodedInstruction -> DecodedInstruction -> Bool
(DecodedInstruction -> DecodedInstruction -> Bool)
-> (DecodedInstruction -> DecodedInstruction -> Bool)
-> Eq DecodedInstruction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecodedInstruction -> DecodedInstruction -> Bool
$c/= :: DecodedInstruction -> DecodedInstruction -> Bool
== :: DecodedInstruction -> DecodedInstruction -> Bool
$c== :: DecodedInstruction -> DecodedInstruction -> Bool
Eq)
decodedInstructionStore :: Store.Dictionary DecodedInstruction
decodedInstructionStore :: Dictionary DecodedInstruction
decodedInstructionStore =
Access DecodedInstruction DecodedInstruction
-> Dictionary DecodedInstruction
forall r. Access r r -> Dictionary r
Store.run
(Access DecodedInstruction DecodedInstruction
-> Dictionary DecodedInstruction)
-> Access DecodedInstruction DecodedInstruction
-> Dictionary DecodedInstruction
forall a b. (a -> b) -> a -> b
$ MachineMode
-> Mnemonic
-> Word8
-> InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction
MachineMode
-> Mnemonic
-> Word8
-> InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction (ZydisCpuFlagMaxValue + 1)
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction
DecodedInstruction
(MachineMode
-> Mnemonic
-> Word8
-> InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction MachineMode
-> Access
DecodedInstruction
(Mnemonic
-> Word8
-> InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DecodedInstruction -> MachineMode)
-> Access DecodedInstruction MachineMode
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> MachineMode
decodedInstructionMachineMode
Access
DecodedInstruction
(Mnemonic
-> Word8
-> InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Mnemonic
-> Access
DecodedInstruction
(Word8
-> InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Mnemonic)
-> Access DecodedInstruction Mnemonic
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Mnemonic
decodedInstructionMnemonic
Access
DecodedInstruction
(Word8
-> InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Word8
-> Access
DecodedInstruction
(InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Word8) -> Access DecodedInstruction Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Word8
decodedInstructionLength
Access
DecodedInstruction
(InstructionEncoding
-> OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction InstructionEncoding
-> Access
DecodedInstruction
(OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> InstructionEncoding)
-> Access DecodedInstruction InstructionEncoding
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> InstructionEncoding
decodedInstructionEncoding
Access
DecodedInstruction
(OpcodeMap
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction OpcodeMap
-> Access
DecodedInstruction
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> OpcodeMap)
-> Access DecodedInstruction OpcodeMap
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> OpcodeMap
decodedInstructionOpcodeMap
Access
DecodedInstruction
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Word8
-> Access
DecodedInstruction
(Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Word8) -> Access DecodedInstruction Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Word8
decodedInstructionOpcode
Access
DecodedInstruction
(Word8
-> Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Word8
-> Access
DecodedInstruction
(Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Word8) -> Access DecodedInstruction Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Word8
decodedInstructionStackWidth
Access
DecodedInstruction
(Word8
-> Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Word8
-> Access
DecodedInstruction
(Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Word8) -> Access DecodedInstruction Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Word8
decodedInstructionOperandWidth
Access
DecodedInstruction
(Word8
-> Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Word8
-> Access
DecodedInstruction
(Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Word8) -> Access DecodedInstruction Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Word8
decodedInstructionAddressWidth
Access
DecodedInstruction
(Word8
-> StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Word8
-> Access
DecodedInstruction
(StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Word8) -> Access DecodedInstruction Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Word8
decodedInstructionOperandCount
Access
DecodedInstruction
(StorableFixedArray Operand ZydisMaxOperandCount
-> Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access
DecodedInstruction
(StorableFixedArray Operand ZydisMaxOperandCount)
-> Access
DecodedInstruction
(Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction
-> StorableFixedArray Operand ZydisMaxOperandCount)
-> Access
DecodedInstruction
(StorableFixedArray Operand ZydisMaxOperandCount)
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction
-> StorableFixedArray Operand ZydisMaxOperandCount
decodedInstructionOperands
Access
DecodedInstruction
(Word64
-> StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction Word64
-> Access
DecodedInstruction
(StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> Word64) -> Access DecodedInstruction Word64
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> Word64
decodedInstructionAttributes
Access
DecodedInstruction
(StorableFixedArray CPUFlagAction 22
-> DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction (StorableFixedArray CPUFlagAction 22)
-> Access
DecodedInstruction
(DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> StorableFixedArray CPUFlagAction 22)
-> Access DecodedInstruction (StorableFixedArray CPUFlagAction 22)
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> StorableFixedArray CPUFlagAction 22
DecodedInstruction
-> StorableFixedArray CPUFlagAction (ZydisCpuFlagMaxValue + 1)
decodedInstructionAccessedFlags
Access
DecodedInstruction
(DecodedInstructionAvx
-> DecodedInstructionMeta
-> DecodedInstructionRaw
-> DecodedInstruction)
-> Access DecodedInstruction DecodedInstructionAvx
-> Access
DecodedInstruction
(DecodedInstructionMeta
-> DecodedInstructionRaw -> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> DecodedInstructionAvx)
-> Access DecodedInstruction DecodedInstructionAvx
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> DecodedInstructionAvx
decodedInstructionAvx
Access
DecodedInstruction
(DecodedInstructionMeta
-> DecodedInstructionRaw -> DecodedInstruction)
-> Access DecodedInstruction DecodedInstructionMeta
-> Access
DecodedInstruction (DecodedInstructionRaw -> DecodedInstruction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> DecodedInstructionMeta)
-> Access DecodedInstruction DecodedInstructionMeta
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> DecodedInstructionMeta
decodedInstructionMeta
Access
DecodedInstruction (DecodedInstructionRaw -> DecodedInstruction)
-> Access DecodedInstruction DecodedInstructionRaw
-> Access DecodedInstruction DecodedInstruction
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (DecodedInstruction -> DecodedInstructionRaw)
-> Access DecodedInstruction DecodedInstructionRaw
forall a r. Storable a => (r -> a) -> Access r a
Store.element DecodedInstruction -> DecodedInstructionRaw
decodedInstructionRaw
instance Storable DecodedInstruction where
alignment :: DecodedInstruction -> Int
alignment = Dictionary DecodedInstruction -> DecodedInstruction -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary DecodedInstruction
decodedInstructionStore
sizeOf :: DecodedInstruction -> Int
sizeOf = Dictionary DecodedInstruction -> DecodedInstruction -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary DecodedInstruction
decodedInstructionStore
peek :: Ptr DecodedInstruction -> IO DecodedInstruction
peek = Dictionary DecodedInstruction
-> Ptr DecodedInstruction -> IO DecodedInstruction
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary DecodedInstruction
decodedInstructionStore
poke :: Ptr DecodedInstruction -> DecodedInstruction -> IO ()
poke = Dictionary DecodedInstruction
-> Ptr DecodedInstruction -> DecodedInstruction -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary DecodedInstruction
decodedInstructionStore
data Decoder =
Decoder
{ Decoder -> MachineMode
decoderMachineMode :: !MachineMode
, Decoder -> AddressWidth
decoderAddressWidth :: !AddressWidth
, Decoder -> Word8
decoderDecoderMode :: {-# UNPACK #-}!Word8
}
deriving stock (Int -> Decoder -> ShowS
[Decoder] -> ShowS
Decoder -> String
(Int -> Decoder -> ShowS)
-> (Decoder -> String) -> ([Decoder] -> ShowS) -> Show Decoder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Decoder] -> ShowS
$cshowList :: [Decoder] -> ShowS
show :: Decoder -> String
$cshow :: Decoder -> String
showsPrec :: Int -> Decoder -> ShowS
$cshowsPrec :: Int -> Decoder -> ShowS
Show, Decoder -> Decoder -> Bool
(Decoder -> Decoder -> Bool)
-> (Decoder -> Decoder -> Bool) -> Eq Decoder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Decoder -> Decoder -> Bool
$c/= :: Decoder -> Decoder -> Bool
== :: Decoder -> Decoder -> Bool
$c== :: Decoder -> Decoder -> Bool
Eq)
decoderStore :: Store.Dictionary Decoder
decoderStore :: Dictionary Decoder
decoderStore =
Access Decoder Decoder -> Dictionary Decoder
forall r. Access r r -> Dictionary r
Store.run
(Access Decoder Decoder -> Dictionary Decoder)
-> Access Decoder Decoder -> Dictionary Decoder
forall a b. (a -> b) -> a -> b
$ MachineMode -> AddressWidth -> Word8 -> Decoder
Decoder
(MachineMode -> AddressWidth -> Word8 -> Decoder)
-> Access Decoder MachineMode
-> Access Decoder (AddressWidth -> Word8 -> Decoder)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Decoder -> MachineMode) -> Access Decoder MachineMode
forall a r. Storable a => (r -> a) -> Access r a
Store.element Decoder -> MachineMode
decoderMachineMode
Access Decoder (AddressWidth -> Word8 -> Decoder)
-> Access Decoder AddressWidth -> Access Decoder (Word8 -> Decoder)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Decoder -> AddressWidth) -> Access Decoder AddressWidth
forall a r. Storable a => (r -> a) -> Access r a
Store.element Decoder -> AddressWidth
decoderAddressWidth
Access Decoder (Word8 -> Decoder)
-> Access Decoder Word8 -> Access Decoder Decoder
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Decoder -> Word8) -> Access Decoder Word8
forall a r. Storable a => (r -> a) -> Access r a
Store.element Decoder -> Word8
decoderDecoderMode
instance Storable Decoder where
alignment :: Decoder -> Int
alignment = Dictionary Decoder -> Decoder -> Int
forall r. Dictionary r -> r -> Int
Store.alignment Dictionary Decoder
decoderStore
sizeOf :: Decoder -> Int
sizeOf = Dictionary Decoder -> Decoder -> Int
forall r. Dictionary r -> r -> Int
Store.sizeOf Dictionary Decoder
decoderStore
peek :: Ptr Decoder -> IO Decoder
peek = Dictionary Decoder -> Ptr Decoder -> IO Decoder
forall r. Dictionary r -> Ptr r -> IO r
Store.peek Dictionary Decoder
decoderStore
poke :: Ptr Decoder -> Decoder -> IO ()
poke = Dictionary Decoder -> Ptr Decoder -> Decoder -> IO ()
forall r. Dictionary r -> Ptr r -> r -> IO ()
Store.poke Dictionary Decoder
decoderStore