{-# LANGUAGE DerivingVia #-}
module Zydis.OperandVisibility
( OperandVisibility(..)
)
where
import Zydis.Util
data OperandVisibility
= OperandVisibilityInvalid
| OperandVisibilityExplicit
| OperandVisibilityImplicit
| OperandVisibilityHidden
deriving stock (Int -> OperandVisibility -> ShowS
[OperandVisibility] -> ShowS
OperandVisibility -> String
(Int -> OperandVisibility -> ShowS)
-> (OperandVisibility -> String)
-> ([OperandVisibility] -> ShowS)
-> Show OperandVisibility
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperandVisibility] -> ShowS
$cshowList :: [OperandVisibility] -> ShowS
show :: OperandVisibility -> String
$cshow :: OperandVisibility -> String
showsPrec :: Int -> OperandVisibility -> ShowS
$cshowsPrec :: Int -> OperandVisibility -> ShowS
Show, OperandVisibility -> OperandVisibility -> Bool
(OperandVisibility -> OperandVisibility -> Bool)
-> (OperandVisibility -> OperandVisibility -> Bool)
-> Eq OperandVisibility
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperandVisibility -> OperandVisibility -> Bool
$c/= :: OperandVisibility -> OperandVisibility -> Bool
== :: OperandVisibility -> OperandVisibility -> Bool
$c== :: OperandVisibility -> OperandVisibility -> Bool
Eq, OperandVisibility
OperandVisibility -> OperandVisibility -> Bounded OperandVisibility
forall a. a -> a -> Bounded a
maxBound :: OperandVisibility
$cmaxBound :: OperandVisibility
minBound :: OperandVisibility
$cminBound :: OperandVisibility
Bounded, Int -> OperandVisibility
OperandVisibility -> Int
OperandVisibility -> [OperandVisibility]
OperandVisibility -> OperandVisibility
OperandVisibility -> OperandVisibility -> [OperandVisibility]
OperandVisibility
-> OperandVisibility -> OperandVisibility -> [OperandVisibility]
(OperandVisibility -> OperandVisibility)
-> (OperandVisibility -> OperandVisibility)
-> (Int -> OperandVisibility)
-> (OperandVisibility -> Int)
-> (OperandVisibility -> [OperandVisibility])
-> (OperandVisibility -> OperandVisibility -> [OperandVisibility])
-> (OperandVisibility -> OperandVisibility -> [OperandVisibility])
-> (OperandVisibility
-> OperandVisibility -> OperandVisibility -> [OperandVisibility])
-> Enum OperandVisibility
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: OperandVisibility
-> OperandVisibility -> OperandVisibility -> [OperandVisibility]
$cenumFromThenTo :: OperandVisibility
-> OperandVisibility -> OperandVisibility -> [OperandVisibility]
enumFromTo :: OperandVisibility -> OperandVisibility -> [OperandVisibility]
$cenumFromTo :: OperandVisibility -> OperandVisibility -> [OperandVisibility]
enumFromThen :: OperandVisibility -> OperandVisibility -> [OperandVisibility]
$cenumFromThen :: OperandVisibility -> OperandVisibility -> [OperandVisibility]
enumFrom :: OperandVisibility -> [OperandVisibility]
$cenumFrom :: OperandVisibility -> [OperandVisibility]
fromEnum :: OperandVisibility -> Int
$cfromEnum :: OperandVisibility -> Int
toEnum :: Int -> OperandVisibility
$ctoEnum :: Int -> OperandVisibility
pred :: OperandVisibility -> OperandVisibility
$cpred :: OperandVisibility -> OperandVisibility
succ :: OperandVisibility -> OperandVisibility
$csucc :: OperandVisibility -> OperandVisibility
Enum)
deriving Ptr b -> Int -> IO OperandVisibility
Ptr b -> Int -> OperandVisibility -> IO ()
Ptr OperandVisibility -> IO OperandVisibility
Ptr OperandVisibility -> Int -> IO OperandVisibility
Ptr OperandVisibility -> Int -> OperandVisibility -> IO ()
Ptr OperandVisibility -> OperandVisibility -> IO ()
OperandVisibility -> Int
(OperandVisibility -> Int)
-> (OperandVisibility -> Int)
-> (Ptr OperandVisibility -> Int -> IO OperandVisibility)
-> (Ptr OperandVisibility -> Int -> OperandVisibility -> IO ())
-> (forall b. Ptr b -> Int -> IO OperandVisibility)
-> (forall b. Ptr b -> Int -> OperandVisibility -> IO ())
-> (Ptr OperandVisibility -> IO OperandVisibility)
-> (Ptr OperandVisibility -> OperandVisibility -> IO ())
-> Storable OperandVisibility
forall b. Ptr b -> Int -> IO OperandVisibility
forall b. Ptr b -> Int -> OperandVisibility -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr OperandVisibility -> OperandVisibility -> IO ()
$cpoke :: Ptr OperandVisibility -> OperandVisibility -> IO ()
peek :: Ptr OperandVisibility -> IO OperandVisibility
$cpeek :: Ptr OperandVisibility -> IO OperandVisibility
pokeByteOff :: Ptr b -> Int -> OperandVisibility -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> OperandVisibility -> IO ()
peekByteOff :: Ptr b -> Int -> IO OperandVisibility
$cpeekByteOff :: forall b. Ptr b -> Int -> IO OperandVisibility
pokeElemOff :: Ptr OperandVisibility -> Int -> OperandVisibility -> IO ()
$cpokeElemOff :: Ptr OperandVisibility -> Int -> OperandVisibility -> IO ()
peekElemOff :: Ptr OperandVisibility -> Int -> IO OperandVisibility
$cpeekElemOff :: Ptr OperandVisibility -> Int -> IO OperandVisibility
alignment :: OperandVisibility -> Int
$calignment :: OperandVisibility -> Int
sizeOf :: OperandVisibility -> Int
$csizeOf :: OperandVisibility -> Int
Storable via StorableExt OperandVisibility