{-# language CPP #-}
module Vulkan.Extensions.VK_NV_descriptor_pool_overallocation ( PhysicalDeviceDescriptorPoolOverallocationFeaturesNV(..)
, NV_DESCRIPTOR_POOL_OVERALLOCATION_SPEC_VERSION
, pattern NV_DESCRIPTOR_POOL_OVERALLOCATION_SPEC_VERSION
, NV_DESCRIPTOR_POOL_OVERALLOCATION_EXTENSION_NAME
, pattern NV_DESCRIPTOR_POOL_OVERALLOCATION_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_POOL_OVERALLOCATION_FEATURES_NV))
data PhysicalDeviceDescriptorPoolOverallocationFeaturesNV = PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
{
PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Bool
descriptorPoolOverallocation :: Bool }
deriving (Typeable, PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Bool
$c/= :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Bool
== :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Bool
$c== :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDescriptorPoolOverallocationFeaturesNV)
#endif
deriving instance Show PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
instance ToCStruct PhysicalDeviceDescriptorPoolOverallocationFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> (Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> IO b)
-> IO b
withCStruct PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
x Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
x (Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> IO b
f Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p PhysicalDeviceDescriptorPoolOverallocationFeaturesNV{Bool
descriptorPoolOverallocation :: Bool
$sel:descriptorPoolOverallocation:PhysicalDeviceDescriptorPoolOverallocationFeaturesNV :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_POOL_OVERALLOCATION_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorPoolOverallocation))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_POOL_OVERALLOCATION_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceDescriptorPoolOverallocationFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> IO PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
peekCStruct Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p = do
Bool32
descriptorPoolOverallocation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
descriptorPoolOverallocation)
instance Storable PhysicalDeviceDescriptorPoolOverallocationFeaturesNV where
sizeOf :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Int
sizeOf ~PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> Int
alignment ~PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> IO PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
-> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV -> IO ()
poke Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
ptr PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDescriptorPoolOverallocationFeaturesNV where
zero :: PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
zero = Bool -> PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
PhysicalDeviceDescriptorPoolOverallocationFeaturesNV
forall a. Zero a => a
zero
type NV_DESCRIPTOR_POOL_OVERALLOCATION_SPEC_VERSION = 1
pattern NV_DESCRIPTOR_POOL_OVERALLOCATION_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DESCRIPTOR_POOL_OVERALLOCATION_SPEC_VERSION :: forall a. Integral a => a
$mNV_DESCRIPTOR_POOL_OVERALLOCATION_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DESCRIPTOR_POOL_OVERALLOCATION_SPEC_VERSION = 1
type NV_DESCRIPTOR_POOL_OVERALLOCATION_EXTENSION_NAME = "VK_NV_descriptor_pool_overallocation"
pattern NV_DESCRIPTOR_POOL_OVERALLOCATION_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DESCRIPTOR_POOL_OVERALLOCATION_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_DESCRIPTOR_POOL_OVERALLOCATION_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DESCRIPTOR_POOL_OVERALLOCATION_EXTENSION_NAME = "VK_NV_descriptor_pool_overallocation"