{-# language CPP #-} -- No documentation found for Chapter "PipelineLayout" module Vulkan.Core10.PipelineLayout ( createPipelineLayout , withPipelineLayout , destroyPipelineLayout , PushConstantRange(..) , PipelineLayoutCreateInfo(..) , PipelineLayout(..) ) where import Vulkan.Internal.Utils (traceAroundEvent) import Control.Exception.Base (bracket) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Foreign.Marshal.Alloc (allocaBytes) import Foreign.Marshal.Alloc (callocBytes) import Foreign.Marshal.Alloc (free) import GHC.Base (when) 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 Data.Vector (generateM) import qualified Data.Vector (imapM_) import qualified Data.Vector (length) import Vulkan.CStruct (FromCStruct) import Vulkan.CStruct (FromCStruct(..)) import Vulkan.CStruct (ToCStruct) import Vulkan.CStruct (ToCStruct(..)) import Vulkan.Zero (Zero(..)) import Control.Monad.IO.Class (MonadIO) 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 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.Utils (advancePtrBytes) import Vulkan.NamedType ((:::)) import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks) import Vulkan.Core10.Handles (DescriptorSetLayout) import Vulkan.Core10.Handles (Device) import Vulkan.Core10.Handles (Device(..)) import Vulkan.Core10.Handles (Device(Device)) import Vulkan.Dynamic (DeviceCmds(pVkCreatePipelineLayout)) import Vulkan.Dynamic (DeviceCmds(pVkDestroyPipelineLayout)) import Vulkan.Core10.Handles (Device_T) import Vulkan.Core10.Handles (PipelineLayout) import Vulkan.Core10.Handles (PipelineLayout(..)) import Vulkan.Core10.Enums.PipelineLayoutCreateFlagBits (PipelineLayoutCreateFlags) import Vulkan.Core10.Enums.Result (Result) import Vulkan.Core10.Enums.Result (Result(..)) import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags) import Vulkan.Core10.Enums.StructureType (StructureType) import Vulkan.Exception (VulkanException(..)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO)) import Vulkan.Core10.Enums.Result (Result(SUCCESS)) import Vulkan.Core10.Handles (PipelineLayout(..)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCreatePipelineLayout :: FunPtr (Ptr Device_T -> Ptr PipelineLayoutCreateInfo -> Ptr AllocationCallbacks -> Ptr PipelineLayout -> IO Result) -> Ptr Device_T -> Ptr PipelineLayoutCreateInfo -> Ptr AllocationCallbacks -> Ptr PipelineLayout -> IO Result -- | vkCreatePipelineLayout - Creates a new pipeline layout object -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCreatePipelineLayout-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkCreatePipelineLayout-pCreateInfo-parameter# @pCreateInfo@ -- /must/ be a valid pointer to a valid 'PipelineLayoutCreateInfo' -- structure -- -- - #VUID-vkCreatePipelineLayout-pAllocator-parameter# If @pAllocator@ -- is not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkCreatePipelineLayout-pPipelineLayout-parameter# -- @pPipelineLayout@ /must/ be a valid pointer to a -- 'Vulkan.Core10.Handles.PipelineLayout' handle -- -- == Return Codes -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>] -- -- - 'Vulkan.Core10.Enums.Result.SUCCESS' -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>] -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.PipelineLayout', -- 'PipelineLayoutCreateInfo' createPipelineLayout :: forall io . (MonadIO io) => -- | @device@ is the logical device that creates the pipeline layout. Device -> -- | @pCreateInfo@ is a pointer to a 'PipelineLayoutCreateInfo' structure -- specifying the state of the pipeline layout object. PipelineLayoutCreateInfo -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io (PipelineLayout) createPipelineLayout :: forall (io :: * -> *). MonadIO io => Device -> PipelineLayoutCreateInfo -> ("allocator" ::: Maybe AllocationCallbacks) -> io PipelineLayout createPipelineLayout Device device PipelineLayoutCreateInfo createInfo "allocator" ::: Maybe AllocationCallbacks allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCreatePipelineLayoutPtr :: FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result) vkCreatePipelineLayoutPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result) pVkCreatePipelineLayout (case Device device of Device{DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds :: DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result) vkCreatePipelineLayoutPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCreatePipelineLayout is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCreatePipelineLayout' :: Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result vkCreatePipelineLayout' = FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result) -> Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result mkVkCreatePipelineLayout FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result) vkCreatePipelineLayoutPtr "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo pCreateInfo <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (PipelineLayoutCreateInfo createInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) "pPipelineLayout" ::: Ptr PipelineLayout pPPipelineLayout <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket (forall a. Int -> IO (Ptr a) callocBytes @PipelineLayout Int 8) forall a. Ptr a -> IO () free Result r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCreatePipelineLayout" (Ptr Device_T -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO Result vkCreatePipelineLayout' (Device -> Ptr Device_T deviceHandle (Device device)) "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks pAllocator ("pPipelineLayout" ::: Ptr PipelineLayout pPPipelineLayout)) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (Result r forall a. Ord a => a -> a -> Bool < Result SUCCESS) (forall e a. Exception e => e -> IO a throwIO (Result -> VulkanException VulkanException Result r)) PipelineLayout pPipelineLayout <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> IO a peek @PipelineLayout "pPipelineLayout" ::: Ptr PipelineLayout pPPipelineLayout forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ (PipelineLayout pPipelineLayout) -- | A convenience wrapper to make a compatible pair of calls to -- 'createPipelineLayout' and 'destroyPipelineLayout' -- -- To ensure that 'destroyPipelineLayout' is always called: pass -- 'Control.Exception.bracket' (or the allocate function from your -- favourite resource management library) as the last argument. -- To just extract the pair pass '(,)' as the last argument. -- withPipelineLayout :: forall io r . MonadIO io => Device -> PipelineLayoutCreateInfo -> Maybe AllocationCallbacks -> (io PipelineLayout -> (PipelineLayout -> io ()) -> r) -> r withPipelineLayout :: forall (io :: * -> *) r. MonadIO io => Device -> PipelineLayoutCreateInfo -> ("allocator" ::: Maybe AllocationCallbacks) -> (io PipelineLayout -> (PipelineLayout -> io ()) -> r) -> r withPipelineLayout Device device PipelineLayoutCreateInfo pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator io PipelineLayout -> (PipelineLayout -> io ()) -> r b = io PipelineLayout -> (PipelineLayout -> io ()) -> r b (forall (io :: * -> *). MonadIO io => Device -> PipelineLayoutCreateInfo -> ("allocator" ::: Maybe AllocationCallbacks) -> io PipelineLayout createPipelineLayout Device device PipelineLayoutCreateInfo pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator) (\(PipelineLayout o0) -> forall (io :: * -> *). MonadIO io => Device -> PipelineLayout -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyPipelineLayout Device device PipelineLayout o0 "allocator" ::: Maybe AllocationCallbacks pAllocator) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkDestroyPipelineLayout :: FunPtr (Ptr Device_T -> PipelineLayout -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> PipelineLayout -> Ptr AllocationCallbacks -> IO () -- | vkDestroyPipelineLayout - Destroy a pipeline layout object -- -- == Valid Usage -- -- - #VUID-vkDestroyPipelineLayout-pipelineLayout-00299# If -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @pipelineLayout@ was created, a compatible set of -- callbacks /must/ be provided here -- -- - #VUID-vkDestroyPipelineLayout-pipelineLayout-00300# If no -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @pipelineLayout@ was created, @pAllocator@ /must/ be -- @NULL@ -- -- - #VUID-vkDestroyPipelineLayout-pipelineLayout-02004# @pipelineLayout@ -- /must/ not have been passed to any @vkCmd*@ command for any command -- buffers that are still in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- when 'destroyPipelineLayout' is called -- -- == Valid Usage (Implicit) -- -- - #VUID-vkDestroyPipelineLayout-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkDestroyPipelineLayout-pipelineLayout-parameter# If -- @pipelineLayout@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', -- @pipelineLayout@ /must/ be a valid -- 'Vulkan.Core10.Handles.PipelineLayout' handle -- -- - #VUID-vkDestroyPipelineLayout-pAllocator-parameter# If @pAllocator@ -- is not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkDestroyPipelineLayout-pipelineLayout-parent# If -- @pipelineLayout@ is a valid handle, it /must/ have been created, -- allocated, or retrieved from @device@ -- -- == Host Synchronization -- -- - Host access to @pipelineLayout@ /must/ be externally synchronized -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.PipelineLayout' destroyPipelineLayout :: forall io . (MonadIO io) => -- | @device@ is the logical device that destroys the pipeline layout. Device -> -- | @pipelineLayout@ is the pipeline layout to destroy. PipelineLayout -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyPipelineLayout :: forall (io :: * -> *). MonadIO io => Device -> PipelineLayout -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyPipelineLayout Device device PipelineLayout pipelineLayout "allocator" ::: Maybe AllocationCallbacks allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkDestroyPipelineLayoutPtr :: FunPtr (Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyPipelineLayoutPtr = DeviceCmds -> FunPtr (Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) pVkDestroyPipelineLayout (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyPipelineLayoutPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkDestroyPipelineLayout is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkDestroyPipelineLayout' :: Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyPipelineLayout' = FunPtr (Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () mkVkDestroyPipelineLayout FunPtr (Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyPipelineLayoutPtr "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkDestroyPipelineLayout" (Ptr Device_T -> PipelineLayout -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyPipelineLayout' (Device -> Ptr Device_T deviceHandle (Device device)) (PipelineLayout pipelineLayout) "pAllocator" ::: Ptr AllocationCallbacks pAllocator) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () -- | VkPushConstantRange - Structure specifying a push constant range -- -- == Valid Usage (Implicit) -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'PipelineLayoutCreateInfo', -- 'Vulkan.Extensions.VK_EXT_shader_object.ShaderCreateInfoEXT', -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlags' data PushConstantRange = PushConstantRange { -- | @stageFlags@ is a set of stage flags describing the shader stages that -- will access a range of push constants. If a particular stage is not -- included in the range, then accessing members of that range of push -- constants from the corresponding shader stage will return undefined -- values. -- -- #VUID-VkPushConstantRange-stageFlags-parameter# @stageFlags@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' values -- -- #VUID-VkPushConstantRange-stageFlags-requiredbitmask# @stageFlags@ -- /must/ not be @0@ PushConstantRange -> ShaderStageFlags stageFlags :: ShaderStageFlags , -- | @offset@ and @size@ are the start offset and size, respectively, -- consumed by the range. Both @offset@ and @size@ are in units of bytes -- and /must/ be a multiple of 4. The layout of the push constant variables -- is specified in the shader. -- -- #VUID-VkPushConstantRange-offset-00294# @offset@ /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@ -- -- #VUID-VkPushConstantRange-offset-00295# @offset@ /must/ be a multiple of -- @4@ PushConstantRange -> Word32 offset :: Word32 , -- | #VUID-VkPushConstantRange-size-00296# @size@ /must/ be greater than @0@ -- -- #VUID-VkPushConstantRange-size-00297# @size@ /must/ be a multiple of @4@ -- -- #VUID-VkPushConstantRange-size-00298# @size@ /must/ be less than or -- equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@ -- minus @offset@ PushConstantRange -> Word32 size :: Word32 } deriving (Typeable, PushConstantRange -> PushConstantRange -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: PushConstantRange -> PushConstantRange -> Bool $c/= :: PushConstantRange -> PushConstantRange -> Bool == :: PushConstantRange -> PushConstantRange -> Bool $c== :: PushConstantRange -> PushConstantRange -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (PushConstantRange) #endif deriving instance Show PushConstantRange instance ToCStruct PushConstantRange where withCStruct :: forall b. PushConstantRange -> (Ptr PushConstantRange -> IO b) -> IO b withCStruct PushConstantRange x Ptr PushConstantRange -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 12 forall a b. (a -> b) -> a -> b $ \Ptr PushConstantRange p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr PushConstantRange p PushConstantRange x (Ptr PushConstantRange -> IO b f Ptr PushConstantRange p) pokeCStruct :: forall b. Ptr PushConstantRange -> PushConstantRange -> IO b -> IO b pokeCStruct Ptr PushConstantRange p PushConstantRange{Word32 ShaderStageFlags size :: Word32 offset :: Word32 stageFlags :: ShaderStageFlags $sel:size:PushConstantRange :: PushConstantRange -> Word32 $sel:offset:PushConstantRange :: PushConstantRange -> Word32 $sel:stageFlags:PushConstantRange :: PushConstantRange -> ShaderStageFlags ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ShaderStageFlags)) (ShaderStageFlags stageFlags) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (Word32 offset) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) (Word32 size) IO b f cStructSize :: Int cStructSize = Int 12 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. Ptr PushConstantRange -> IO b -> IO b pokeZeroCStruct Ptr PushConstantRange p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ShaderStageFlags)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct PushConstantRange where peekCStruct :: Ptr PushConstantRange -> IO PushConstantRange peekCStruct Ptr PushConstantRange p = do ShaderStageFlags stageFlags <- forall a. Storable a => Ptr a -> IO a peek @ShaderStageFlags ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr ShaderStageFlags)) Word32 offset <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) Word32 size <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr PushConstantRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ShaderStageFlags -> Word32 -> Word32 -> PushConstantRange PushConstantRange ShaderStageFlags stageFlags Word32 offset Word32 size instance Storable PushConstantRange where sizeOf :: PushConstantRange -> Int sizeOf ~PushConstantRange _ = Int 12 alignment :: PushConstantRange -> Int alignment ~PushConstantRange _ = Int 4 peek :: Ptr PushConstantRange -> IO PushConstantRange peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr PushConstantRange -> PushConstantRange -> IO () poke Ptr PushConstantRange ptr PushConstantRange poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr PushConstantRange ptr PushConstantRange poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero PushConstantRange where zero :: PushConstantRange zero = ShaderStageFlags -> Word32 -> Word32 -> PushConstantRange PushConstantRange forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkPipelineLayoutCreateInfo - Structure specifying the parameters of a -- newly created pipeline layout object -- -- == Valid Usage -- -- - #VUID-VkPipelineLayoutCreateInfo-setLayoutCount-00286# -- @setLayoutCount@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxBoundDescriptorSets@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03016# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER' and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageDescriptorSamplers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03017# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageDescriptorUniformBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03018# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageDescriptorStorageBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-06939# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER', -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE', -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLE_WEIGHT_IMAGE_QCOM', -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_BLOCK_MATCH_IMAGE_QCOM', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER', -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageDescriptorSampledImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03020# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageDescriptorStorageImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03021# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageDescriptorInputAttachments@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-02214# The total -- number of bindings in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set and with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK' -- accessible to any given shader stage across all elements of -- @pSetLayouts@, /must/ be less than or equal to -- 'Vulkan.Core13.Promoted_From_VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockProperties'::@maxPerStageDescriptorInlineUniformBlocks@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03022# The total -- number of descriptors with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER' and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxPerStageDescriptorUpdateAfterBindSamplers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03023# The total -- number of descriptors with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxPerStageDescriptorUpdateAfterBindUniformBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03024# The total -- number of descriptors with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxPerStageDescriptorUpdateAfterBindStorageBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03025# The total -- number of descriptors with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER', -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxPerStageDescriptorUpdateAfterBindSampledImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03026# The total -- number of descriptors with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxPerStageDescriptorUpdateAfterBindStorageImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03027# The total -- number of descriptors with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxPerStageDescriptorUpdateAfterBindInputAttachments@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-02215# The total -- number of bindings with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core13.Promoted_From_VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockProperties'::@maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03028# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER' and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetSamplers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03029# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetUniformBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03030# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetUniformBuffersDynamic@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03031# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetStorageBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03032# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetStorageBuffersDynamic@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03033# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER', -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetSampledImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03034# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetStorageImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03035# The total -- number of descriptors in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDescriptorSetInputAttachments@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-02216# The total -- number of bindings in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core13.Promoted_From_VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockProperties'::@maxDescriptorSetInlineUniformBlocks@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03036# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER' and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindSamplers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03037# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindUniformBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03038# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindUniformBuffersDynamic@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03039# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindStorageBuffers@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03040# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindStorageBuffersDynamic@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03041# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER', -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindSampledImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03042# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE', -- and -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindStorageImages@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-03043# The total number -- of descriptors of the type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties'::@maxDescriptorSetUpdateAfterBindInputAttachments@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-02217# The total -- number of bindings with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core13.Promoted_From_VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockProperties'::@maxDescriptorSetUpdateAfterBindInlineUniformBlocks@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-06531# The total -- number of descriptors with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Core13.PhysicalDeviceVulkan13Properties'::@maxInlineUniformTotalSize@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pPushConstantRanges-00292# Any two -- elements of @pPushConstantRanges@ /must/ not include the same stage -- in @stageFlags@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-00293# @pSetLayouts@ -- /must/ not contain more than one descriptor set layout that was -- created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR' -- set -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03571# The total -- number of bindings in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Extensions.VK_KHR_acceleration_structure.PhysicalDeviceAccelerationStructurePropertiesKHR'::@maxPerStageDescriptorAccelerationStructures@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03572# The total -- number of bindings with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR' -- accessible to any given shader stage across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Extensions.VK_KHR_acceleration_structure.PhysicalDeviceAccelerationStructurePropertiesKHR'::@maxPerStageDescriptorUpdateAfterBindAccelerationStructures@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03573# The total -- number of bindings in descriptor set layouts created without the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT' -- bit set with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Extensions.VK_KHR_acceleration_structure.PhysicalDeviceAccelerationStructurePropertiesKHR'::@maxDescriptorSetAccelerationStructures@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-03574# The total -- number of bindings with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_KHR' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Extensions.VK_KHR_acceleration_structure.PhysicalDeviceAccelerationStructurePropertiesKHR'::@maxDescriptorSetUpdateAfterBindAccelerationStructures@ -- -- - #VUID-VkPipelineLayoutCreateInfo-descriptorType-02381# The total -- number of bindings with a @descriptorType@ of -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_ACCELERATION_STRUCTURE_NV' -- accessible across all shader stages and across all elements of -- @pSetLayouts@ /must/ be less than or equal to -- 'Vulkan.Extensions.VK_NV_ray_tracing.PhysicalDeviceRayTracingPropertiesNV'::@maxDescriptorSetAccelerationStructures@ -- -- - #VUID-VkPipelineLayoutCreateInfo-pImmutableSamplers-03566# The total -- number of @pImmutableSamplers@ created with @flags@ containing -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_SUBSAMPLED_BIT_EXT' -- or -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT' -- across all shader stages and across all elements of @pSetLayouts@ -- /must/ be less than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxDescriptorSetSubsampledSamplers ::maxDescriptorSetSubsampledSamplers> -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-04606# Any element of -- @pSetLayouts@ /must/ not have been created with the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_HOST_ONLY_POOL_BIT_EXT' -- bit set -- -- - #VUID-VkPipelineLayoutCreateInfo-graphicsPipelineLibrary-06753# If -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-graphicsPipelineLibrary graphicsPipelineLibrary> -- is not enabled, elements of @pSetLayouts@ /must/ be valid -- 'Vulkan.Core10.Handles.DescriptorSetLayout' objects -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-08008# If any element -- of @pSetLayouts@ was created with the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- bit set, all elements of @pSetLayouts@ /must/ have been created with -- the -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- bit set -- -- == Valid Usage (Implicit) -- -- - #VUID-VkPipelineLayoutCreateInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO' -- -- - #VUID-VkPipelineLayoutCreateInfo-pNext-pNext# @pNext@ /must/ be -- @NULL@ -- -- - #VUID-VkPipelineLayoutCreateInfo-flags-parameter# @flags@ /must/ be -- a valid combination of -- 'Vulkan.Core10.Enums.PipelineLayoutCreateFlagBits.PipelineLayoutCreateFlagBits' -- values -- -- - #VUID-VkPipelineLayoutCreateInfo-pSetLayouts-parameter# If -- @setLayoutCount@ is not @0@, @pSetLayouts@ /must/ be a valid pointer -- to an array of @setLayoutCount@ valid or -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- 'Vulkan.Core10.Handles.DescriptorSetLayout' handles -- -- - #VUID-VkPipelineLayoutCreateInfo-pPushConstantRanges-parameter# If -- @pushConstantRangeCount@ is not @0@, @pPushConstantRanges@ /must/ be -- a valid pointer to an array of @pushConstantRangeCount@ valid -- 'PushConstantRange' structures -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.DescriptorSetLayout', -- 'Vulkan.Core10.Enums.PipelineLayoutCreateFlagBits.PipelineLayoutCreateFlags', -- 'PushConstantRange', 'Vulkan.Core10.Enums.StructureType.StructureType', -- 'createPipelineLayout' data PipelineLayoutCreateInfo = PipelineLayoutCreateInfo { -- | @flags@ is a bitmask of -- 'Vulkan.Core10.Enums.PipelineLayoutCreateFlagBits.PipelineLayoutCreateFlagBits' -- specifying options for pipeline layout creation. PipelineLayoutCreateInfo -> PipelineLayoutCreateFlags flags :: PipelineLayoutCreateFlags , -- | @pSetLayouts@ is a pointer to an array of -- 'Vulkan.Core10.Handles.DescriptorSetLayout' objects. PipelineLayoutCreateInfo -> Vector DescriptorSetLayout setLayouts :: Vector DescriptorSetLayout , -- | @pPushConstantRanges@ is a pointer to an array of 'PushConstantRange' -- structures defining a set of push constant ranges for use in a single -- pipeline layout. In addition to descriptor set layouts, a pipeline -- layout also describes how many push constants /can/ be accessed by each -- stage of the pipeline. -- -- Note -- -- Push constants represent a high speed path to modify constant data in -- pipelines that is expected to outperform memory-backed resource updates. PipelineLayoutCreateInfo -> Vector PushConstantRange pushConstantRanges :: Vector PushConstantRange } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (PipelineLayoutCreateInfo) #endif deriving instance Show PipelineLayoutCreateInfo instance ToCStruct PipelineLayoutCreateInfo where withCStruct :: forall b. PipelineLayoutCreateInfo -> (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b) -> IO b withCStruct PipelineLayoutCreateInfo x ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 48 forall a b. (a -> b) -> a -> b $ \"pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p PipelineLayoutCreateInfo x (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b f "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p) pokeCStruct :: forall b. ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> PipelineLayoutCreateInfo -> IO b -> IO b pokeCStruct "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p PipelineLayoutCreateInfo{Vector DescriptorSetLayout Vector PushConstantRange PipelineLayoutCreateFlags pushConstantRanges :: Vector PushConstantRange setLayouts :: Vector DescriptorSetLayout flags :: PipelineLayoutCreateFlags $sel:pushConstantRanges:PipelineLayoutCreateInfo :: PipelineLayoutCreateInfo -> Vector PushConstantRange $sel:setLayouts:PipelineLayoutCreateInfo :: PipelineLayoutCreateInfo -> Vector DescriptorSetLayout $sel:flags:PipelineLayoutCreateInfo :: PipelineLayoutCreateInfo -> PipelineLayoutCreateFlags ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr PipelineLayoutCreateFlags)) (PipelineLayoutCreateFlags flags) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector DescriptorSetLayout setLayouts)) :: Word32)) Ptr DescriptorSetLayout pPSetLayouts' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @DescriptorSetLayout ((forall a. Vector a -> Int Data.Vector.length (Vector DescriptorSetLayout setLayouts)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i DescriptorSetLayout e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr DescriptorSetLayout pPSetLayouts' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr DescriptorSetLayout) (DescriptorSetLayout e)) (Vector DescriptorSetLayout setLayouts) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr DescriptorSetLayout))) (Ptr DescriptorSetLayout pPSetLayouts') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector PushConstantRange pushConstantRanges)) :: Word32)) Ptr PushConstantRange pPPushConstantRanges' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @PushConstantRange ((forall a. Vector a -> Int Data.Vector.length (Vector PushConstantRange pushConstantRanges)) forall a. Num a => a -> a -> a * Int 12) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i PushConstantRange e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr PushConstantRange pPPushConstantRanges' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 12 forall a. Num a => a -> a -> a * (Int i)) :: Ptr PushConstantRange) (PushConstantRange e)) (Vector PushConstantRange pushConstantRanges) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr PushConstantRange))) (Ptr PushConstantRange pPPushConstantRanges') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 48 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b -> IO b pokeZeroCStruct "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO) forall a. Storable a => Ptr a -> a -> IO () poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) IO b f instance FromCStruct PipelineLayoutCreateInfo where peekCStruct :: ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO PipelineLayoutCreateInfo peekCStruct "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p = do PipelineLayoutCreateFlags flags <- forall a. Storable a => Ptr a -> IO a peek @PipelineLayoutCreateFlags (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr PipelineLayoutCreateFlags)) Word32 setLayoutCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) Ptr DescriptorSetLayout pSetLayouts <- forall a. Storable a => Ptr a -> IO a peek @(Ptr DescriptorSetLayout) (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr DescriptorSetLayout))) Vector DescriptorSetLayout pSetLayouts' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 setLayoutCount) (\Int i -> forall a. Storable a => Ptr a -> IO a peek @DescriptorSetLayout ((Ptr DescriptorSetLayout pSetLayouts forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr DescriptorSetLayout))) Word32 pushConstantRangeCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) Ptr PushConstantRange pPushConstantRanges <- forall a. Storable a => Ptr a -> IO a peek @(Ptr PushConstantRange) (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr PushConstantRange))) Vector PushConstantRange pPushConstantRanges' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 pushConstantRangeCount) (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @PushConstantRange ((Ptr PushConstantRange pPushConstantRanges forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 12 forall a. Num a => a -> a -> a * (Int i)) :: Ptr PushConstantRange))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ PipelineLayoutCreateFlags -> Vector DescriptorSetLayout -> Vector PushConstantRange -> PipelineLayoutCreateInfo PipelineLayoutCreateInfo PipelineLayoutCreateFlags flags Vector DescriptorSetLayout pSetLayouts' Vector PushConstantRange pPushConstantRanges' instance Zero PipelineLayoutCreateInfo where zero :: PipelineLayoutCreateInfo zero = PipelineLayoutCreateFlags -> Vector DescriptorSetLayout -> Vector PushConstantRange -> PipelineLayoutCreateInfo PipelineLayoutCreateInfo forall a. Zero a => a zero forall a. Monoid a => a mempty forall a. Monoid a => a mempty