{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_push_descriptor ( cmdPushDescriptorSetKHR
, cmdPushDescriptorSetWithTemplateKHR
, PhysicalDevicePushDescriptorPropertiesKHR(..)
, KHR_PUSH_DESCRIPTOR_SPEC_VERSION
, pattern KHR_PUSH_DESCRIPTOR_SPEC_VERSION
, KHR_PUSH_DESCRIPTOR_EXTENSION_NAME
, pattern KHR_PUSH_DESCRIPTOR_EXTENSION_NAME
) where
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
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.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core11.Handles (DescriptorUpdateTemplate)
import Vulkan.Core11.Handles (DescriptorUpdateTemplate(..))
import Vulkan.Dynamic (DeviceCmds(pVkCmdPushDescriptorSetKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdPushDescriptorSetWithTemplateKHR))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint)
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint(..))
import Vulkan.Core10.Handles (PipelineLayout)
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Core10.DescriptorSet (WriteDescriptorSet)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PUSH_DESCRIPTOR_PROPERTIES_KHR))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdPushDescriptorSetKHR
:: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr (WriteDescriptorSet a) -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr (WriteDescriptorSet a) -> IO ()
cmdPushDescriptorSetKHR :: forall io . MonadIO io => CommandBuffer -> PipelineBindPoint -> PipelineLayout -> ("set" ::: Word32) -> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)) -> io ()
cmdPushDescriptorSetKHR :: CommandBuffer
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> io ()
cmdPushDescriptorSetKHR commandBuffer :: CommandBuffer
commandBuffer pipelineBindPoint :: PipelineBindPoint
pipelineBindPoint layout :: PipelineLayout
layout set :: "set" ::: Word32
set descriptorWrites :: "descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkCmdPushDescriptorSetKHRPtr :: FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
vkCmdPushDescriptorSetKHRPtr = DeviceCmds
-> forall (a :: [*]).
FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet a))
-> IO ())
pVkCmdPushDescriptorSetKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
vkCmdPushDescriptorSetKHRPtr FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
-> FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCmdPushDescriptorSetKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCmdPushDescriptorSetKHR' :: Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ()
vkCmdPushDescriptorSetKHR' = FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
-> Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ()
forall (a :: [*]).
FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> Ptr (WriteDescriptorSet a)
-> IO ())
-> Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> Ptr (WriteDescriptorSet a)
-> IO ()
mkVkCmdPushDescriptorSetKHR FunPtr
(Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
vkCmdPushDescriptorSetKHRPtr
"pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any)
pPDescriptorWrites <- ((("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any)) -> IO ())
-> IO ())
-> ContT
() IO ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any)) -> IO ())
-> IO ())
-> ContT
() IO ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any)))
-> ((("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
-> IO ())
-> ContT
() IO ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(WriteDescriptorSet _) ((("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 64) 8
(Int -> SomeStruct WriteDescriptorSet -> ContT () IO ())
-> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct WriteDescriptorSet
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct WriteDescriptorSet)
-> SomeStruct WriteDescriptorSet -> IO () -> IO ()
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> Ptr (SomeStruct WriteDescriptorSet)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any)
pPDescriptorWrites ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> Int -> Ptr (WriteDescriptorSet _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (64 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (WriteDescriptorSet _))) (SomeStruct WriteDescriptorSet
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites)
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any))
-> IO ()
vkCmdPushDescriptorSetKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (PipelineBindPoint
pipelineBindPoint) (PipelineLayout
layout) ("set" ::: Word32
set) ((Int -> "set" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> Int)
-> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> Int
forall a b. (a -> b) -> a -> b
$ ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites)) :: Word32)) ("pDescriptorWrites" ::: Ptr (WriteDescriptorSet Any)
pPDescriptorWrites)
() -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdPushDescriptorSetWithTemplateKHR
:: FunPtr (Ptr CommandBuffer_T -> DescriptorUpdateTemplate -> PipelineLayout -> Word32 -> Ptr () -> IO ()) -> Ptr CommandBuffer_T -> DescriptorUpdateTemplate -> PipelineLayout -> Word32 -> Ptr () -> IO ()
cmdPushDescriptorSetWithTemplateKHR :: forall io . MonadIO io => CommandBuffer -> DescriptorUpdateTemplate -> PipelineLayout -> ("set" ::: Word32) -> ("data" ::: Ptr ()) -> io ()
cmdPushDescriptorSetWithTemplateKHR :: CommandBuffer
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> io ()
cmdPushDescriptorSetWithTemplateKHR commandBuffer :: CommandBuffer
commandBuffer descriptorUpdateTemplate :: DescriptorUpdateTemplate
descriptorUpdateTemplate layout :: PipelineLayout
layout set :: "set" ::: Word32
set data' :: "data" ::: Ptr ()
data' = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkCmdPushDescriptorSetWithTemplateKHRPtr :: FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
vkCmdPushDescriptorSetWithTemplateKHRPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
pVkCmdPushDescriptorSetWithTemplateKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
vkCmdPushDescriptorSetWithTemplateKHRPtr FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
-> FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCmdPushDescriptorSetWithTemplateKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCmdPushDescriptorSetWithTemplateKHR' :: Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdPushDescriptorSetWithTemplateKHR' = FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
-> Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
mkVkCmdPushDescriptorSetWithTemplateKHR FunPtr
(Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ())
vkCmdPushDescriptorSetWithTemplateKHRPtr
Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdPushDescriptorSetWithTemplateKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (DescriptorUpdateTemplate
descriptorUpdateTemplate) (PipelineLayout
layout) ("set" ::: Word32
set) ("data" ::: Ptr ()
data')
() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
data PhysicalDevicePushDescriptorPropertiesKHR = PhysicalDevicePushDescriptorPropertiesKHR
{
PhysicalDevicePushDescriptorPropertiesKHR -> "set" ::: Word32
maxPushDescriptors :: Word32 }
deriving (Typeable)
deriving instance Show PhysicalDevicePushDescriptorPropertiesKHR
instance ToCStruct PhysicalDevicePushDescriptorPropertiesKHR where
withCStruct :: PhysicalDevicePushDescriptorPropertiesKHR
-> (Ptr PhysicalDevicePushDescriptorPropertiesKHR -> IO b) -> IO b
withCStruct x :: PhysicalDevicePushDescriptorPropertiesKHR
x f :: Ptr PhysicalDevicePushDescriptorPropertiesKHR -> IO b
f = Int
-> Int
-> (Ptr PhysicalDevicePushDescriptorPropertiesKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDevicePushDescriptorPropertiesKHR -> IO b) -> IO b)
-> (Ptr PhysicalDevicePushDescriptorPropertiesKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
p -> Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePushDescriptorPropertiesKHR
p PhysicalDevicePushDescriptorPropertiesKHR
x (Ptr PhysicalDevicePushDescriptorPropertiesKHR -> IO b
f Ptr PhysicalDevicePushDescriptorPropertiesKHR
p)
pokeCStruct :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
p PhysicalDevicePushDescriptorPropertiesKHR{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PUSH_DESCRIPTOR_PROPERTIES_KHR)
Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
Ptr ("set" ::: Word32) -> ("set" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr ("set" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("set" ::: Word32
maxPushDescriptors)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PhysicalDevicePushDescriptorPropertiesKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PUSH_DESCRIPTOR_PROPERTIES_KHR)
Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
Ptr ("set" ::: Word32) -> ("set" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr ("set" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("set" ::: Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDevicePushDescriptorPropertiesKHR where
peekCStruct :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
peekCStruct p :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
p = do
"set" ::: Word32
maxPushDescriptors <- Ptr ("set" ::: Word32) -> IO ("set" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr ("set" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR)
-> PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
forall a b. (a -> b) -> a -> b
$ ("set" ::: Word32) -> PhysicalDevicePushDescriptorPropertiesKHR
PhysicalDevicePushDescriptorPropertiesKHR
"set" ::: Word32
maxPushDescriptors
instance Storable PhysicalDevicePushDescriptorPropertiesKHR where
sizeOf :: PhysicalDevicePushDescriptorPropertiesKHR -> Int
sizeOf ~PhysicalDevicePushDescriptorPropertiesKHR
_ = 24
alignment :: PhysicalDevicePushDescriptorPropertiesKHR -> Int
alignment ~PhysicalDevicePushDescriptorPropertiesKHR
_ = 8
peek :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
peek = Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> IO ()
poke ptr :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
ptr poked :: PhysicalDevicePushDescriptorPropertiesKHR
poked = Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePushDescriptorPropertiesKHR
ptr PhysicalDevicePushDescriptorPropertiesKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePushDescriptorPropertiesKHR where
zero :: PhysicalDevicePushDescriptorPropertiesKHR
zero = ("set" ::: Word32) -> PhysicalDevicePushDescriptorPropertiesKHR
PhysicalDevicePushDescriptorPropertiesKHR
"set" ::: Word32
forall a. Zero a => a
zero
type KHR_PUSH_DESCRIPTOR_SPEC_VERSION = 2
pattern KHR_PUSH_DESCRIPTOR_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_PUSH_DESCRIPTOR_SPEC_VERSION :: a
$mKHR_PUSH_DESCRIPTOR_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_PUSH_DESCRIPTOR_SPEC_VERSION = 2
type KHR_PUSH_DESCRIPTOR_EXTENSION_NAME = "VK_KHR_push_descriptor"
pattern KHR_PUSH_DESCRIPTOR_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_PUSH_DESCRIPTOR_EXTENSION_NAME :: a
$mKHR_PUSH_DESCRIPTOR_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_PUSH_DESCRIPTOR_EXTENSION_NAME = "VK_KHR_push_descriptor"