{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.GeneratedCommands
       (VkGeneratedCommandsInfoNV,
        VkGeneratedCommandsMemoryRequirementsInfoNV)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.BaseTypes               (VkDeviceSize)
import Graphics.Vulkan.Types.Enum.Pipeline           (VkPipelineBindPoint)
import Graphics.Vulkan.Types.Enum.StructureType      (VkStructureType)
import Graphics.Vulkan.Types.Handles                 (VkBuffer,
                                                      VkIndirectCommandsLayoutNV,
                                                      VkPipeline)
import Graphics.Vulkan.Types.Struct.IndirectCommands (VkIndirectCommandsStreamNV)

-- | > typedef struct VkGeneratedCommandsInfoNV {
--   >     VkStructureType sType;
--   >     const void*                        pNext;
--   >     VkPipelineBindPoint                pipelineBindPoint;
--   >     VkPipeline                         pipeline;
--   >     VkIndirectCommandsLayoutNV         indirectCommandsLayout;
--   >     uint32_t                           streamCount;
--   >     const VkIndirectCommandsStreamNV*  pStreams;
--   >     uint32_t                           sequencesCount;
--   >     VkBuffer                           preprocessBuffer;
--   >     VkDeviceSize                       preprocessOffset;
--   >     VkDeviceSize                       preprocessSize;
--   >     VkBuffer           sequencesCountBuffer;
--   >     VkDeviceSize       sequencesCountOffset;
--   >     VkBuffer           sequencesIndexBuffer;
--   >     VkDeviceSize       sequencesIndexOffset;
--   > } VkGeneratedCommandsInfoNV;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkGeneratedCommandsInfoNV VkGeneratedCommandsInfoNV registry at www.khronos.org>
type VkGeneratedCommandsInfoNV =
     VkStruct VkGeneratedCommandsInfoNV' -- ' closing tick for hsc2hs

data VkGeneratedCommandsInfoNV' -- ' closing tick for hsc2hs

instance VulkanMarshal VkGeneratedCommandsInfoNV where
    type StructRep VkGeneratedCommandsInfoNV =
         'StructMeta "VkGeneratedCommandsInfoNV" VkGeneratedCommandsInfoNV -- ' closing tick for hsc2hs
           (120)
{-# LINE 50 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
           8
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 53 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False 
                                                   (8)
{-# LINE 58 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipelineBindPoint" VkPipelineBindPoint 'False
                (16)
{-# LINE 63 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipeline" VkPipeline 'False 
                                                      (24)
{-# LINE 68 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "indirectCommandsLayout" VkIndirectCommandsLayoutNV -- ' closing tick for hsc2hs
                'False -- ' closing tick for hsc2hs
                (32)
{-# LINE 74 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "streamCount" Word32 'False 
                                                     (40)
{-# LINE 79 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pStreams" (Ptr VkIndirectCommandsStreamNV) 'False
                (48)
{-# LINE 84 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "sequencesCount" Word32 'False 
                                                        (56)
{-# LINE 89 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "preprocessBuffer" VkBuffer 'False 
                                                            (64)
{-# LINE 94 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "preprocessOffset" VkDeviceSize 'False 
                                                                (72)
{-# LINE 99 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "preprocessSize" VkDeviceSize 'False 
                                                              (80)
{-# LINE 104 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "sequencesCountBuffer" VkBuffer 'True 
                                                               (88)
{-# LINE 109 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "sequencesCountOffset" VkDeviceSize 'True 
                                                                   (96)
{-# LINE 114 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "sequencesIndexBuffer" VkBuffer 'True 
                                                               (104)
{-# LINE 119 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "sequencesIndexOffset" VkDeviceSize 'True 
                                                                   (112)
{-# LINE 124 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[] -- ' closing tick for hsc2hs

-- | > typedef struct VkGeneratedCommandsMemoryRequirementsInfoNV {
--   >     VkStructureType sType;
--   >     const void*                 pNext;
--   >     VkPipelineBindPoint         pipelineBindPoint;
--   >     VkPipeline                  pipeline;
--   >     VkIndirectCommandsLayoutNV  indirectCommandsLayout;
--   >     uint32_t                    maxSequencesCount;
--   > } VkGeneratedCommandsMemoryRequirementsInfoNV;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkGeneratedCommandsMemoryRequirementsInfoNV VkGeneratedCommandsMemoryRequirementsInfoNV registry at www.khronos.org>
type VkGeneratedCommandsMemoryRequirementsInfoNV =
     VkStruct VkGeneratedCommandsMemoryRequirementsInfoNV' -- ' closing tick for hsc2hs

data VkGeneratedCommandsMemoryRequirementsInfoNV' -- ' closing tick for hsc2hs

instance VulkanMarshal VkGeneratedCommandsMemoryRequirementsInfoNV
         where
    type StructRep VkGeneratedCommandsMemoryRequirementsInfoNV =
         'StructMeta "VkGeneratedCommandsMemoryRequirementsInfoNV" -- ' closing tick for hsc2hs
           VkGeneratedCommandsMemoryRequirementsInfoNV
           (48)
{-# LINE 152 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
           8
{-# LINE 153 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 155 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False 
                                                   (8)
{-# LINE 160 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipelineBindPoint" VkPipelineBindPoint 'False
                (16)
{-# LINE 165 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipeline" VkPipeline 'False 
                                                      (24)
{-# LINE 170 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "indirectCommandsLayout" VkIndirectCommandsLayoutNV -- ' closing tick for hsc2hs
                'False -- ' closing tick for hsc2hs
                (32)
{-# LINE 176 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "maxSequencesCount" Word32 'False 
                                                           (40)
{-# LINE 181 "src-gen/Graphics/Vulkan/Types/Struct/GeneratedCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[] -- ' closing tick for hsc2hs