{-# language CPP #-}
-- | = Name
--
-- VK_EXT_nested_command_buffer - device extension
--
-- == VK_EXT_nested_command_buffer
--
-- [__Name String__]
--     @VK_EXT_nested_command_buffer@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     452
--
-- [__Revision__]
--     1
--
-- [__Ratification Status__]
--     Not ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_physical_device_properties2 VK_KHR_get_physical_device_properties2>
--
-- [__Contact__]
--
--     -   Piers Daniell
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_nested_command_buffer] @pdaniell-nv%0A*Here describe the issue or question you have about the VK_EXT_nested_command_buffer extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-09-18
--
-- [__Contributors__]
--
--     -   Daniel Story, Nintendo
--
--     -   Peter Kohaut, NVIDIA
--
--     -   Shahbaz Youssefi, Google
--
--     -   Slawomir Grajewski, Intel
--
--     -   Stu Smith, AMD
--
-- == Description
--
-- With core Vulkan it is not legal to call
-- 'Vulkan.Core10.CommandBufferBuilding.cmdExecuteCommands' when recording
-- a secondary command buffer. This extension relaxes that restriction,
-- allowing secondary command buffers to execute other secondary command
-- buffers.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceNestedCommandBufferFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceNestedCommandBufferPropertiesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME'
--
-- -   'EXT_NESTED_COMMAND_BUFFER_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core13.Enums.RenderingFlagBits.RenderingFlagBits':
--
--     -   'Vulkan.Core13.Enums.RenderingFlagBits.RENDERING_CONTENTS_INLINE_BIT_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_PROPERTIES_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.SubpassContents.SubpassContents':
--
--     -   'Vulkan.Core10.Enums.SubpassContents.SUBPASS_CONTENTS_INLINE_AND_SECONDARY_COMMAND_BUFFERS_EXT'
--
-- == Issues
--
-- 1) The Command Buffer Levels property for the Vulkan commands comes from
-- the @cmdbufferlevel@ attribute in @vk.xml@ for the command, and it is
-- currently not possible to modify this attribute based on whether an
-- extension is enabled. For this extension we want the @cmdbufferlevel@
-- attribute for vkCmdExecuteCommands to be @primary,secondary@ when this
-- extension is enabled and @primary@ otherwise.
--
-- __RESOLVED__: The @cmdbufferlevel@ attribute for
-- 'Vulkan.Core10.CommandBufferBuilding.cmdExecuteCommands' has been
-- changed to @primary,secondary@ and a new VUID added to prohibit
-- recording this command in a secondary command buffer unless this
-- extension is enabled.
--
-- == Version History
--
-- -   Revision 1, 2023-09-18 (Piers Daniell)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'PhysicalDeviceNestedCommandBufferFeaturesEXT',
-- 'PhysicalDeviceNestedCommandBufferPropertiesEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_nested_command_buffer Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_nested_command_buffer  ( PhysicalDeviceNestedCommandBufferFeaturesEXT(..)
                                                       , PhysicalDeviceNestedCommandBufferPropertiesEXT(..)
                                                       , EXT_NESTED_COMMAND_BUFFER_SPEC_VERSION
                                                       , pattern EXT_NESTED_COMMAND_BUFFER_SPEC_VERSION
                                                       , EXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME
                                                       , pattern EXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME
                                                       ) where

import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_PROPERTIES_EXT))
-- | VkPhysicalDeviceNestedCommandBufferFeaturesEXT - Structure describing
-- whether nested command buffers are supported by the implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceNestedCommandBufferFeaturesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceNestedCommandBufferFeaturesEXT' /can/ also be
-- used in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_nested_command_buffer VK_EXT_nested_command_buffer>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceNestedCommandBufferFeaturesEXT = PhysicalDeviceNestedCommandBufferFeaturesEXT
  { -- | #features-nestedCommandBuffer# @nestedCommandBuffer@ indicates the
    -- implementation supports nested command buffers, which allows
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary Secondary Command Buffers>
    -- to execute other
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary Secondary Command Buffers>.
    PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
nestedCommandBuffer :: Bool
  , -- | #features-nestedCommandBufferRendering# @nestedCommandBufferRendering@
    -- indicates that it is valid to call
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdExecuteCommands' inside a
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary Secondary Command Buffer>
    -- recorded with
    -- 'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_RENDER_PASS_CONTINUE_BIT'.
    PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
nestedCommandBufferRendering :: Bool
  , -- | #features-nestedCommandBufferSimultaneousUse#
    -- @nestedCommandBufferSimultaneousUse@ indicates that the implementation
    -- supports nested command buffers with command buffers that are recorded
    -- with
    -- 'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT'.
    PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
nestedCommandBufferSimultaneousUse :: Bool
  }
  deriving (Typeable, PhysicalDeviceNestedCommandBufferFeaturesEXT
-> PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceNestedCommandBufferFeaturesEXT
-> PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
$c/= :: PhysicalDeviceNestedCommandBufferFeaturesEXT
-> PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
== :: PhysicalDeviceNestedCommandBufferFeaturesEXT
-> PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
$c== :: PhysicalDeviceNestedCommandBufferFeaturesEXT
-> PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceNestedCommandBufferFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceNestedCommandBufferFeaturesEXT

instance ToCStruct PhysicalDeviceNestedCommandBufferFeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceNestedCommandBufferFeaturesEXT
-> (Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceNestedCommandBufferFeaturesEXT
x Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p PhysicalDeviceNestedCommandBufferFeaturesEXT
x (Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT -> IO b
f Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
-> PhysicalDeviceNestedCommandBufferFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p PhysicalDeviceNestedCommandBufferFeaturesEXT{Bool
nestedCommandBufferSimultaneousUse :: Bool
nestedCommandBufferRendering :: Bool
nestedCommandBuffer :: Bool
$sel:nestedCommandBufferSimultaneousUse:PhysicalDeviceNestedCommandBufferFeaturesEXT :: PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
$sel:nestedCommandBufferRendering:PhysicalDeviceNestedCommandBufferFeaturesEXT :: PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
$sel:nestedCommandBuffer:PhysicalDeviceNestedCommandBufferFeaturesEXT :: PhysicalDeviceNestedCommandBufferFeaturesEXT -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
nestedCommandBuffer))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
nestedCommandBufferRendering))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
nestedCommandBufferSimultaneousUse))
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceNestedCommandBufferFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
-> IO PhysicalDeviceNestedCommandBufferFeaturesEXT
peekCStruct Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p = do
    Bool32
nestedCommandBuffer <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    Bool32
nestedCommandBufferRendering <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Bool32
nestedCommandBufferSimultaneousUse <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool -> Bool -> PhysicalDeviceNestedCommandBufferFeaturesEXT
PhysicalDeviceNestedCommandBufferFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
nestedCommandBuffer)
             (Bool32 -> Bool
bool32ToBool Bool32
nestedCommandBufferRendering)
             (Bool32 -> Bool
bool32ToBool Bool32
nestedCommandBufferSimultaneousUse)

instance Storable PhysicalDeviceNestedCommandBufferFeaturesEXT where
  sizeOf :: PhysicalDeviceNestedCommandBufferFeaturesEXT -> Int
sizeOf ~PhysicalDeviceNestedCommandBufferFeaturesEXT
_ = Int
32
  alignment :: PhysicalDeviceNestedCommandBufferFeaturesEXT -> Int
alignment ~PhysicalDeviceNestedCommandBufferFeaturesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
-> IO PhysicalDeviceNestedCommandBufferFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
-> PhysicalDeviceNestedCommandBufferFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
ptr PhysicalDeviceNestedCommandBufferFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceNestedCommandBufferFeaturesEXT where
  zero :: PhysicalDeviceNestedCommandBufferFeaturesEXT
zero = Bool
-> Bool -> Bool -> PhysicalDeviceNestedCommandBufferFeaturesEXT
PhysicalDeviceNestedCommandBufferFeaturesEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkPhysicalDeviceNestedCommandBufferPropertiesEXT - Structure describing
-- the nested command buffer limits of an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceNestedCommandBufferPropertiesEXT'
-- structure describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceNestedCommandBufferPropertiesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_nested_command_buffer VK_EXT_nested_command_buffer>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceNestedCommandBufferPropertiesEXT = PhysicalDeviceNestedCommandBufferPropertiesEXT
  { -- | #limits-maxCommandBufferNestingLevel# @maxCommandBufferNestingLevel@
    -- indicates the maximum nesting level of calls to
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdExecuteCommands' from
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#glossary Secondary Command Buffers>.
    -- A @maxCommandBufferNestingLevel@ of @UINT32_MAX@ means there is no limit
    -- to the nesting level.
    PhysicalDeviceNestedCommandBufferPropertiesEXT -> Word32
maxCommandBufferNestingLevel :: Word32 }
  deriving (Typeable, PhysicalDeviceNestedCommandBufferPropertiesEXT
-> PhysicalDeviceNestedCommandBufferPropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceNestedCommandBufferPropertiesEXT
-> PhysicalDeviceNestedCommandBufferPropertiesEXT -> Bool
$c/= :: PhysicalDeviceNestedCommandBufferPropertiesEXT
-> PhysicalDeviceNestedCommandBufferPropertiesEXT -> Bool
== :: PhysicalDeviceNestedCommandBufferPropertiesEXT
-> PhysicalDeviceNestedCommandBufferPropertiesEXT -> Bool
$c== :: PhysicalDeviceNestedCommandBufferPropertiesEXT
-> PhysicalDeviceNestedCommandBufferPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceNestedCommandBufferPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceNestedCommandBufferPropertiesEXT

instance ToCStruct PhysicalDeviceNestedCommandBufferPropertiesEXT where
  withCStruct :: forall b.
PhysicalDeviceNestedCommandBufferPropertiesEXT
-> (Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceNestedCommandBufferPropertiesEXT
x Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p PhysicalDeviceNestedCommandBufferPropertiesEXT
x (Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT -> IO b
f Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
-> PhysicalDeviceNestedCommandBufferPropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p PhysicalDeviceNestedCommandBufferPropertiesEXT{Word32
maxCommandBufferNestingLevel :: Word32
$sel:maxCommandBufferNestingLevel:PhysicalDeviceNestedCommandBufferPropertiesEXT :: PhysicalDeviceNestedCommandBufferPropertiesEXT -> Word32
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
maxCommandBufferNestingLevel)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_NESTED_COMMAND_BUFFER_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceNestedCommandBufferPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
-> IO PhysicalDeviceNestedCommandBufferPropertiesEXT
peekCStruct Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p = do
    Word32
maxCommandBufferNestingLevel <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> PhysicalDeviceNestedCommandBufferPropertiesEXT
PhysicalDeviceNestedCommandBufferPropertiesEXT
             Word32
maxCommandBufferNestingLevel

instance Storable PhysicalDeviceNestedCommandBufferPropertiesEXT where
  sizeOf :: PhysicalDeviceNestedCommandBufferPropertiesEXT -> Int
sizeOf ~PhysicalDeviceNestedCommandBufferPropertiesEXT
_ = Int
24
  alignment :: PhysicalDeviceNestedCommandBufferPropertiesEXT -> Int
alignment ~PhysicalDeviceNestedCommandBufferPropertiesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
-> IO PhysicalDeviceNestedCommandBufferPropertiesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
-> PhysicalDeviceNestedCommandBufferPropertiesEXT -> IO ()
poke Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
ptr PhysicalDeviceNestedCommandBufferPropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

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


type EXT_NESTED_COMMAND_BUFFER_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_NESTED_COMMAND_BUFFER_SPEC_VERSION"
pattern EXT_NESTED_COMMAND_BUFFER_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_NESTED_COMMAND_BUFFER_SPEC_VERSION :: forall a. Integral a => a
$mEXT_NESTED_COMMAND_BUFFER_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_NESTED_COMMAND_BUFFER_SPEC_VERSION = 1


type EXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME = "VK_EXT_nested_command_buffer"

-- No documentation found for TopLevel "VK_EXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME"
pattern EXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_NESTED_COMMAND_BUFFER_EXTENSION_NAME = "VK_EXT_nested_command_buffer"