{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE Strict                     #-}
{-# LANGUAGE TypeSynonymInstances       #-}
module Graphics.Vulkan.Types.Enum.Memory
       (VkMemoryAllocateFlagBitsKHR(..),
        VkMemoryAllocateBitmask(VkMemoryAllocateBitmask,
                                VkMemoryAllocateFlags, VkMemoryAllocateFlagBits,
                                VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT),
        VkMemoryAllocateFlags, VkMemoryAllocateFlagBits,
        VkMemoryHeapBitmask(VkMemoryHeapBitmask, VkMemoryHeapFlags,
                            VkMemoryHeapFlagBits, VK_MEMORY_HEAP_DEVICE_LOCAL_BIT),
        VkMemoryHeapFlags, VkMemoryHeapFlagBits,
        VkMemoryOverallocationBehaviorAMD(VkMemoryOverallocationBehaviorAMD,
                                          VK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD,
                                          VK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD,
                                          VK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD),
        VkMemoryPropertyBitmask(VkMemoryPropertyBitmask,
                                VkMemoryPropertyFlags, VkMemoryPropertyFlagBits,
                                VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT,
                                VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT,
                                VK_MEMORY_PROPERTY_HOST_COHERENT_BIT,
                                VK_MEMORY_PROPERTY_HOST_CACHED_BIT,
                                VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT),
        VkMemoryPropertyFlags, VkMemoryPropertyFlagBits)
       where
import Data.Bits                       (Bits, FiniteBits)
import Data.Coerce                     (coerce)
import Foreign.Storable                (Storable)
import GHC.Read                        (choose, expectP)
import Graphics.Vulkan.Marshal         (FlagBit, FlagMask, FlagType, Int32)
import Graphics.Vulkan.Types.BaseTypes (VkFlags (..))
import Text.ParserCombinators.ReadPrec (prec, step, (+++))
import Text.Read                       (Read (..), parens)
import Text.Read.Lex                   (Lexeme (..))

newtype VkMemoryAllocateFlagBitsKHR = VkMemoryAllocateFlagBitsKHR VkFlags
                                      deriving (VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
(VkMemoryAllocateFlagBitsKHR
 -> VkMemoryAllocateFlagBitsKHR -> Bool)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> Bool)
-> Eq VkMemoryAllocateFlagBitsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
$c/= :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
== :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
$c== :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
Eq, Eq VkMemoryAllocateFlagBitsKHR
Eq VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> Ordering)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> Bool)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> Bool)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> Bool)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> Bool)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> Ord VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> Ordering
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
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 :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cmin :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
max :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cmax :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
>= :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
$c>= :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
> :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
$c> :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
<= :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
$c<= :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
< :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
$c< :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR -> Bool
compare :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> Ordering
$ccompare :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> Ordering
Ord, Int -> VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> Int
VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> [VkMemoryAllocateFlagBitsKHR]
(VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> Int)
-> (VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR])
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR])
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR])
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR
    -> [VkMemoryAllocateFlagBitsKHR])
-> Enum VkMemoryAllocateFlagBitsKHR
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 :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> [VkMemoryAllocateFlagBitsKHR]
$cenumFromThenTo :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> [VkMemoryAllocateFlagBitsKHR]
enumFromTo :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
$cenumFromTo :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
enumFromThen :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
$cenumFromThen :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
enumFrom :: VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
$cenumFrom :: VkMemoryAllocateFlagBitsKHR -> [VkMemoryAllocateFlagBitsKHR]
fromEnum :: VkMemoryAllocateFlagBitsKHR -> Int
$cfromEnum :: VkMemoryAllocateFlagBitsKHR -> Int
toEnum :: Int -> VkMemoryAllocateFlagBitsKHR
$ctoEnum :: Int -> VkMemoryAllocateFlagBitsKHR
pred :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cpred :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
succ :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$csucc :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
Enum, Eq VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR
Eq VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> VkMemoryAllocateFlagBitsKHR
-> (Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> Int -> Bool)
-> (VkMemoryAllocateFlagBitsKHR -> Maybe Int)
-> (VkMemoryAllocateFlagBitsKHR -> Int)
-> (VkMemoryAllocateFlagBitsKHR -> Bool)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> Int)
-> Bits VkMemoryAllocateFlagBitsKHR
Int -> VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> Bool
VkMemoryAllocateFlagBitsKHR -> Int
VkMemoryAllocateFlagBitsKHR -> Maybe Int
VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> Int -> Bool
VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
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 :: VkMemoryAllocateFlagBitsKHR -> Int
$cpopCount :: VkMemoryAllocateFlagBitsKHR -> Int
rotateR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$crotateR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
rotateL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$crotateL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
unsafeShiftR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$cunsafeShiftR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
shiftR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$cshiftR :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
unsafeShiftL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$cunsafeShiftL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
shiftL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$cshiftL :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
isSigned :: VkMemoryAllocateFlagBitsKHR -> Bool
$cisSigned :: VkMemoryAllocateFlagBitsKHR -> Bool
bitSize :: VkMemoryAllocateFlagBitsKHR -> Int
$cbitSize :: VkMemoryAllocateFlagBitsKHR -> Int
bitSizeMaybe :: VkMemoryAllocateFlagBitsKHR -> Maybe Int
$cbitSizeMaybe :: VkMemoryAllocateFlagBitsKHR -> Maybe Int
testBit :: VkMemoryAllocateFlagBitsKHR -> Int -> Bool
$ctestBit :: VkMemoryAllocateFlagBitsKHR -> Int -> Bool
complementBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$ccomplementBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
clearBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$cclearBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
setBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$csetBit :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
bit :: Int -> VkMemoryAllocateFlagBitsKHR
$cbit :: Int -> VkMemoryAllocateFlagBitsKHR
zeroBits :: VkMemoryAllocateFlagBitsKHR
$czeroBits :: VkMemoryAllocateFlagBitsKHR
rotate :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$crotate :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
shift :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
$cshift :: VkMemoryAllocateFlagBitsKHR -> Int -> VkMemoryAllocateFlagBitsKHR
complement :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$ccomplement :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
xor :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cxor :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
.|. :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$c.|. :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
.&. :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$c.&. :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
Bits, Bits VkMemoryAllocateFlagBitsKHR
Bits VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR -> Int)
-> (VkMemoryAllocateFlagBitsKHR -> Int)
-> (VkMemoryAllocateFlagBitsKHR -> Int)
-> FiniteBits VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: VkMemoryAllocateFlagBitsKHR -> Int
$ccountTrailingZeros :: VkMemoryAllocateFlagBitsKHR -> Int
countLeadingZeros :: VkMemoryAllocateFlagBitsKHR -> Int
$ccountLeadingZeros :: VkMemoryAllocateFlagBitsKHR -> Int
finiteBitSize :: VkMemoryAllocateFlagBitsKHR -> Int
$cfiniteBitSize :: VkMemoryAllocateFlagBitsKHR -> Int
FiniteBits, Ptr VkMemoryAllocateFlagBitsKHR -> IO VkMemoryAllocateFlagBitsKHR
Ptr VkMemoryAllocateFlagBitsKHR
-> Int -> IO VkMemoryAllocateFlagBitsKHR
Ptr VkMemoryAllocateFlagBitsKHR
-> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
Ptr VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> IO ()
VkMemoryAllocateFlagBitsKHR -> Int
(VkMemoryAllocateFlagBitsKHR -> Int)
-> (VkMemoryAllocateFlagBitsKHR -> Int)
-> (Ptr VkMemoryAllocateFlagBitsKHR
    -> Int -> IO VkMemoryAllocateFlagBitsKHR)
-> (Ptr VkMemoryAllocateFlagBitsKHR
    -> Int -> VkMemoryAllocateFlagBitsKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkMemoryAllocateFlagBitsKHR)
-> (forall b. Ptr b -> Int -> VkMemoryAllocateFlagBitsKHR -> IO ())
-> (Ptr VkMemoryAllocateFlagBitsKHR
    -> IO VkMemoryAllocateFlagBitsKHR)
-> (Ptr VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> IO ())
-> Storable VkMemoryAllocateFlagBitsKHR
forall b. Ptr b -> Int -> IO VkMemoryAllocateFlagBitsKHR
forall b. Ptr b -> Int -> VkMemoryAllocateFlagBitsKHR -> 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 VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> IO ()
$cpoke :: Ptr VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> IO ()
peek :: Ptr VkMemoryAllocateFlagBitsKHR -> IO VkMemoryAllocateFlagBitsKHR
$cpeek :: Ptr VkMemoryAllocateFlagBitsKHR -> IO VkMemoryAllocateFlagBitsKHR
pokeByteOff :: forall b. Ptr b -> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkMemoryAllocateFlagBitsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkMemoryAllocateFlagBitsKHR
pokeElemOff :: Ptr VkMemoryAllocateFlagBitsKHR
-> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
$cpokeElemOff :: Ptr VkMemoryAllocateFlagBitsKHR
-> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
peekElemOff :: Ptr VkMemoryAllocateFlagBitsKHR
-> Int -> IO VkMemoryAllocateFlagBitsKHR
$cpeekElemOff :: Ptr VkMemoryAllocateFlagBitsKHR
-> Int -> IO VkMemoryAllocateFlagBitsKHR
alignment :: VkMemoryAllocateFlagBitsKHR -> Int
$calignment :: VkMemoryAllocateFlagBitsKHR -> Int
sizeOf :: VkMemoryAllocateFlagBitsKHR -> Int
$csizeOf :: VkMemoryAllocateFlagBitsKHR -> Int
Storable)

instance Show VkMemoryAllocateFlagBitsKHR where
    {-# INLINE showsPrec #-}
    showsPrec :: Int -> VkMemoryAllocateFlagBitsKHR -> ShowS
showsPrec = (Int -> VkFlags -> ShowS)
-> Int -> VkMemoryAllocateFlagBitsKHR -> ShowS
coerce (Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec :: Int -> VkFlags -> ShowS)

instance Read VkMemoryAllocateFlagBitsKHR where
    {-# INLINE readsPrec #-}
    readsPrec :: Int -> ReadS VkMemoryAllocateFlagBitsKHR
readsPrec = (Int -> ReadS VkFlags) -> Int -> ReadS VkMemoryAllocateFlagBitsKHR
coerce (Int -> ReadS VkFlags
forall a. Read a => Int -> ReadS a
readsPrec :: Int -> ReadS VkFlags)

newtype VkMemoryAllocateBitmask (a ::
                                   FlagType) = VkMemoryAllocateBitmask VkFlags
                                               deriving (VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
(VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool)
-> (VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool)
-> Eq (VkMemoryAllocateBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
/= :: VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
== :: VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
Eq, Eq (VkMemoryAllocateBitmask a)
Eq (VkMemoryAllocateBitmask a)
-> (VkMemoryAllocateBitmask a
    -> VkMemoryAllocateBitmask a -> Ordering)
-> (VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool)
-> (VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool)
-> (VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool)
-> (VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool)
-> (VkMemoryAllocateBitmask a
    -> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a)
-> (VkMemoryAllocateBitmask a
    -> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a)
-> Ord (VkMemoryAllocateBitmask a)
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Ordering
VkMemoryAllocateBitmask a
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
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
forall (a :: FlagType). Eq (VkMemoryAllocateBitmask a)
forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Ordering
forall (a :: FlagType).
VkMemoryAllocateBitmask a
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
min :: VkMemoryAllocateBitmask a
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
$cmin :: forall (a :: FlagType).
VkMemoryAllocateBitmask a
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
max :: VkMemoryAllocateBitmask a
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
$cmax :: forall (a :: FlagType).
VkMemoryAllocateBitmask a
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
>= :: VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
> :: VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
<= :: VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
< :: VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Bool
compare :: VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a -> Ordering
Ord, Ptr (VkMemoryAllocateBitmask a) -> IO (VkMemoryAllocateBitmask a)
Ptr (VkMemoryAllocateBitmask a)
-> Int -> IO (VkMemoryAllocateBitmask a)
Ptr (VkMemoryAllocateBitmask a)
-> Int -> VkMemoryAllocateBitmask a -> IO ()
Ptr (VkMemoryAllocateBitmask a)
-> VkMemoryAllocateBitmask a -> IO ()
VkMemoryAllocateBitmask a -> Int
(VkMemoryAllocateBitmask a -> Int)
-> (VkMemoryAllocateBitmask a -> Int)
-> (Ptr (VkMemoryAllocateBitmask a)
    -> Int -> IO (VkMemoryAllocateBitmask a))
-> (Ptr (VkMemoryAllocateBitmask a)
    -> Int -> VkMemoryAllocateBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkMemoryAllocateBitmask a))
-> (forall b. Ptr b -> Int -> VkMemoryAllocateBitmask a -> IO ())
-> (Ptr (VkMemoryAllocateBitmask a)
    -> IO (VkMemoryAllocateBitmask a))
-> (Ptr (VkMemoryAllocateBitmask a)
    -> VkMemoryAllocateBitmask a -> IO ())
-> Storable (VkMemoryAllocateBitmask a)
forall b. Ptr b -> Int -> IO (VkMemoryAllocateBitmask a)
forall b. Ptr b -> Int -> VkMemoryAllocateBitmask a -> 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
forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a) -> IO (VkMemoryAllocateBitmask a)
forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a)
-> Int -> IO (VkMemoryAllocateBitmask a)
forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a)
-> Int -> VkMemoryAllocateBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a)
-> VkMemoryAllocateBitmask a -> IO ()
forall (a :: FlagType). VkMemoryAllocateBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkMemoryAllocateBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryAllocateBitmask a -> IO ()
poke :: Ptr (VkMemoryAllocateBitmask a)
-> VkMemoryAllocateBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a)
-> VkMemoryAllocateBitmask a -> IO ()
peek :: Ptr (VkMemoryAllocateBitmask a) -> IO (VkMemoryAllocateBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a) -> IO (VkMemoryAllocateBitmask a)
pokeByteOff :: forall b. Ptr b -> Int -> VkMemoryAllocateBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryAllocateBitmask a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (VkMemoryAllocateBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkMemoryAllocateBitmask a)
pokeElemOff :: Ptr (VkMemoryAllocateBitmask a)
-> Int -> VkMemoryAllocateBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a)
-> Int -> VkMemoryAllocateBitmask a -> IO ()
peekElemOff :: Ptr (VkMemoryAllocateBitmask a)
-> Int -> IO (VkMemoryAllocateBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkMemoryAllocateBitmask a)
-> Int -> IO (VkMemoryAllocateBitmask a)
alignment :: VkMemoryAllocateBitmask a -> Int
$calignment :: forall (a :: FlagType). VkMemoryAllocateBitmask a -> Int
sizeOf :: VkMemoryAllocateBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkMemoryAllocateBitmask a -> Int
Storable)

type VkMemoryAllocateFlags = VkMemoryAllocateBitmask FlagMask

type VkMemoryAllocateFlagBits = VkMemoryAllocateBitmask FlagBit

pattern VkMemoryAllocateFlagBits ::
        VkFlags -> VkMemoryAllocateBitmask FlagBit

pattern $bVkMemoryAllocateFlagBits :: VkFlags -> VkMemoryAllocateBitmask FlagBit
$mVkMemoryAllocateFlagBits :: forall {r}.
VkMemoryAllocateBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkMemoryAllocateFlagBits n = VkMemoryAllocateBitmask n

pattern VkMemoryAllocateFlags ::
        VkFlags -> VkMemoryAllocateBitmask FlagMask

pattern $bVkMemoryAllocateFlags :: VkFlags -> VkMemoryAllocateBitmask FlagMask
$mVkMemoryAllocateFlags :: forall {r}.
VkMemoryAllocateBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkMemoryAllocateFlags n = VkMemoryAllocateBitmask n

deriving instance Bits (VkMemoryAllocateBitmask FlagMask)

deriving instance FiniteBits (VkMemoryAllocateBitmask FlagMask)

instance Show (VkMemoryAllocateBitmask a) where
    showsPrec :: Int -> VkMemoryAllocateBitmask a -> ShowS
showsPrec Int
_ VkMemoryAllocateBitmask a
VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT
      = String -> ShowS
showString String
"VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT"
    showsPrec Int
p (VkMemoryAllocateBitmask VkFlags
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkMemoryAllocateBitmask " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkMemoryAllocateBitmask a) where
    readPrec :: ReadPrec (VkMemoryAllocateBitmask a)
readPrec
      = ReadPrec (VkMemoryAllocateBitmask a)
-> ReadPrec (VkMemoryAllocateBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec (VkMemoryAllocateBitmask a))]
-> ReadPrec (VkMemoryAllocateBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT",
               VkMemoryAllocateBitmask a -> ReadPrec (VkMemoryAllocateBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryAllocateBitmask a
forall (a :: FlagType). VkMemoryAllocateBitmask a
VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT)]
             ReadPrec (VkMemoryAllocateBitmask a)
-> ReadPrec (VkMemoryAllocateBitmask a)
-> ReadPrec (VkMemoryAllocateBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec (VkMemoryAllocateBitmask a)
-> ReadPrec (VkMemoryAllocateBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkMemoryAllocateBitmask") ReadPrec ()
-> ReadPrec (VkMemoryAllocateBitmask a)
-> ReadPrec (VkMemoryAllocateBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (VkFlags -> VkMemoryAllocateBitmask a
forall (a :: FlagType). VkFlags -> VkMemoryAllocateBitmask a
VkMemoryAllocateBitmask (VkFlags -> VkMemoryAllocateBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkMemoryAllocateBitmask a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | Force allocation on specific devices
--
--   bitpos = @0@
pattern VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT ::
        VkMemoryAllocateBitmask a

pattern $bVK_MEMORY_ALLOCATE_DEVICE_MASK_BIT :: forall (a :: FlagType). VkMemoryAllocateBitmask a
$mVK_MEMORY_ALLOCATE_DEVICE_MASK_BIT :: forall {r} {a :: FlagType}.
VkMemoryAllocateBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT =
        VkMemoryAllocateBitmask 1

newtype VkMemoryHeapBitmask (a ::
                               FlagType) = VkMemoryHeapBitmask VkFlags
                                           deriving (VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
(VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool)
-> (VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool)
-> Eq (VkMemoryHeapBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
/= :: VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
== :: VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
Eq, Eq (VkMemoryHeapBitmask a)
Eq (VkMemoryHeapBitmask a)
-> (VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Ordering)
-> (VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool)
-> (VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool)
-> (VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool)
-> (VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool)
-> (VkMemoryHeapBitmask a
    -> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a)
-> (VkMemoryHeapBitmask a
    -> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a)
-> Ord (VkMemoryHeapBitmask a)
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Ordering
VkMemoryHeapBitmask a
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
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
forall (a :: FlagType). Eq (VkMemoryHeapBitmask a)
forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Ordering
forall (a :: FlagType).
VkMemoryHeapBitmask a
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
min :: VkMemoryHeapBitmask a
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
$cmin :: forall (a :: FlagType).
VkMemoryHeapBitmask a
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
max :: VkMemoryHeapBitmask a
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
$cmax :: forall (a :: FlagType).
VkMemoryHeapBitmask a
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
>= :: VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
> :: VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
<= :: VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
< :: VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Bool
compare :: VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a -> Ordering
Ord, Ptr (VkMemoryHeapBitmask a) -> IO (VkMemoryHeapBitmask a)
Ptr (VkMemoryHeapBitmask a) -> Int -> IO (VkMemoryHeapBitmask a)
Ptr (VkMemoryHeapBitmask a)
-> Int -> VkMemoryHeapBitmask a -> IO ()
Ptr (VkMemoryHeapBitmask a) -> VkMemoryHeapBitmask a -> IO ()
VkMemoryHeapBitmask a -> Int
(VkMemoryHeapBitmask a -> Int)
-> (VkMemoryHeapBitmask a -> Int)
-> (Ptr (VkMemoryHeapBitmask a)
    -> Int -> IO (VkMemoryHeapBitmask a))
-> (Ptr (VkMemoryHeapBitmask a)
    -> Int -> VkMemoryHeapBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkMemoryHeapBitmask a))
-> (forall b. Ptr b -> Int -> VkMemoryHeapBitmask a -> IO ())
-> (Ptr (VkMemoryHeapBitmask a) -> IO (VkMemoryHeapBitmask a))
-> (Ptr (VkMemoryHeapBitmask a) -> VkMemoryHeapBitmask a -> IO ())
-> Storable (VkMemoryHeapBitmask a)
forall b. Ptr b -> Int -> IO (VkMemoryHeapBitmask a)
forall b. Ptr b -> Int -> VkMemoryHeapBitmask a -> 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
forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a) -> IO (VkMemoryHeapBitmask a)
forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a) -> Int -> IO (VkMemoryHeapBitmask a)
forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a)
-> Int -> VkMemoryHeapBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a) -> VkMemoryHeapBitmask a -> IO ()
forall (a :: FlagType). VkMemoryHeapBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkMemoryHeapBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryHeapBitmask a -> IO ()
poke :: Ptr (VkMemoryHeapBitmask a) -> VkMemoryHeapBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a) -> VkMemoryHeapBitmask a -> IO ()
peek :: Ptr (VkMemoryHeapBitmask a) -> IO (VkMemoryHeapBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a) -> IO (VkMemoryHeapBitmask a)
pokeByteOff :: forall b. Ptr b -> Int -> VkMemoryHeapBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryHeapBitmask a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (VkMemoryHeapBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkMemoryHeapBitmask a)
pokeElemOff :: Ptr (VkMemoryHeapBitmask a)
-> Int -> VkMemoryHeapBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a)
-> Int -> VkMemoryHeapBitmask a -> IO ()
peekElemOff :: Ptr (VkMemoryHeapBitmask a) -> Int -> IO (VkMemoryHeapBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkMemoryHeapBitmask a) -> Int -> IO (VkMemoryHeapBitmask a)
alignment :: VkMemoryHeapBitmask a -> Int
$calignment :: forall (a :: FlagType). VkMemoryHeapBitmask a -> Int
sizeOf :: VkMemoryHeapBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkMemoryHeapBitmask a -> Int
Storable)

type VkMemoryHeapFlags = VkMemoryHeapBitmask FlagMask

type VkMemoryHeapFlagBits = VkMemoryHeapBitmask FlagBit

pattern VkMemoryHeapFlagBits ::
        VkFlags -> VkMemoryHeapBitmask FlagBit

pattern $bVkMemoryHeapFlagBits :: VkFlags -> VkMemoryHeapBitmask FlagBit
$mVkMemoryHeapFlagBits :: forall {r}.
VkMemoryHeapBitmask FlagBit -> (VkFlags -> r) -> (Void# -> r) -> r
VkMemoryHeapFlagBits n = VkMemoryHeapBitmask n

pattern VkMemoryHeapFlags ::
        VkFlags -> VkMemoryHeapBitmask FlagMask

pattern $bVkMemoryHeapFlags :: VkFlags -> VkMemoryHeapBitmask FlagMask
$mVkMemoryHeapFlags :: forall {r}.
VkMemoryHeapBitmask FlagMask -> (VkFlags -> r) -> (Void# -> r) -> r
VkMemoryHeapFlags n = VkMemoryHeapBitmask n

deriving instance Bits (VkMemoryHeapBitmask FlagMask)

deriving instance FiniteBits (VkMemoryHeapBitmask FlagMask)

instance Show (VkMemoryHeapBitmask a) where
    showsPrec :: Int -> VkMemoryHeapBitmask a -> ShowS
showsPrec Int
_ VkMemoryHeapBitmask a
VK_MEMORY_HEAP_DEVICE_LOCAL_BIT
      = String -> ShowS
showString String
"VK_MEMORY_HEAP_DEVICE_LOCAL_BIT"
    showsPrec Int
p (VkMemoryHeapBitmask VkFlags
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkMemoryHeapBitmask " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkMemoryHeapBitmask a) where
    readPrec :: ReadPrec (VkMemoryHeapBitmask a)
readPrec
      = ReadPrec (VkMemoryHeapBitmask a)
-> ReadPrec (VkMemoryHeapBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec (VkMemoryHeapBitmask a))]
-> ReadPrec (VkMemoryHeapBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_MEMORY_HEAP_DEVICE_LOCAL_BIT",
               VkMemoryHeapBitmask a -> ReadPrec (VkMemoryHeapBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryHeapBitmask a
forall (a :: FlagType). VkMemoryHeapBitmask a
VK_MEMORY_HEAP_DEVICE_LOCAL_BIT)]
             ReadPrec (VkMemoryHeapBitmask a)
-> ReadPrec (VkMemoryHeapBitmask a)
-> ReadPrec (VkMemoryHeapBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec (VkMemoryHeapBitmask a)
-> ReadPrec (VkMemoryHeapBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkMemoryHeapBitmask") ReadPrec ()
-> ReadPrec (VkMemoryHeapBitmask a)
-> ReadPrec (VkMemoryHeapBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (VkFlags -> VkMemoryHeapBitmask a
forall (a :: FlagType). VkFlags -> VkMemoryHeapBitmask a
VkMemoryHeapBitmask (VkFlags -> VkMemoryHeapBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkMemoryHeapBitmask a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | If set, heap represents device memory
--
--   bitpos = @0@
pattern VK_MEMORY_HEAP_DEVICE_LOCAL_BIT :: VkMemoryHeapBitmask a

pattern $bVK_MEMORY_HEAP_DEVICE_LOCAL_BIT :: forall (a :: FlagType). VkMemoryHeapBitmask a
$mVK_MEMORY_HEAP_DEVICE_LOCAL_BIT :: forall {r} {a :: FlagType}.
VkMemoryHeapBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_HEAP_DEVICE_LOCAL_BIT = VkMemoryHeapBitmask 1

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkMemoryOverallocationBehaviorAMD VkMemoryOverallocationBehaviorAMD registry at www.khronos.org>
newtype VkMemoryOverallocationBehaviorAMD = VkMemoryOverallocationBehaviorAMD Int32
                                            deriving (VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
(VkMemoryOverallocationBehaviorAMD
 -> VkMemoryOverallocationBehaviorAMD -> Bool)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD -> Bool)
-> Eq VkMemoryOverallocationBehaviorAMD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
$c/= :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
== :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
$c== :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
Eq, Eq VkMemoryOverallocationBehaviorAMD
Eq VkMemoryOverallocationBehaviorAMD
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD -> Ordering)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD -> Bool)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD -> Bool)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD -> Bool)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD -> Bool)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD)
-> Ord VkMemoryOverallocationBehaviorAMD
VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Ordering
VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
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 :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
$cmin :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
max :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
$cmax :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
>= :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
$c>= :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
> :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
$c> :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
<= :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
$c<= :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
< :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
$c< :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Bool
compare :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Ordering
$ccompare :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> Ordering
Ord, Int -> VkMemoryOverallocationBehaviorAMD
VkMemoryOverallocationBehaviorAMD -> Int
VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
(VkMemoryOverallocationBehaviorAMD
 -> VkMemoryOverallocationBehaviorAMD)
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD)
-> (Int -> VkMemoryOverallocationBehaviorAMD)
-> (VkMemoryOverallocationBehaviorAMD -> Int)
-> (VkMemoryOverallocationBehaviorAMD
    -> [VkMemoryOverallocationBehaviorAMD])
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD
    -> [VkMemoryOverallocationBehaviorAMD])
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD
    -> [VkMemoryOverallocationBehaviorAMD])
-> (VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD
    -> [VkMemoryOverallocationBehaviorAMD])
-> Enum VkMemoryOverallocationBehaviorAMD
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 :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
$cenumFromThenTo :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
enumFromTo :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
$cenumFromTo :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
enumFromThen :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
$cenumFromThen :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
enumFrom :: VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
$cenumFrom :: VkMemoryOverallocationBehaviorAMD
-> [VkMemoryOverallocationBehaviorAMD]
fromEnum :: VkMemoryOverallocationBehaviorAMD -> Int
$cfromEnum :: VkMemoryOverallocationBehaviorAMD -> Int
toEnum :: Int -> VkMemoryOverallocationBehaviorAMD
$ctoEnum :: Int -> VkMemoryOverallocationBehaviorAMD
pred :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
$cpred :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
succ :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
$csucc :: VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD
Enum, Ptr VkMemoryOverallocationBehaviorAMD
-> IO VkMemoryOverallocationBehaviorAMD
Ptr VkMemoryOverallocationBehaviorAMD
-> Int -> IO VkMemoryOverallocationBehaviorAMD
Ptr VkMemoryOverallocationBehaviorAMD
-> Int -> VkMemoryOverallocationBehaviorAMD -> IO ()
Ptr VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> IO ()
VkMemoryOverallocationBehaviorAMD -> Int
(VkMemoryOverallocationBehaviorAMD -> Int)
-> (VkMemoryOverallocationBehaviorAMD -> Int)
-> (Ptr VkMemoryOverallocationBehaviorAMD
    -> Int -> IO VkMemoryOverallocationBehaviorAMD)
-> (Ptr VkMemoryOverallocationBehaviorAMD
    -> Int -> VkMemoryOverallocationBehaviorAMD -> IO ())
-> (forall b. Ptr b -> Int -> IO VkMemoryOverallocationBehaviorAMD)
-> (forall b.
    Ptr b -> Int -> VkMemoryOverallocationBehaviorAMD -> IO ())
-> (Ptr VkMemoryOverallocationBehaviorAMD
    -> IO VkMemoryOverallocationBehaviorAMD)
-> (Ptr VkMemoryOverallocationBehaviorAMD
    -> VkMemoryOverallocationBehaviorAMD -> IO ())
-> Storable VkMemoryOverallocationBehaviorAMD
forall b. Ptr b -> Int -> IO VkMemoryOverallocationBehaviorAMD
forall b.
Ptr b -> Int -> VkMemoryOverallocationBehaviorAMD -> 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 VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> IO ()
$cpoke :: Ptr VkMemoryOverallocationBehaviorAMD
-> VkMemoryOverallocationBehaviorAMD -> IO ()
peek :: Ptr VkMemoryOverallocationBehaviorAMD
-> IO VkMemoryOverallocationBehaviorAMD
$cpeek :: Ptr VkMemoryOverallocationBehaviorAMD
-> IO VkMemoryOverallocationBehaviorAMD
pokeByteOff :: forall b.
Ptr b -> Int -> VkMemoryOverallocationBehaviorAMD -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> VkMemoryOverallocationBehaviorAMD -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkMemoryOverallocationBehaviorAMD
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkMemoryOverallocationBehaviorAMD
pokeElemOff :: Ptr VkMemoryOverallocationBehaviorAMD
-> Int -> VkMemoryOverallocationBehaviorAMD -> IO ()
$cpokeElemOff :: Ptr VkMemoryOverallocationBehaviorAMD
-> Int -> VkMemoryOverallocationBehaviorAMD -> IO ()
peekElemOff :: Ptr VkMemoryOverallocationBehaviorAMD
-> Int -> IO VkMemoryOverallocationBehaviorAMD
$cpeekElemOff :: Ptr VkMemoryOverallocationBehaviorAMD
-> Int -> IO VkMemoryOverallocationBehaviorAMD
alignment :: VkMemoryOverallocationBehaviorAMD -> Int
$calignment :: VkMemoryOverallocationBehaviorAMD -> Int
sizeOf :: VkMemoryOverallocationBehaviorAMD -> Int
$csizeOf :: VkMemoryOverallocationBehaviorAMD -> Int
Storable)

instance Show VkMemoryOverallocationBehaviorAMD where
    showsPrec :: Int -> VkMemoryOverallocationBehaviorAMD -> ShowS
showsPrec Int
_ VkMemoryOverallocationBehaviorAMD
VK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD
      = String -> ShowS
showString String
"VK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD"
    showsPrec Int
_ VkMemoryOverallocationBehaviorAMD
VK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD
      = String -> ShowS
showString String
"VK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD"
    showsPrec Int
_ VkMemoryOverallocationBehaviorAMD
VK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD
      = String -> ShowS
showString String
"VK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD"
    showsPrec Int
p (VkMemoryOverallocationBehaviorAMD Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkMemoryOverallocationBehaviorAMD " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkMemoryOverallocationBehaviorAMD where
    readPrec :: ReadPrec VkMemoryOverallocationBehaviorAMD
readPrec
      = ReadPrec VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkMemoryOverallocationBehaviorAMD)]
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD",
               VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryOverallocationBehaviorAMD
VK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD),
              (String
"VK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD",
               VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryOverallocationBehaviorAMD
VK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD),
              (String
"VK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD",
               VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryOverallocationBehaviorAMD
VK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD)]
             ReadPrec VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkMemoryOverallocationBehaviorAMD") ReadPrec ()
-> ReadPrec VkMemoryOverallocationBehaviorAMD
-> ReadPrec VkMemoryOverallocationBehaviorAMD
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkMemoryOverallocationBehaviorAMD
VkMemoryOverallocationBehaviorAMD (Int32 -> VkMemoryOverallocationBehaviorAMD)
-> ReadPrec Int32 -> ReadPrec VkMemoryOverallocationBehaviorAMD
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD ::
        VkMemoryOverallocationBehaviorAMD

pattern $bVK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD :: VkMemoryOverallocationBehaviorAMD
$mVK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD :: forall {r}.
VkMemoryOverallocationBehaviorAMD
-> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_OVERALLOCATION_BEHAVIOR_DEFAULT_AMD =
        VkMemoryOverallocationBehaviorAMD 0

pattern VK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD ::
        VkMemoryOverallocationBehaviorAMD

pattern $bVK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD :: VkMemoryOverallocationBehaviorAMD
$mVK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD :: forall {r}.
VkMemoryOverallocationBehaviorAMD
-> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_OVERALLOCATION_BEHAVIOR_ALLOWED_AMD =
        VkMemoryOverallocationBehaviorAMD 1

pattern VK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD ::
        VkMemoryOverallocationBehaviorAMD

pattern $bVK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD :: VkMemoryOverallocationBehaviorAMD
$mVK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD :: forall {r}.
VkMemoryOverallocationBehaviorAMD
-> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_OVERALLOCATION_BEHAVIOR_DISALLOWED_AMD =
        VkMemoryOverallocationBehaviorAMD 2

newtype VkMemoryPropertyBitmask (a ::
                                   FlagType) = VkMemoryPropertyBitmask VkFlags
                                               deriving (VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
(VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool)
-> (VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool)
-> Eq (VkMemoryPropertyBitmask a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
/= :: VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
$c/= :: forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
== :: VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
$c== :: forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
Eq, Eq (VkMemoryPropertyBitmask a)
Eq (VkMemoryPropertyBitmask a)
-> (VkMemoryPropertyBitmask a
    -> VkMemoryPropertyBitmask a -> Ordering)
-> (VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool)
-> (VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool)
-> (VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool)
-> (VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool)
-> (VkMemoryPropertyBitmask a
    -> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a)
-> (VkMemoryPropertyBitmask a
    -> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a)
-> Ord (VkMemoryPropertyBitmask a)
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Ordering
VkMemoryPropertyBitmask a
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
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
forall (a :: FlagType). Eq (VkMemoryPropertyBitmask a)
forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Ordering
forall (a :: FlagType).
VkMemoryPropertyBitmask a
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
min :: VkMemoryPropertyBitmask a
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
$cmin :: forall (a :: FlagType).
VkMemoryPropertyBitmask a
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
max :: VkMemoryPropertyBitmask a
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
$cmax :: forall (a :: FlagType).
VkMemoryPropertyBitmask a
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
>= :: VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
$c>= :: forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
> :: VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
$c> :: forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
<= :: VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
$c<= :: forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
< :: VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
$c< :: forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Bool
compare :: VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Ordering
$ccompare :: forall (a :: FlagType).
VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a -> Ordering
Ord, Ptr (VkMemoryPropertyBitmask a) -> IO (VkMemoryPropertyBitmask a)
Ptr (VkMemoryPropertyBitmask a)
-> Int -> IO (VkMemoryPropertyBitmask a)
Ptr (VkMemoryPropertyBitmask a)
-> Int -> VkMemoryPropertyBitmask a -> IO ()
Ptr (VkMemoryPropertyBitmask a)
-> VkMemoryPropertyBitmask a -> IO ()
VkMemoryPropertyBitmask a -> Int
(VkMemoryPropertyBitmask a -> Int)
-> (VkMemoryPropertyBitmask a -> Int)
-> (Ptr (VkMemoryPropertyBitmask a)
    -> Int -> IO (VkMemoryPropertyBitmask a))
-> (Ptr (VkMemoryPropertyBitmask a)
    -> Int -> VkMemoryPropertyBitmask a -> IO ())
-> (forall b. Ptr b -> Int -> IO (VkMemoryPropertyBitmask a))
-> (forall b. Ptr b -> Int -> VkMemoryPropertyBitmask a -> IO ())
-> (Ptr (VkMemoryPropertyBitmask a)
    -> IO (VkMemoryPropertyBitmask a))
-> (Ptr (VkMemoryPropertyBitmask a)
    -> VkMemoryPropertyBitmask a -> IO ())
-> Storable (VkMemoryPropertyBitmask a)
forall b. Ptr b -> Int -> IO (VkMemoryPropertyBitmask a)
forall b. Ptr b -> Int -> VkMemoryPropertyBitmask a -> 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
forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a) -> IO (VkMemoryPropertyBitmask a)
forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a)
-> Int -> IO (VkMemoryPropertyBitmask a)
forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a)
-> Int -> VkMemoryPropertyBitmask a -> IO ()
forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a)
-> VkMemoryPropertyBitmask a -> IO ()
forall (a :: FlagType). VkMemoryPropertyBitmask a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkMemoryPropertyBitmask a)
forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryPropertyBitmask a -> IO ()
poke :: Ptr (VkMemoryPropertyBitmask a)
-> VkMemoryPropertyBitmask a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a)
-> VkMemoryPropertyBitmask a -> IO ()
peek :: Ptr (VkMemoryPropertyBitmask a) -> IO (VkMemoryPropertyBitmask a)
$cpeek :: forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a) -> IO (VkMemoryPropertyBitmask a)
pokeByteOff :: forall b. Ptr b -> Int -> VkMemoryPropertyBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryPropertyBitmask a -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (VkMemoryPropertyBitmask a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkMemoryPropertyBitmask a)
pokeElemOff :: Ptr (VkMemoryPropertyBitmask a)
-> Int -> VkMemoryPropertyBitmask a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a)
-> Int -> VkMemoryPropertyBitmask a -> IO ()
peekElemOff :: Ptr (VkMemoryPropertyBitmask a)
-> Int -> IO (VkMemoryPropertyBitmask a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkMemoryPropertyBitmask a)
-> Int -> IO (VkMemoryPropertyBitmask a)
alignment :: VkMemoryPropertyBitmask a -> Int
$calignment :: forall (a :: FlagType). VkMemoryPropertyBitmask a -> Int
sizeOf :: VkMemoryPropertyBitmask a -> Int
$csizeOf :: forall (a :: FlagType). VkMemoryPropertyBitmask a -> Int
Storable)

type VkMemoryPropertyFlags = VkMemoryPropertyBitmask FlagMask

type VkMemoryPropertyFlagBits = VkMemoryPropertyBitmask FlagBit

pattern VkMemoryPropertyFlagBits ::
        VkFlags -> VkMemoryPropertyBitmask FlagBit

pattern $bVkMemoryPropertyFlagBits :: VkFlags -> VkMemoryPropertyBitmask FlagBit
$mVkMemoryPropertyFlagBits :: forall {r}.
VkMemoryPropertyBitmask FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkMemoryPropertyFlagBits n = VkMemoryPropertyBitmask n

pattern VkMemoryPropertyFlags ::
        VkFlags -> VkMemoryPropertyBitmask FlagMask

pattern $bVkMemoryPropertyFlags :: VkFlags -> VkMemoryPropertyBitmask FlagMask
$mVkMemoryPropertyFlags :: forall {r}.
VkMemoryPropertyBitmask FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkMemoryPropertyFlags n = VkMemoryPropertyBitmask n

deriving instance Bits (VkMemoryPropertyBitmask FlagMask)

deriving instance FiniteBits (VkMemoryPropertyBitmask FlagMask)

instance Show (VkMemoryPropertyBitmask a) where
    showsPrec :: Int -> VkMemoryPropertyBitmask a -> ShowS
showsPrec Int
_ VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT
      = String -> ShowS
showString String
"VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT"
    showsPrec Int
_ VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT
      = String -> ShowS
showString String
"VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT"
    showsPrec Int
_ VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_HOST_COHERENT_BIT
      = String -> ShowS
showString String
"VK_MEMORY_PROPERTY_HOST_COHERENT_BIT"
    showsPrec Int
_ VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_HOST_CACHED_BIT
      = String -> ShowS
showString String
"VK_MEMORY_PROPERTY_HOST_CACHED_BIT"
    showsPrec Int
_ VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT
      = String -> ShowS
showString String
"VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT"
    showsPrec Int
p (VkMemoryPropertyBitmask VkFlags
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkMemoryPropertyBitmask " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkMemoryPropertyBitmask a) where
    readPrec :: ReadPrec (VkMemoryPropertyBitmask a)
readPrec
      = ReadPrec (VkMemoryPropertyBitmask a)
-> ReadPrec (VkMemoryPropertyBitmask a)
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec (VkMemoryPropertyBitmask a))]
-> ReadPrec (VkMemoryPropertyBitmask a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT",
               VkMemoryPropertyBitmask a -> ReadPrec (VkMemoryPropertyBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryPropertyBitmask a
forall (a :: FlagType). VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT),
              (String
"VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT",
               VkMemoryPropertyBitmask a -> ReadPrec (VkMemoryPropertyBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryPropertyBitmask a
forall (a :: FlagType). VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT),
              (String
"VK_MEMORY_PROPERTY_HOST_COHERENT_BIT",
               VkMemoryPropertyBitmask a -> ReadPrec (VkMemoryPropertyBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryPropertyBitmask a
forall (a :: FlagType). VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_HOST_COHERENT_BIT),
              (String
"VK_MEMORY_PROPERTY_HOST_CACHED_BIT",
               VkMemoryPropertyBitmask a -> ReadPrec (VkMemoryPropertyBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryPropertyBitmask a
forall (a :: FlagType). VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_HOST_CACHED_BIT),
              (String
"VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT",
               VkMemoryPropertyBitmask a -> ReadPrec (VkMemoryPropertyBitmask a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkMemoryPropertyBitmask a
forall (a :: FlagType). VkMemoryPropertyBitmask a
VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT)]
             ReadPrec (VkMemoryPropertyBitmask a)
-> ReadPrec (VkMemoryPropertyBitmask a)
-> ReadPrec (VkMemoryPropertyBitmask a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec (VkMemoryPropertyBitmask a)
-> ReadPrec (VkMemoryPropertyBitmask a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkMemoryPropertyBitmask") ReadPrec ()
-> ReadPrec (VkMemoryPropertyBitmask a)
-> ReadPrec (VkMemoryPropertyBitmask a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (VkFlags -> VkMemoryPropertyBitmask a
forall (a :: FlagType). VkFlags -> VkMemoryPropertyBitmask a
VkMemoryPropertyBitmask (VkFlags -> VkMemoryPropertyBitmask a)
-> ReadPrec VkFlags -> ReadPrec (VkMemoryPropertyBitmask a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | If otherwise stated, then allocate memory on device
--
--   bitpos = @0@
pattern VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT ::
        VkMemoryPropertyBitmask a

pattern $bVK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT :: forall (a :: FlagType). VkMemoryPropertyBitmask a
$mVK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT :: forall {r} {a :: FlagType}.
VkMemoryPropertyBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_PROPERTY_DEVICE_LOCAL_BIT =
        VkMemoryPropertyBitmask 1

-- | Memory is mappable by host
--
--   bitpos = @1@
pattern VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT ::
        VkMemoryPropertyBitmask a

pattern $bVK_MEMORY_PROPERTY_HOST_VISIBLE_BIT :: forall (a :: FlagType). VkMemoryPropertyBitmask a
$mVK_MEMORY_PROPERTY_HOST_VISIBLE_BIT :: forall {r} {a :: FlagType}.
VkMemoryPropertyBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_PROPERTY_HOST_VISIBLE_BIT =
        VkMemoryPropertyBitmask 2

-- | Memory will have i/o coherency. If not set, application may need to use vkFlushMappedMemoryRanges and vkInvalidateMappedMemoryRanges to flush/invalidate host cache
--
--   bitpos = @2@
pattern VK_MEMORY_PROPERTY_HOST_COHERENT_BIT ::
        VkMemoryPropertyBitmask a

pattern $bVK_MEMORY_PROPERTY_HOST_COHERENT_BIT :: forall (a :: FlagType). VkMemoryPropertyBitmask a
$mVK_MEMORY_PROPERTY_HOST_COHERENT_BIT :: forall {r} {a :: FlagType}.
VkMemoryPropertyBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_PROPERTY_HOST_COHERENT_BIT =
        VkMemoryPropertyBitmask 4

-- | Memory will be cached by the host
--
--   bitpos = @3@
pattern VK_MEMORY_PROPERTY_HOST_CACHED_BIT ::
        VkMemoryPropertyBitmask a

pattern $bVK_MEMORY_PROPERTY_HOST_CACHED_BIT :: forall (a :: FlagType). VkMemoryPropertyBitmask a
$mVK_MEMORY_PROPERTY_HOST_CACHED_BIT :: forall {r} {a :: FlagType}.
VkMemoryPropertyBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_PROPERTY_HOST_CACHED_BIT =
        VkMemoryPropertyBitmask 8

-- | Memory may be allocated by the driver when it is required
--
--   bitpos = @4@
pattern VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT ::
        VkMemoryPropertyBitmask a

pattern $bVK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT :: forall (a :: FlagType). VkMemoryPropertyBitmask a
$mVK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT :: forall {r} {a :: FlagType}.
VkMemoryPropertyBitmask a -> (Void# -> r) -> (Void# -> r) -> r
VK_MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT =
        VkMemoryPropertyBitmask 16