{-# language CPP #-}
module Vulkan.Core10.PipelineLayout  ( createPipelineLayout
                                     , withPipelineLayout
                                     , destroyPipelineLayout
                                     , PushConstantRange(..)
                                     , PipelineLayoutCreateInfo(..)
                                     , PipelineLayout(..)
                                     ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
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 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.Dynamic (DeviceCmds(pVkCreatePipelineLayout))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyPipelineLayout))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (PipelineLayout)
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.Core10.Enums.PipelineLayoutCreateFlags (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.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
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)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pCreateInfo@ /must/ be a valid pointer to a valid
--     'PipelineLayoutCreateInfo' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @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
--
-- '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://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                        -- chapter.
                        ("allocator" ::: Maybe AllocationCallbacks)
                     -> io (PipelineLayout)
createPipelineLayout :: Device
-> PipelineLayoutCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineLayout
createPipelineLayout device :: Device
device createInfo :: PipelineLayoutCreateInfo
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO PipelineLayout -> io PipelineLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PipelineLayout -> io PipelineLayout)
-> (ContT PipelineLayout IO PipelineLayout -> IO PipelineLayout)
-> ContT PipelineLayout IO PipelineLayout
-> io PipelineLayout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT PipelineLayout IO PipelineLayout -> IO PipelineLayout
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT PipelineLayout IO PipelineLayout -> io PipelineLayout)
-> ContT PipelineLayout IO PipelineLayout -> io PipelineLayout
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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT PipelineLayout IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PipelineLayout IO ())
-> IO () -> ContT PipelineLayout IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineLayout" ::: Ptr PipelineLayout)
   -> IO Result)
vkCreatePipelineLayoutPtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineLayout" ::: Ptr PipelineLayout)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelineLayout" ::: Ptr PipelineLayout)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineLayout" ::: Ptr PipelineLayout)
   -> IO Result)
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 vkCreatePipelineLayout is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
  -> IO PipelineLayout)
 -> IO PipelineLayout)
-> ContT
     PipelineLayout IO ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
   -> IO PipelineLayout)
  -> IO PipelineLayout)
 -> ContT
      PipelineLayout IO ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo))
-> ((("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
     -> IO PipelineLayout)
    -> IO PipelineLayout)
-> ContT
     PipelineLayout IO ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
forall a b. (a -> b) -> a -> b
$ PipelineLayoutCreateInfo
-> (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
    -> IO PipelineLayout)
-> IO PipelineLayout
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
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     PipelineLayout IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO PipelineLayout)
 -> IO PipelineLayout)
-> ContT
     PipelineLayout IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO PipelineLayout)
  -> IO PipelineLayout)
 -> ContT
      PipelineLayout IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO PipelineLayout)
    -> IO PipelineLayout)
-> ContT
     PipelineLayout IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks)
    -> IO PipelineLayout)
-> IO PipelineLayout
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pPipelineLayout" ::: Ptr PipelineLayout
pPPipelineLayout <- ((("pPipelineLayout" ::: Ptr PipelineLayout) -> IO PipelineLayout)
 -> IO PipelineLayout)
-> ContT
     PipelineLayout IO ("pPipelineLayout" ::: Ptr PipelineLayout)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPipelineLayout" ::: Ptr PipelineLayout) -> IO PipelineLayout)
  -> IO PipelineLayout)
 -> ContT
      PipelineLayout IO ("pPipelineLayout" ::: Ptr PipelineLayout))
-> ((("pPipelineLayout" ::: Ptr PipelineLayout)
     -> IO PipelineLayout)
    -> IO PipelineLayout)
-> ContT
     PipelineLayout IO ("pPipelineLayout" ::: Ptr PipelineLayout)
forall a b. (a -> b) -> a -> b
$ IO ("pPipelineLayout" ::: Ptr PipelineLayout)
-> (("pPipelineLayout" ::: Ptr PipelineLayout) -> IO ())
-> (("pPipelineLayout" ::: Ptr PipelineLayout)
    -> IO PipelineLayout)
-> IO PipelineLayout
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPipelineLayout" ::: Ptr PipelineLayout)
forall a. Int -> IO (Ptr a)
callocBytes @PipelineLayout 8) ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT PipelineLayout IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT PipelineLayout IO Result)
-> IO Result -> ContT PipelineLayout IO Result
forall a b. (a -> b) -> a -> b
$ 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)
  IO () -> ContT PipelineLayout IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PipelineLayout IO ())
-> IO () -> ContT PipelineLayout IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  PipelineLayout
pPipelineLayout <- IO PipelineLayout -> ContT PipelineLayout IO PipelineLayout
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PipelineLayout -> ContT PipelineLayout IO PipelineLayout)
-> IO PipelineLayout -> ContT PipelineLayout IO PipelineLayout
forall a b. (a -> b) -> a -> b
$ ("pPipelineLayout" ::: Ptr PipelineLayout) -> IO PipelineLayout
forall a. Storable a => Ptr a -> IO a
peek @PipelineLayout "pPipelineLayout" ::: Ptr PipelineLayout
pPPipelineLayout
  PipelineLayout -> ContT PipelineLayout IO PipelineLayout
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineLayout -> ContT PipelineLayout IO PipelineLayout)
-> PipelineLayout -> ContT PipelineLayout IO PipelineLayout
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 first argument.
-- To just extract the pair pass '(,)' as the first argument.
--
withPipelineLayout :: forall io r . MonadIO io => Device -> PipelineLayoutCreateInfo -> Maybe AllocationCallbacks -> (io (PipelineLayout) -> ((PipelineLayout) -> io ()) -> r) -> r
withPipelineLayout :: Device
-> PipelineLayoutCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io PipelineLayout -> (PipelineLayout -> io ()) -> r)
-> r
withPipelineLayout device :: Device
device pCreateInfo :: PipelineLayoutCreateInfo
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io PipelineLayout -> (PipelineLayout -> io ()) -> r
b =
  io PipelineLayout -> (PipelineLayout -> io ()) -> r
b (Device
-> PipelineLayoutCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineLayout
forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineLayoutCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineLayout
createPipelineLayout Device
device PipelineLayoutCreateInfo
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(PipelineLayout
o0) -> Device
-> PipelineLayout
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
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
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @pipelineLayout@ was created, a compatible set of
--     callbacks /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @pipelineLayout@ was created, @pAllocator@ /must/ be
--     @NULL@
--
-- -   @pipelineLayout@ /must/ not have been passed to any @vkCmd*@ command
--     for any command buffers that are still in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--     when 'destroyPipelineLayout' is called
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @pipelineLayout@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @pipelineLayout@ /must/ be a valid
--     'Vulkan.Core10.Handles.PipelineLayout' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   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
--
-- '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://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                         -- chapter.
                         ("allocator" ::: Maybe AllocationCallbacks)
                      -> io ()
destroyPipelineLayout :: Device
-> PipelineLayout
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPipelineLayout device :: Device
device pipelineLayout :: PipelineLayout
pipelineLayout allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = 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 vkDestroyPipelineLayoutPtr :: FunPtr
  (Ptr Device_T
   -> PipelineLayout
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyPipelineLayoutPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PipelineLayout
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyPipelineLayout (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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 Device_T
   -> PipelineLayout
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyPipelineLayoutPtr FunPtr
  (Ptr Device_T
   -> PipelineLayout
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> PipelineLayout
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PipelineLayout
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> 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 vkDestroyPipelineLayout is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  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 Device_T
-> PipelineLayout
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyPipelineLayout' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PipelineLayout
pipelineLayout) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkPushConstantRange - Structure specifying a push constant range
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'PipelineLayoutCreateInfo',
-- '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.
    --
    -- @stageFlags@ /must/ be a valid combination of
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' values
    --
    -- @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.
    --
    -- @offset@ /must/ be less than
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@
    --
    -- @offset@ /must/ be a multiple of @4@
    PushConstantRange -> Word32
offset :: Word32
  , -- | @size@ /must/ be greater than @0@
    --
    -- @size@ /must/ be a multiple of @4@
    --
    -- @size@ /must/ be less than or equal to
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPushConstantsSize@
    -- minus @offset@
    PushConstantRange -> Word32
size :: Word32
  }
  deriving (Typeable, PushConstantRange -> PushConstantRange -> Bool
(PushConstantRange -> PushConstantRange -> Bool)
-> (PushConstantRange -> PushConstantRange -> Bool)
-> Eq PushConstantRange
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 :: PushConstantRange -> (Ptr PushConstantRange -> IO b) -> IO b
withCStruct x :: PushConstantRange
x f :: Ptr PushConstantRange -> IO b
f = Int -> Int -> (Ptr PushConstantRange -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((Ptr PushConstantRange -> IO b) -> IO b)
-> (Ptr PushConstantRange -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PushConstantRange
p -> Ptr PushConstantRange -> PushConstantRange -> IO b -> IO b
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 :: Ptr PushConstantRange -> PushConstantRange -> IO b -> IO b
pokeCStruct p :: Ptr PushConstantRange
p PushConstantRange{..} f :: IO b
f = do
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ShaderStageFlags)) (ShaderStageFlags
stageFlags)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
offset)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
size)
    IO b
f
  cStructSize :: Int
cStructSize = 12
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr PushConstantRange -> IO b -> IO b
pokeZeroCStruct p :: Ptr PushConstantRange
p f :: IO b
f = do
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ShaderStageFlags)) (ShaderStageFlags
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PushConstantRange where
  peekCStruct :: Ptr PushConstantRange -> IO PushConstantRange
peekCStruct p :: Ptr PushConstantRange
p = do
    ShaderStageFlags
stageFlags <- Ptr ShaderStageFlags -> IO ShaderStageFlags
forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ShaderStageFlags))
    Word32
offset <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
size <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PushConstantRange
p Ptr PushConstantRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    PushConstantRange -> IO PushConstantRange
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PushConstantRange -> IO PushConstantRange)
-> PushConstantRange -> IO PushConstantRange
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
_ = 12
  alignment :: PushConstantRange -> Int
alignment ~PushConstantRange
_ = 4
  peek :: Ptr PushConstantRange -> IO PushConstantRange
peek = Ptr PushConstantRange -> IO PushConstantRange
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PushConstantRange -> PushConstantRange -> IO ()
poke ptr :: Ptr PushConstantRange
ptr poked :: PushConstantRange
poked = Ptr PushConstantRange -> PushConstantRange -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PushConstantRange
ptr PushConstantRange
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PushConstantRange where
  zero :: PushConstantRange
zero = ShaderStageFlags -> Word32 -> Word32 -> PushConstantRange
PushConstantRange
           ShaderStageFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkPipelineLayoutCreateInfo - Structure specifying the parameters of a
-- newly created pipeline layout object
--
-- == Valid Usage
--
-- -   @setLayoutCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxBoundDescriptorSets@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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 to any given shader stage across all elements of
--     @pSetLayouts@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageDescriptorSampledImages@
--
-- -   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@
--
-- -   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@
--
-- -   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_EXT'
--     accessible to any given shader stage across all elements of
--     @pSetLayouts@ /must/ be less than or equal to
--     'Vulkan.Extensions.VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockPropertiesEXT'::@maxPerStageDescriptorInlineUniformBlocks@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   The total number of bindings with a @descriptorType@ of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT'
--     accessible to any given shader stage across all elements of
--     @pSetLayouts@ /must/ be less than or equal to
--     'Vulkan.Extensions.VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockPropertiesEXT'::@maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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_EXT'
--     accessible across all shader stages and across all elements of
--     @pSetLayouts@ /must/ be less than or equal to
--     'Vulkan.Extensions.VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockPropertiesEXT'::@maxDescriptorSetInlineUniformBlocks@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   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@
--
-- -   The total number of bindings with a @descriptorType@ of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INLINE_UNIFORM_BLOCK_EXT'
--     accessible across all shader stages and across all elements of
--     @pSetLayouts@ /must/ be less than or equal to
--     'Vulkan.Extensions.VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockPropertiesEXT'::@maxDescriptorSetUpdateAfterBindInlineUniformBlocks@
--
-- -   Any two elements of @pPushConstantRanges@ /must/ not include the
--     same stage in @stageFlags@
--
-- -   @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
--
-- -   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_ray_tracing.PhysicalDeviceRayTracingPropertiesKHR'::@maxDescriptorSetAccelerationStructures@
--
-- -   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://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxDescriptorSetSubsampledSamplers ::maxDescriptorSetSubsampledSamplers>
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @flags@ /must/ be @0@
--
-- -   If @setLayoutCount@ is not @0@, @pSetLayouts@ /must/ be a valid
--     pointer to an array of @setLayoutCount@ valid
--     'Vulkan.Core10.Handles.DescriptorSetLayout' handles
--
-- -   If @pushConstantRangeCount@ is not @0@, @pPushConstantRanges@ /must/
--     be a valid pointer to an array of @pushConstantRangeCount@ valid
--     'PushConstantRange' structures
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.DescriptorSetLayout',
-- 'Vulkan.Core10.Enums.PipelineLayoutCreateFlags.PipelineLayoutCreateFlags',
-- 'PushConstantRange', 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createPipelineLayout'
data PipelineLayoutCreateInfo = PipelineLayoutCreateInfo
  { -- | @flags@ is reserved for future use.
    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 :: PipelineLayoutCreateInfo
-> (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b)
-> IO b
withCStruct x :: PipelineLayoutCreateInfo
x f :: ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b
f = Int
-> Int
-> (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b)
 -> IO b)
-> (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p -> ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> PipelineLayoutCreateInfo -> IO b -> IO b
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 :: ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> PipelineLayoutCreateInfo -> IO b -> IO b
pokeCStruct p :: "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p PipelineLayoutCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineLayoutCreateFlags -> PipelineLayoutCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr PipelineLayoutCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineLayoutCreateFlags)) (PipelineLayoutCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector DescriptorSetLayout -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DescriptorSetLayout -> Int)
-> Vector DescriptorSetLayout -> Int
forall a b. (a -> b) -> a -> b
$ (Vector DescriptorSetLayout
setLayouts)) :: Word32))
    Ptr DescriptorSetLayout
pPSetLayouts' <- ((Ptr DescriptorSetLayout -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorSetLayout)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DescriptorSetLayout -> IO b) -> IO b)
 -> ContT b IO (Ptr DescriptorSetLayout))
-> ((Ptr DescriptorSetLayout -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorSetLayout)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DescriptorSetLayout -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DescriptorSetLayout ((Vector DescriptorSetLayout -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DescriptorSetLayout
setLayouts)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> DescriptorSetLayout -> IO ())
-> Vector DescriptorSetLayout -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DescriptorSetLayout
e -> Ptr DescriptorSetLayout -> DescriptorSetLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DescriptorSetLayout
pPSetLayouts' Ptr DescriptorSetLayout -> Int -> Ptr DescriptorSetLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorSetLayout) (DescriptorSetLayout
e)) (Vector DescriptorSetLayout
setLayouts)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr DescriptorSetLayout) -> Ptr DescriptorSetLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr DescriptorSetLayout)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DescriptorSetLayout))) (Ptr DescriptorSetLayout
pPSetLayouts')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector PushConstantRange -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector PushConstantRange -> Int)
-> Vector PushConstantRange -> Int
forall a b. (a -> b) -> a -> b
$ (Vector PushConstantRange
pushConstantRanges)) :: Word32))
    Ptr PushConstantRange
pPPushConstantRanges' <- ((Ptr PushConstantRange -> IO b) -> IO b)
-> ContT b IO (Ptr PushConstantRange)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PushConstantRange -> IO b) -> IO b)
 -> ContT b IO (Ptr PushConstantRange))
-> ((Ptr PushConstantRange -> IO b) -> IO b)
-> ContT b IO (Ptr PushConstantRange)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr PushConstantRange -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @PushConstantRange ((Vector PushConstantRange -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector PushConstantRange
pushConstantRanges)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 12) 4
    (Int -> PushConstantRange -> ContT b IO ())
-> Vector PushConstantRange -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: PushConstantRange
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PushConstantRange -> PushConstantRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr PushConstantRange
pPPushConstantRanges' Ptr PushConstantRange -> Int -> Ptr PushConstantRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PushConstantRange) (PushConstantRange
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector PushConstantRange
pushConstantRanges)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PushConstantRange) -> Ptr PushConstantRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr PushConstantRange)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr PushConstantRange))) (Ptr PushConstantRange
pPPushConstantRanges')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo) -> IO b -> IO b
pokeZeroCStruct p :: "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DescriptorSetLayout
pPSetLayouts' <- ((Ptr DescriptorSetLayout -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorSetLayout)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DescriptorSetLayout -> IO b) -> IO b)
 -> ContT b IO (Ptr DescriptorSetLayout))
-> ((Ptr DescriptorSetLayout -> IO b) -> IO b)
-> ContT b IO (Ptr DescriptorSetLayout)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DescriptorSetLayout -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DescriptorSetLayout ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> DescriptorSetLayout -> IO ())
-> Vector DescriptorSetLayout -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DescriptorSetLayout
e -> Ptr DescriptorSetLayout -> DescriptorSetLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DescriptorSetLayout
pPSetLayouts' Ptr DescriptorSetLayout -> Int -> Ptr DescriptorSetLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorSetLayout) (DescriptorSetLayout
e)) (Vector DescriptorSetLayout
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr DescriptorSetLayout) -> Ptr DescriptorSetLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr DescriptorSetLayout)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DescriptorSetLayout))) (Ptr DescriptorSetLayout
pPSetLayouts')
    Ptr PushConstantRange
pPPushConstantRanges' <- ((Ptr PushConstantRange -> IO b) -> IO b)
-> ContT b IO (Ptr PushConstantRange)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PushConstantRange -> IO b) -> IO b)
 -> ContT b IO (Ptr PushConstantRange))
-> ((Ptr PushConstantRange -> IO b) -> IO b)
-> ContT b IO (Ptr PushConstantRange)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr PushConstantRange -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @PushConstantRange ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 12) 4
    (Int -> PushConstantRange -> ContT b IO ())
-> Vector PushConstantRange -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: PushConstantRange
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PushConstantRange -> PushConstantRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr PushConstantRange
pPPushConstantRanges' Ptr PushConstantRange -> Int -> Ptr PushConstantRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PushConstantRange) (PushConstantRange
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector PushConstantRange
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PushConstantRange) -> Ptr PushConstantRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr PushConstantRange)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr PushConstantRange))) (Ptr PushConstantRange
pPPushConstantRanges')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct PipelineLayoutCreateInfo where
  peekCStruct :: ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> IO PipelineLayoutCreateInfo
peekCStruct p :: "pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p = do
    PipelineLayoutCreateFlags
flags <- Ptr PipelineLayoutCreateFlags -> IO PipelineLayoutCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineLayoutCreateFlags (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr PipelineLayoutCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineLayoutCreateFlags))
    Word32
setLayoutCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr DescriptorSetLayout
pSetLayouts <- Ptr (Ptr DescriptorSetLayout) -> IO (Ptr DescriptorSetLayout)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DescriptorSetLayout) (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr DescriptorSetLayout)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DescriptorSetLayout)))
    Vector DescriptorSetLayout
pSetLayouts' <- Int
-> (Int -> IO DescriptorSetLayout)
-> IO (Vector DescriptorSetLayout)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
setLayoutCount) (\i :: Int
i -> Ptr DescriptorSetLayout -> IO DescriptorSetLayout
forall a. Storable a => Ptr a -> IO a
peek @DescriptorSetLayout ((Ptr DescriptorSetLayout
pSetLayouts Ptr DescriptorSetLayout -> Int -> Ptr DescriptorSetLayout
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DescriptorSetLayout)))
    Word32
pushConstantRangeCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr PushConstantRange
pPushConstantRanges <- Ptr (Ptr PushConstantRange) -> IO (Ptr PushConstantRange)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PushConstantRange) (("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo
p ("pCreateInfo" ::: Ptr PipelineLayoutCreateInfo)
-> Int -> Ptr (Ptr PushConstantRange)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr PushConstantRange)))
    Vector PushConstantRange
pPushConstantRanges' <- Int
-> (Int -> IO PushConstantRange) -> IO (Vector PushConstantRange)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
pushConstantRangeCount) (\i :: Int
i -> Ptr PushConstantRange -> IO PushConstantRange
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PushConstantRange ((Ptr PushConstantRange
pPushConstantRanges Ptr PushConstantRange -> Int -> Ptr PushConstantRange
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PushConstantRange)))
    PipelineLayoutCreateInfo -> IO PipelineLayoutCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineLayoutCreateInfo -> IO PipelineLayoutCreateInfo)
-> PipelineLayoutCreateInfo -> IO PipelineLayoutCreateInfo
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
           PipelineLayoutCreateFlags
forall a. Zero a => a
zero
           Vector DescriptorSetLayout
forall a. Monoid a => a
mempty
           Vector PushConstantRange
forall a. Monoid a => a
mempty