{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# 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,
        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           Data.Data                       (Data)
import           Foreign.Storable                (Storable)
import           GHC.Generics                    (Generic)
import           GHC.Read                        (choose, expectP)
import           Graphics.Vulkan.Marshal         (FlagBit, FlagMask, FlagType)
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
$cp1Ord :: Eq VkMemoryAllocateFlagBitsKHR
Ord, Integer -> VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
(VkMemoryAllocateFlagBitsKHR
 -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (Integer -> VkMemoryAllocateFlagBitsKHR)
-> Num VkMemoryAllocateFlagBitsKHR
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> VkMemoryAllocateFlagBitsKHR
$cfromInteger :: Integer -> VkMemoryAllocateFlagBitsKHR
signum :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$csignum :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
abs :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cabs :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
negate :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cnegate :: VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
* :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$c* :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
- :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$c- :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
+ :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$c+ :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
Num, VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> Bounded VkMemoryAllocateFlagBitsKHR
forall a. a -> a -> Bounded a
maxBound :: VkMemoryAllocateFlagBitsKHR
$cmaxBound :: VkMemoryAllocateFlagBitsKHR
minBound :: VkMemoryAllocateFlagBitsKHR
$cminBound :: VkMemoryAllocateFlagBitsKHR
Bounded, 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, Enum VkMemoryAllocateFlagBitsKHR
Real VkMemoryAllocateFlagBitsKHR
Real VkMemoryAllocateFlagBitsKHR
-> Enum VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR
    -> (VkMemoryAllocateFlagBitsKHR, VkMemoryAllocateFlagBitsKHR))
-> (VkMemoryAllocateFlagBitsKHR
    -> VkMemoryAllocateFlagBitsKHR
    -> (VkMemoryAllocateFlagBitsKHR, VkMemoryAllocateFlagBitsKHR))
-> (VkMemoryAllocateFlagBitsKHR -> Integer)
-> Integral VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> Integer
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR, VkMemoryAllocateFlagBitsKHR)
VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: VkMemoryAllocateFlagBitsKHR -> Integer
$ctoInteger :: VkMemoryAllocateFlagBitsKHR -> Integer
divMod :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR, VkMemoryAllocateFlagBitsKHR)
$cdivMod :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR, VkMemoryAllocateFlagBitsKHR)
quotRem :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR, VkMemoryAllocateFlagBitsKHR)
$cquotRem :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR, VkMemoryAllocateFlagBitsKHR)
mod :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cmod :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
div :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cdiv :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
rem :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$crem :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
quot :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cquot :: VkMemoryAllocateFlagBitsKHR
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cp2Integral :: Enum VkMemoryAllocateFlagBitsKHR
$cp1Integral :: Real VkMemoryAllocateFlagBitsKHR
Integral, 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
$cp1Bits :: Eq 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
$cp1FiniteBits :: Bits VkMemoryAllocateFlagBitsKHR
FiniteBits, Ptr b -> Int -> IO VkMemoryAllocateFlagBitsKHR
Ptr b -> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
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 :: Ptr b -> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkMemoryAllocateFlagBitsKHR -> IO ()
peekByteOff :: 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, Num VkMemoryAllocateFlagBitsKHR
Ord VkMemoryAllocateFlagBitsKHR
Num VkMemoryAllocateFlagBitsKHR
-> Ord VkMemoryAllocateFlagBitsKHR
-> (VkMemoryAllocateFlagBitsKHR -> Rational)
-> Real VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: VkMemoryAllocateFlagBitsKHR -> Rational
$ctoRational :: VkMemoryAllocateFlagBitsKHR -> Rational
$cp2Real :: Ord VkMemoryAllocateFlagBitsKHR
$cp1Real :: Num VkMemoryAllocateFlagBitsKHR
Real, Typeable VkMemoryAllocateFlagBitsKHR
DataType
Constr
Typeable VkMemoryAllocateFlagBitsKHR
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkMemoryAllocateFlagBitsKHR
    -> c VkMemoryAllocateFlagBitsKHR)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c VkMemoryAllocateFlagBitsKHR)
-> (VkMemoryAllocateFlagBitsKHR -> Constr)
-> (VkMemoryAllocateFlagBitsKHR -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c VkMemoryAllocateFlagBitsKHR))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c VkMemoryAllocateFlagBitsKHR))
-> ((forall b. Data b => b -> b)
    -> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryAllocateFlagBitsKHR
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryAllocateFlagBitsKHR
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u)
    -> VkMemoryAllocateFlagBitsKHR
    -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR)
-> Data VkMemoryAllocateFlagBitsKHR
VkMemoryAllocateFlagBitsKHR -> DataType
VkMemoryAllocateFlagBitsKHR -> Constr
(forall b. Data b => b -> b)
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateFlagBitsKHR
-> c VkMemoryAllocateFlagBitsKHR
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkMemoryAllocateFlagBitsKHR
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> u
forall u.
(forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateFlagBitsKHR
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateFlagBitsKHR
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkMemoryAllocateFlagBitsKHR
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateFlagBitsKHR
-> c VkMemoryAllocateFlagBitsKHR
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c VkMemoryAllocateFlagBitsKHR)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkMemoryAllocateFlagBitsKHR)
$cVkMemoryAllocateFlagBitsKHR :: Constr
$tVkMemoryAllocateFlagBitsKHR :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
gmapMp :: (forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
gmapM :: (forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateFlagBitsKHR -> m VkMemoryAllocateFlagBitsKHR
gmapQi :: Int
-> (forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> u
gmapQ :: (forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> VkMemoryAllocateFlagBitsKHR -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateFlagBitsKHR
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateFlagBitsKHR
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateFlagBitsKHR
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateFlagBitsKHR
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
$cgmapT :: (forall b. Data b => b -> b)
-> VkMemoryAllocateFlagBitsKHR -> VkMemoryAllocateFlagBitsKHR
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkMemoryAllocateFlagBitsKHR)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VkMemoryAllocateFlagBitsKHR)
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c VkMemoryAllocateFlagBitsKHR)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c VkMemoryAllocateFlagBitsKHR)
dataTypeOf :: VkMemoryAllocateFlagBitsKHR -> DataType
$cdataTypeOf :: VkMemoryAllocateFlagBitsKHR -> DataType
toConstr :: VkMemoryAllocateFlagBitsKHR -> Constr
$ctoConstr :: VkMemoryAllocateFlagBitsKHR -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkMemoryAllocateFlagBitsKHR
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VkMemoryAllocateFlagBitsKHR
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateFlagBitsKHR
-> c VkMemoryAllocateFlagBitsKHR
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateFlagBitsKHR
-> c VkMemoryAllocateFlagBitsKHR
$cp1Data :: Typeable VkMemoryAllocateFlagBitsKHR
Data, (forall x.
 VkMemoryAllocateFlagBitsKHR -> Rep VkMemoryAllocateFlagBitsKHR x)
-> (forall x.
    Rep VkMemoryAllocateFlagBitsKHR x -> VkMemoryAllocateFlagBitsKHR)
-> Generic VkMemoryAllocateFlagBitsKHR
forall x.
Rep VkMemoryAllocateFlagBitsKHR x -> VkMemoryAllocateFlagBitsKHR
forall x.
VkMemoryAllocateFlagBitsKHR -> Rep VkMemoryAllocateFlagBitsKHR x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep VkMemoryAllocateFlagBitsKHR x -> VkMemoryAllocateFlagBitsKHR
$cfrom :: forall x.
VkMemoryAllocateFlagBitsKHR -> Rep VkMemoryAllocateFlagBitsKHR x
Generic)

instance Show VkMemoryAllocateFlagBitsKHR where
        {-# INLINE show #-}
        show :: VkMemoryAllocateFlagBitsKHR -> String
show (VkMemoryAllocateFlagBitsKHR VkFlags
x) = VkFlags -> String
forall a. Show a => a -> String
show VkFlags
x

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
$cp1Ord :: forall (a :: FlagType). Eq (VkMemoryAllocateBitmask a)
Ord, Ptr b -> Int -> IO (VkMemoryAllocateBitmask a)
Ptr b -> Int -> VkMemoryAllocateBitmask a -> IO ()
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 :: Ptr b -> Int -> VkMemoryAllocateBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryAllocateBitmask a -> IO ()
peekByteOff :: 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, Typeable (VkMemoryAllocateBitmask a)
DataType
Constr
Typeable (VkMemoryAllocateBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkMemoryAllocateBitmask a
    -> c (VkMemoryAllocateBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkMemoryAllocateBitmask a))
-> (VkMemoryAllocateBitmask a -> Constr)
-> (VkMemoryAllocateBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkMemoryAllocateBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkMemoryAllocateBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryAllocateBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryAllocateBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a))
-> Data (VkMemoryAllocateBitmask a)
VkMemoryAllocateBitmask a -> DataType
VkMemoryAllocateBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateBitmask a
-> c (VkMemoryAllocateBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryAllocateBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> u
forall u.
(forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkMemoryAllocateBitmask a)
forall (a :: FlagType).
Typeable a =>
VkMemoryAllocateBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkMemoryAllocateBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryAllocateBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateBitmask a
-> c (VkMemoryAllocateBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkMemoryAllocateBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryAllocateBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryAllocateBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateBitmask a
-> c (VkMemoryAllocateBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (VkMemoryAllocateBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryAllocateBitmask a))
$cVkMemoryAllocateBitmask :: Constr
$tVkMemoryAllocateBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkMemoryAllocateBitmask a -> m (VkMemoryAllocateBitmask a)
gmapQi :: Int
-> (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkMemoryAllocateBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryAllocateBitmask a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkMemoryAllocateBitmask a -> VkMemoryAllocateBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryAllocateBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryAllocateBitmask a))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (VkMemoryAllocateBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkMemoryAllocateBitmask a))
dataTypeOf :: VkMemoryAllocateBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkMemoryAllocateBitmask a -> DataType
toConstr :: VkMemoryAllocateBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkMemoryAllocateBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryAllocateBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryAllocateBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateBitmask a
-> c (VkMemoryAllocateBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryAllocateBitmask a
-> c (VkMemoryAllocateBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkMemoryAllocateBitmask a)
Data, (forall x.
 VkMemoryAllocateBitmask a -> Rep (VkMemoryAllocateBitmask a) x)
-> (forall x.
    Rep (VkMemoryAllocateBitmask a) x -> VkMemoryAllocateBitmask a)
-> Generic (VkMemoryAllocateBitmask a)
forall x.
Rep (VkMemoryAllocateBitmask a) x -> VkMemoryAllocateBitmask a
forall x.
VkMemoryAllocateBitmask a -> Rep (VkMemoryAllocateBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkMemoryAllocateBitmask a) x -> VkMemoryAllocateBitmask a
forall (a :: FlagType) x.
VkMemoryAllocateBitmask a -> Rep (VkMemoryAllocateBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkMemoryAllocateBitmask a) x -> VkMemoryAllocateBitmask a
$cfrom :: forall (a :: FlagType) x.
VkMemoryAllocateBitmask a -> Rep (VkMemoryAllocateBitmask a) x
Generic)

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)

deriving instance Integral (VkMemoryAllocateBitmask FlagMask)

deriving instance Num (VkMemoryAllocateBitmask FlagMask)

deriving instance Bounded (VkMemoryAllocateBitmask FlagMask)

deriving instance Enum (VkMemoryAllocateBitmask FlagMask)

deriving instance Real (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 :: 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
$cp1Ord :: forall (a :: FlagType). Eq (VkMemoryHeapBitmask a)
Ord, Ptr b -> Int -> IO (VkMemoryHeapBitmask a)
Ptr b -> Int -> VkMemoryHeapBitmask a -> IO ()
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 :: Ptr b -> Int -> VkMemoryHeapBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryHeapBitmask a -> IO ()
peekByteOff :: 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, Typeable (VkMemoryHeapBitmask a)
DataType
Constr
Typeable (VkMemoryHeapBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkMemoryHeapBitmask a
    -> c (VkMemoryHeapBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkMemoryHeapBitmask a))
-> (VkMemoryHeapBitmask a -> Constr)
-> (VkMemoryHeapBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (VkMemoryHeapBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkMemoryHeapBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryHeapBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryHeapBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a))
-> Data (VkMemoryHeapBitmask a)
VkMemoryHeapBitmask a -> DataType
VkMemoryHeapBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryHeapBitmask a
-> c (VkMemoryHeapBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryHeapBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> u
forall u.
(forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkMemoryHeapBitmask a)
forall (a :: FlagType).
Typeable a =>
VkMemoryHeapBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkMemoryHeapBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryHeapBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryHeapBitmask a
-> c (VkMemoryHeapBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkMemoryHeapBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryHeapBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryHeapBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryHeapBitmask a
-> c (VkMemoryHeapBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (VkMemoryHeapBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryHeapBitmask a))
$cVkMemoryHeapBitmask :: Constr
$tVkMemoryHeapBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkMemoryHeapBitmask a -> m (VkMemoryHeapBitmask a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int -> (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkMemoryHeapBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VkMemoryHeapBitmask a -> r
gmapT :: (forall b. Data b => b -> b)
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkMemoryHeapBitmask a -> VkMemoryHeapBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryHeapBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryHeapBitmask a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (VkMemoryHeapBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VkMemoryHeapBitmask a))
dataTypeOf :: VkMemoryHeapBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkMemoryHeapBitmask a -> DataType
toConstr :: VkMemoryHeapBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkMemoryHeapBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryHeapBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryHeapBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryHeapBitmask a
-> c (VkMemoryHeapBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryHeapBitmask a
-> c (VkMemoryHeapBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkMemoryHeapBitmask a)
Data, (forall x. VkMemoryHeapBitmask a -> Rep (VkMemoryHeapBitmask a) x)
-> (forall x.
    Rep (VkMemoryHeapBitmask a) x -> VkMemoryHeapBitmask a)
-> Generic (VkMemoryHeapBitmask a)
forall x. Rep (VkMemoryHeapBitmask a) x -> VkMemoryHeapBitmask a
forall x. VkMemoryHeapBitmask a -> Rep (VkMemoryHeapBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkMemoryHeapBitmask a) x -> VkMemoryHeapBitmask a
forall (a :: FlagType) x.
VkMemoryHeapBitmask a -> Rep (VkMemoryHeapBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkMemoryHeapBitmask a) x -> VkMemoryHeapBitmask a
$cfrom :: forall (a :: FlagType) x.
VkMemoryHeapBitmask a -> Rep (VkMemoryHeapBitmask a) x
Generic)

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)

deriving instance Integral (VkMemoryHeapBitmask FlagMask)

deriving instance Num (VkMemoryHeapBitmask FlagMask)

deriving instance Bounded (VkMemoryHeapBitmask FlagMask)

deriving instance Enum (VkMemoryHeapBitmask FlagMask)

deriving instance Real (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 :: 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

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
$cp1Ord :: forall (a :: FlagType). Eq (VkMemoryPropertyBitmask a)
Ord, Ptr b -> Int -> IO (VkMemoryPropertyBitmask a)
Ptr b -> Int -> VkMemoryPropertyBitmask a -> IO ()
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 :: Ptr b -> Int -> VkMemoryPropertyBitmask a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> VkMemoryPropertyBitmask a -> IO ()
peekByteOff :: 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, Typeable (VkMemoryPropertyBitmask a)
DataType
Constr
Typeable (VkMemoryPropertyBitmask a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> VkMemoryPropertyBitmask a
    -> c (VkMemoryPropertyBitmask a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (VkMemoryPropertyBitmask a))
-> (VkMemoryPropertyBitmask a -> Constr)
-> (VkMemoryPropertyBitmask a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c (VkMemoryPropertyBitmask a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (VkMemoryPropertyBitmask a)))
-> ((forall b. Data b => b -> b)
    -> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryPropertyBitmask a
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> VkMemoryPropertyBitmask a
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a))
-> Data (VkMemoryPropertyBitmask a)
VkMemoryPropertyBitmask a -> DataType
VkMemoryPropertyBitmask a -> Constr
(forall b. Data b => b -> b)
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryPropertyBitmask a
-> c (VkMemoryPropertyBitmask a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryPropertyBitmask a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> u
forall u.
(forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
forall (a :: FlagType).
Typeable a =>
Typeable (VkMemoryPropertyBitmask a)
forall (a :: FlagType).
Typeable a =>
VkMemoryPropertyBitmask a -> DataType
forall (a :: FlagType).
Typeable a =>
VkMemoryPropertyBitmask a -> Constr
forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> u
forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> [u]
forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryPropertyBitmask a)
forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryPropertyBitmask a
-> c (VkMemoryPropertyBitmask a)
forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkMemoryPropertyBitmask a))
forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryPropertyBitmask a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryPropertyBitmask a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryPropertyBitmask a
-> c (VkMemoryPropertyBitmask a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (VkMemoryPropertyBitmask a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryPropertyBitmask a))
$cVkMemoryPropertyBitmask :: Constr
$tVkMemoryPropertyBitmask :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
$cgmapMo :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
gmapMp :: (forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
$cgmapMp :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
gmapM :: (forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
$cgmapM :: forall (a :: FlagType) (m :: * -> *).
(Typeable a, Monad m) =>
(forall d. Data d => d -> m d)
-> VkMemoryPropertyBitmask a -> m (VkMemoryPropertyBitmask a)
gmapQi :: Int
-> (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> u
$cgmapQi :: forall (a :: FlagType) u.
Typeable a =>
Int
-> (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> u
gmapQ :: (forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> [u]
$cgmapQ :: forall (a :: FlagType) u.
Typeable a =>
(forall d. Data d => d -> u) -> VkMemoryPropertyBitmask a -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
$cgmapQr :: forall (a :: FlagType) r r'.
Typeable a =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
$cgmapQl :: forall (a :: FlagType) r r'.
Typeable a =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> VkMemoryPropertyBitmask a
-> r
gmapT :: (forall b. Data b => b -> b)
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
$cgmapT :: forall (a :: FlagType).
Typeable a =>
(forall b. Data b => b -> b)
-> VkMemoryPropertyBitmask a -> VkMemoryPropertyBitmask a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryPropertyBitmask a))
$cdataCast2 :: forall (a :: FlagType) (t :: * -> * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VkMemoryPropertyBitmask a))
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c (VkMemoryPropertyBitmask a))
$cdataCast1 :: forall (a :: FlagType) (t :: * -> *) (c :: * -> *).
(Typeable a, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (VkMemoryPropertyBitmask a))
dataTypeOf :: VkMemoryPropertyBitmask a -> DataType
$cdataTypeOf :: forall (a :: FlagType).
Typeable a =>
VkMemoryPropertyBitmask a -> DataType
toConstr :: VkMemoryPropertyBitmask a -> Constr
$ctoConstr :: forall (a :: FlagType).
Typeable a =>
VkMemoryPropertyBitmask a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryPropertyBitmask a)
$cgunfold :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VkMemoryPropertyBitmask a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryPropertyBitmask a
-> c (VkMemoryPropertyBitmask a)
$cgfoldl :: forall (a :: FlagType) (c :: * -> *).
Typeable a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> VkMemoryPropertyBitmask a
-> c (VkMemoryPropertyBitmask a)
$cp1Data :: forall (a :: FlagType).
Typeable a =>
Typeable (VkMemoryPropertyBitmask a)
Data, (forall x.
 VkMemoryPropertyBitmask a -> Rep (VkMemoryPropertyBitmask a) x)
-> (forall x.
    Rep (VkMemoryPropertyBitmask a) x -> VkMemoryPropertyBitmask a)
-> Generic (VkMemoryPropertyBitmask a)
forall x.
Rep (VkMemoryPropertyBitmask a) x -> VkMemoryPropertyBitmask a
forall x.
VkMemoryPropertyBitmask a -> Rep (VkMemoryPropertyBitmask a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: FlagType) x.
Rep (VkMemoryPropertyBitmask a) x -> VkMemoryPropertyBitmask a
forall (a :: FlagType) x.
VkMemoryPropertyBitmask a -> Rep (VkMemoryPropertyBitmask a) x
$cto :: forall (a :: FlagType) x.
Rep (VkMemoryPropertyBitmask a) x -> VkMemoryPropertyBitmask a
$cfrom :: forall (a :: FlagType) x.
VkMemoryPropertyBitmask a -> Rep (VkMemoryPropertyBitmask a) x
Generic)

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)

deriving instance Integral (VkMemoryPropertyBitmask FlagMask)

deriving instance Num (VkMemoryPropertyBitmask FlagMask)

deriving instance Bounded (VkMemoryPropertyBitmask FlagMask)

deriving instance Enum (VkMemoryPropertyBitmask FlagMask)

deriving instance Real (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 :: 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 :: 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 :: 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 :: 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 :: 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