{-# language CPP #-}
-- No documentation found for Chapter "MemoryMapFlags"
module Vulkan.Core10.Enums.MemoryMapFlags  (MemoryMapFlags(..)) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Vulkan.Core10.FundamentalTypes (Flags)
-- | VkMemoryMapFlags - Reserved for future use
--
-- = Description
--
-- 'MemoryMapFlags' is a bitmask type for setting a mask, but is currently
-- reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.Memory.mapMemory'
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
/= :: MemoryMapFlags -> MemoryMapFlags -> Bool
$c/= :: MemoryMapFlags -> MemoryMapFlags -> Bool
== :: MemoryMapFlags -> MemoryMapFlags -> Bool
$c== :: 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
min :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$cmin :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
max :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$cmax :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
>= :: MemoryMapFlags -> MemoryMapFlags -> Bool
$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
compare :: MemoryMapFlags -> MemoryMapFlags -> Ordering
$ccompare :: MemoryMapFlags -> MemoryMapFlags -> Ordering
$cp1Ord :: Eq MemoryMapFlags
Ord, Ptr b -> Int -> IO MemoryMapFlags
Ptr b -> Int -> MemoryMapFlags -> IO ()
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
poke :: Ptr MemoryMapFlags -> MemoryMapFlags -> IO ()
$cpoke :: Ptr MemoryMapFlags -> MemoryMapFlags -> IO ()
peek :: Ptr MemoryMapFlags -> IO MemoryMapFlags
$cpeek :: Ptr MemoryMapFlags -> IO MemoryMapFlags
pokeByteOff :: Ptr b -> Int -> MemoryMapFlags -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryMapFlags -> IO ()
peekByteOff :: Ptr b -> Int -> IO MemoryMapFlags
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryMapFlags
pokeElemOff :: Ptr MemoryMapFlags -> Int -> MemoryMapFlags -> IO ()
$cpokeElemOff :: Ptr MemoryMapFlags -> Int -> MemoryMapFlags -> IO ()
peekElemOff :: Ptr MemoryMapFlags -> Int -> IO MemoryMapFlags
$cpeekElemOff :: Ptr MemoryMapFlags -> Int -> IO MemoryMapFlags
alignment :: MemoryMapFlags -> Int
$calignment :: MemoryMapFlags -> Int
sizeOf :: MemoryMapFlags -> Int
$csizeOf :: MemoryMapFlags -> Int
Storable, MemoryMapFlags
MemoryMapFlags -> Zero MemoryMapFlags
forall a. a -> Zero a
zero :: MemoryMapFlags
$czero :: 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
popCount :: MemoryMapFlags -> Int
$cpopCount :: MemoryMapFlags -> Int
rotateR :: MemoryMapFlags -> Int -> MemoryMapFlags
$crotateR :: MemoryMapFlags -> Int -> MemoryMapFlags
rotateL :: MemoryMapFlags -> Int -> MemoryMapFlags
$crotateL :: MemoryMapFlags -> Int -> MemoryMapFlags
unsafeShiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
$cunsafeShiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
shiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
$cshiftR :: MemoryMapFlags -> Int -> MemoryMapFlags
unsafeShiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
$cunsafeShiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
shiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
$cshiftL :: MemoryMapFlags -> Int -> MemoryMapFlags
isSigned :: MemoryMapFlags -> Bool
$cisSigned :: MemoryMapFlags -> Bool
bitSize :: MemoryMapFlags -> Int
$cbitSize :: MemoryMapFlags -> Int
bitSizeMaybe :: MemoryMapFlags -> Maybe Int
$cbitSizeMaybe :: MemoryMapFlags -> Maybe Int
testBit :: MemoryMapFlags -> Int -> Bool
$ctestBit :: MemoryMapFlags -> Int -> Bool
complementBit :: MemoryMapFlags -> Int -> MemoryMapFlags
$ccomplementBit :: MemoryMapFlags -> Int -> MemoryMapFlags
clearBit :: MemoryMapFlags -> Int -> MemoryMapFlags
$cclearBit :: MemoryMapFlags -> Int -> MemoryMapFlags
setBit :: MemoryMapFlags -> Int -> MemoryMapFlags
$csetBit :: MemoryMapFlags -> Int -> MemoryMapFlags
bit :: Int -> MemoryMapFlags
$cbit :: Int -> MemoryMapFlags
zeroBits :: MemoryMapFlags
$czeroBits :: MemoryMapFlags
rotate :: MemoryMapFlags -> Int -> MemoryMapFlags
$crotate :: MemoryMapFlags -> Int -> MemoryMapFlags
shift :: MemoryMapFlags -> Int -> MemoryMapFlags
$cshift :: MemoryMapFlags -> Int -> MemoryMapFlags
complement :: MemoryMapFlags -> MemoryMapFlags
$ccomplement :: MemoryMapFlags -> MemoryMapFlags
xor :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$cxor :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
.|. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$c.|. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
.&. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$c.&. :: MemoryMapFlags -> MemoryMapFlags -> MemoryMapFlags
$cp1Bits :: Eq MemoryMapFlags
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
countTrailingZeros :: MemoryMapFlags -> Int
$ccountTrailingZeros :: MemoryMapFlags -> Int
countLeadingZeros :: MemoryMapFlags -> Int
$ccountLeadingZeros :: MemoryMapFlags -> Int
finiteBitSize :: MemoryMapFlags -> Int
$cfiniteBitSize :: MemoryMapFlags -> Int
$cp1FiniteBits :: Bits MemoryMapFlags
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, Show 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