{-# language CPP #-}
module Vulkan.Core10.Enums.MemoryMapFlags (MemoryMapFlags(..)) where
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Vulkan.Core10.FundamentalTypes (Flags)
newtype MemoryMapFlags = MemoryMapFlags Flags
deriving newtype (MemoryMapFlags -> MemoryMapFlags -> Bool
(MemoryMapFlags -> MemoryMapFlags -> Bool)
-> (MemoryMapFlags -> MemoryMapFlags -> Bool) -> Eq MemoryMapFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemoryMapFlags -> MemoryMapFlags -> Bool
== :: MemoryMapFlags -> MemoryMapFlags -> Bool
$c/= :: MemoryMapFlags -> MemoryMapFlags -> Bool
/= :: MemoryMapFlags -> MemoryMapFlags -> Bool
Eq, Eq MemoryMapFlags
Eq MemoryMapFlags =>
(MemoryMapFlags -> MemoryMapFlags -> Ordering)
-> (MemoryMapFlags -> MemoryMapFlags -> Bool)
-> (MemoryMapFlags -> MemoryMapFlags -> Bool)
-> (MemoryMapFlags -> MemoryMapFlags -> Bool)
-> (MemoryMapFlags -> MemoryMapFlags -> Bool)
-> (MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags)
-> (MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags)
-> Ord MemoryMapFlags
MemoryMapFlags -> MemoryMapFlags -> Bool
MemoryMapFlags -> MemoryMapFlags -> Ordering
MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MemoryMapFlags -> MemoryMapFlags -> Ordering
compare :: MemoryMapFlags -> MemoryMapFlags -> Ordering
$c< :: MemoryMapFlags -> MemoryMapFlags -> Bool
< :: MemoryMapFlags -> MemoryMapFlags -> Bool
$c<= :: MemoryMapFlags -> MemoryMapFlags -> Bool
<= :: MemoryMapFlags -> MemoryMapFlags -> Bool
$c> :: MemoryMapFlags -> MemoryMapFlags -> Bool
> :: MemoryMapFlags -> MemoryMapFlags -> Bool
$c>= :: MemoryMapFlags -> MemoryMapFlags -> Bool
>= :: MemoryMapFlags -> MemoryMapFlags -> Bool
$cmax :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
max :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$cmin :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
min :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
Ord, Ptr MemoryMapFlags -> IO MemoryMapFlags
Ptr MemoryMapFlags -> Int -> IO MemoryMapFlags
Ptr MemoryMapFlags -> Int -> MemoryMapFlags -> IO ()
Ptr MemoryMapFlags -> MemoryMapFlags -> IO ()
MemoryMapFlags -> Int
(MemoryMapFlags -> Int)
-> (MemoryMapFlags -> Int)
-> (Ptr MemoryMapFlags -> Int -> IO MemoryMapFlags)
-> (Ptr MemoryMapFlags -> Int -> MemoryMapFlags -> IO ())
-> (forall b. Ptr b -> Int -> IO MemoryMapFlags)
-> (forall b. Ptr b -> Int -> MemoryMapFlags -> IO ())
-> (Ptr MemoryMapFlags -> IO MemoryMapFlags)
-> (Ptr MemoryMapFlags -> MemoryMapFlags -> IO ())
-> Storable MemoryMapFlags
forall b. Ptr b -> Int -> IO MemoryMapFlags
forall b. Ptr b -> Int -> MemoryMapFlags -> 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
$csizeOf :: MemoryMapFlags -> Int
sizeOf :: MemoryMapFlags -> Int
$calignment :: MemoryMapFlags -> Int
alignment :: MemoryMapFlags -> Int
$cpeekElemOff :: Ptr MemoryMapFlags -> Int -> IO MemoryMapFlags
peekElemOff :: Ptr MemoryMapFlags -> Int -> IO MemoryMapFlags
$cpokeElemOff :: Ptr MemoryMapFlags -> Int -> MemoryMapFlags -> IO ()
pokeElemOff :: Ptr MemoryMapFlags -> Int -> MemoryMapFlags -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryMapFlags
peekByteOff :: forall b. Ptr b -> Int -> IO MemoryMapFlags
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryMapFlags -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> MemoryMapFlags -> IO ()
$cpeek :: Ptr MemoryMapFlags -> IO MemoryMapFlags
peek :: Ptr MemoryMapFlags -> IO MemoryMapFlags
$cpoke :: Ptr MemoryMapFlags -> MemoryMapFlags -> IO ()
poke :: Ptr MemoryMapFlags -> MemoryMapFlags -> IO ()
Storable, MemoryMapFlags
MemoryMapFlags -> Zero MemoryMapFlags
forall a. a -> Zero a
$czero :: MemoryMapFlags
zero :: MemoryMapFlags
Zero, Eq MemoryMapFlags
MemoryMapFlags
Eq MemoryMapFlags =>
(MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags)
-> (MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags)
-> (MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags)
-> (MemoryMapFlags -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> MemoryMapFlags
-> (Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> Bool)
-> (MemoryMapFlags -> Maybe Int)
-> (MemoryMapFlags -> Int)
-> (MemoryMapFlags -> Bool)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int -> MemoryMapFlags)
-> (MemoryMapFlags -> Int)
-> Bits MemoryMapFlags
Int -> MemoryMapFlags
MemoryMapFlags -> Bool
MemoryMapFlags -> Int
MemoryMapFlags -> Maybe Int
MemoryMapFlags -> MemoryMapFlags
MemoryMapFlags -> Int -> Bool
MemoryMapFlags -> Int -> MemoryMapFlags
MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
.&. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$c.|. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
.|. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$cxor :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
xor :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$ccomplement :: MemoryMapFlags -> MemoryMapFlags
complement :: MemoryMapFlags -> MemoryMapFlags
$cshift :: MemoryMapFlags -> Int -> MemoryMapFlags
shift :: MemoryMapFlags -> Int -> MemoryMapFlags
$crotate :: MemoryMapFlags -> Int -> MemoryMapFlags
rotate :: MemoryMapFlags -> Int -> MemoryMapFlags
$czeroBits :: MemoryMapFlags
zeroBits :: MemoryMapFlags
$cbit :: Int -> MemoryMapFlags
bit :: Int -> MemoryMapFlags
$csetBit :: MemoryMapFlags -> Int -> MemoryMapFlags
setBit :: MemoryMapFlags -> Int -> MemoryMapFlags
$cclearBit :: MemoryMapFlags -> Int -> MemoryMapFlags
clearBit :: MemoryMapFlags -> Int -> MemoryMapFlags
$ccomplementBit :: MemoryMapFlags -> Int -> MemoryMapFlags
complementBit :: MemoryMapFlags -> Int -> MemoryMapFlags
$ctestBit :: MemoryMapFlags -> Int -> Bool
testBit :: MemoryMapFlags -> Int -> Bool
$cbitSizeMaybe :: MemoryMapFlags -> Maybe Int
bitSizeMaybe :: MemoryMapFlags -> Maybe Int
$cbitSize :: MemoryMapFlags -> Int
bitSize :: MemoryMapFlags -> Int
$cisSigned :: MemoryMapFlags -> Bool
isSigned :: MemoryMapFlags -> Bool
$cshiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
shiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
$cunsafeShiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
unsafeShiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
$cshiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
shiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
$cunsafeShiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
unsafeShiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
$crotateL :: MemoryMapFlags -> Int -> MemoryMapFlags
rotateL :: MemoryMapFlags -> Int -> MemoryMapFlags
$crotateR :: MemoryMapFlags -> Int -> MemoryMapFlags
rotateR :: MemoryMapFlags -> Int -> MemoryMapFlags
$cpopCount :: MemoryMapFlags -> Int
popCount :: MemoryMapFlags -> Int
Bits, Bits MemoryMapFlags
Bits MemoryMapFlags =>
(MemoryMapFlags -> Int)
-> (MemoryMapFlags -> Int)
-> (MemoryMapFlags -> Int)
-> FiniteBits MemoryMapFlags
MemoryMapFlags -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: MemoryMapFlags -> Int
finiteBitSize :: MemoryMapFlags -> Int
$ccountLeadingZeros :: MemoryMapFlags -> Int
countLeadingZeros :: MemoryMapFlags -> Int
$ccountTrailingZeros :: MemoryMapFlags -> Int
countTrailingZeros :: MemoryMapFlags -> Int
FiniteBits)
conNameMemoryMapFlags :: String
conNameMemoryMapFlags :: String
conNameMemoryMapFlags = String
"MemoryMapFlags"
enumPrefixMemoryMapFlags :: String
enumPrefixMemoryMapFlags :: String
enumPrefixMemoryMapFlags = String
""
showTableMemoryMapFlags :: [(MemoryMapFlags, String)]
showTableMemoryMapFlags :: [(MemoryMapFlags, String)]
showTableMemoryMapFlags = []
instance Show MemoryMapFlags where
showsPrec :: Int -> MemoryMapFlags -> ShowS
showsPrec =
String
-> [(MemoryMapFlags, String)]
-> String
-> (MemoryMapFlags -> Flags)
-> (Flags -> ShowS)
-> Int
-> MemoryMapFlags
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixMemoryMapFlags
[(MemoryMapFlags, String)]
showTableMemoryMapFlags
String
conNameMemoryMapFlags
(\(MemoryMapFlags Flags
x) -> Flags
x)
(\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. Integral a => a -> ShowS
showHex Flags
x)
instance Read MemoryMapFlags where
readPrec :: ReadPrec MemoryMapFlags
readPrec =
String
-> [(MemoryMapFlags, String)]
-> String
-> (Flags -> MemoryMapFlags)
-> ReadPrec MemoryMapFlags
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixMemoryMapFlags
[(MemoryMapFlags, String)]
showTableMemoryMapFlags
String
conNameMemoryMapFlags
Flags -> MemoryMapFlags
MemoryMapFlags