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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.IndirectCommands
       (VkIndirectCommandsLayoutCreateInfoNV,
        VkIndirectCommandsLayoutTokenNV, VkIndirectCommandsStreamNV)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.BaseTypes          (VkBool32, VkDeviceSize)
import Graphics.Vulkan.Types.Enum.IndexType     (VkIndexType)
import Graphics.Vulkan.Types.Enum.Indirect      (VkIndirectCommandsLayoutUsageFlagsNV,
                                                 VkIndirectCommandsTokenTypeNV,
                                                 VkIndirectStateFlagsNV)
import Graphics.Vulkan.Types.Enum.Pipeline      (VkPipelineBindPoint)
import Graphics.Vulkan.Types.Enum.Shader        (VkShaderStageFlags)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Handles            (VkBuffer, VkPipelineLayout)

-- | > typedef struct VkIndirectCommandsLayoutCreateInfoNV {
--   >     VkStructureType sType;
--   >     const void*                             pNext;
--   >     VkIndirectCommandsLayoutUsageFlagsNV    flags;
--   >     VkPipelineBindPoint                     pipelineBindPoint;
--   >     uint32_t                                tokenCount;
--   >     const VkIndirectCommandsLayoutTokenNV*  pTokens;
--   >     uint32_t                                streamCount;
--   >     const uint32_t*       pStreamStrides;
--   > } VkIndirectCommandsLayoutCreateInfoNV;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkIndirectCommandsLayoutCreateInfoNV VkIndirectCommandsLayoutCreateInfoNV registry at www.khronos.org>
type VkIndirectCommandsLayoutCreateInfoNV =
     VkStruct VkIndirectCommandsLayoutCreateInfoNV' -- ' closing tick for hsc2hs

data VkIndirectCommandsLayoutCreateInfoNV' -- ' closing tick for hsc2hs

instance VulkanMarshal VkIndirectCommandsLayoutCreateInfoNV where
    type StructRep VkIndirectCommandsLayoutCreateInfoNV =
         'StructMeta "VkIndirectCommandsLayoutCreateInfoNV" -- ' closing tick for hsc2hs
           VkIndirectCommandsLayoutCreateInfoNV
           (56)
{-# LINE 46 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           8
{-# LINE 47 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 49 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False 
                                                   (8)
{-# LINE 54 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "flags" VkIndirectCommandsLayoutUsageFlagsNV 'False
                (16)
{-# LINE 59 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipelineBindPoint" VkPipelineBindPoint 'False
                (20)
{-# LINE 64 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "tokenCount" Word32 'False 
                                                    (24)
{-# LINE 69 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pTokens" (Ptr VkIndirectCommandsLayoutTokenNV) 'False
                (32)
{-# LINE 74 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.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/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pStreamStrides" (Ptr Word32) 'False 
                                                              (48)
{-# LINE 84 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.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 VkIndirectCommandsLayoutTokenNV {
--   >     VkStructureType sType;
--   >     const void*                    pNext;
--   >     VkIndirectCommandsTokenTypeNV  tokenType;
--   >     uint32_t                       stream;
--   >     uint32_t                       offset;
--   >     uint32_t                                vertexBindingUnit;
--   >     VkBool32                                vertexDynamicStride;
--   >     VkPipelineLayout        pushconstantPipelineLayout;
--   >     VkShaderStageFlags      pushconstantShaderStageFlags;
--   >     uint32_t                                pushconstantOffset;
--   >     uint32_t                                pushconstantSize;
--   >     VkIndirectStateFlagsNV  indirectStateFlags;
--   >     uint32_t                indexTypeCount;
--   >     const VkIndexType* pIndexTypes;
--   >     const uint32_t*    pIndexTypeValues;
--   > } VkIndirectCommandsLayoutTokenNV;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkIndirectCommandsLayoutTokenNV VkIndirectCommandsLayoutTokenNV registry at www.khronos.org>
type VkIndirectCommandsLayoutTokenNV =
     VkStruct VkIndirectCommandsLayoutTokenNV' -- ' closing tick for hsc2hs

data VkIndirectCommandsLayoutTokenNV' -- ' closing tick for hsc2hs

instance VulkanMarshal VkIndirectCommandsLayoutTokenNV where
    type StructRep VkIndirectCommandsLayoutTokenNV =
         'StructMeta "VkIndirectCommandsLayoutTokenNV" -- ' closing tick for hsc2hs
           VkIndirectCommandsLayoutTokenNV
           (88)
{-# LINE 120 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           8
{-# LINE 121 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 123 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False 
                                                   (8)
{-# LINE 128 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "tokenType" VkIndirectCommandsTokenTypeNV 'False
                (16)
{-# LINE 133 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "stream" Word32 'False 
                                                (20)
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "offset" Word32 'False 
                                                (24)
{-# LINE 143 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "vertexBindingUnit" Word32 'False 
                                                           (28)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "vertexDynamicStride" VkBool32 'False 
                                                               (32)
{-# LINE 153 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pushconstantPipelineLayout" VkPipelineLayout 'True
                (40)
{-# LINE 158 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pushconstantShaderStageFlags" VkShaderStageFlags 'True
                (48)
{-# LINE 163 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pushconstantOffset" Word32 'False 
                                                            (52)
{-# LINE 168 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pushconstantSize" Word32 'False 
                                                          (56)
{-# LINE 173 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "indirectStateFlags" VkIndirectStateFlagsNV 'True
                (60)
{-# LINE 178 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "indexTypeCount" Word32 'True 
                                                       (64)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pIndexTypes" (Ptr VkIndexType) 'False 
                                                                (72)
{-# LINE 188 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pIndexTypeValues" (Ptr Word32) 'False 
                                                                (80)
{-# LINE 193 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.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 VkIndirectCommandsStreamNV {
--   >     VkBuffer      buffer;
--   >     VkDeviceSize  offset;
--   > } VkIndirectCommandsStreamNV;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkIndirectCommandsStreamNV VkIndirectCommandsStreamNV registry at www.khronos.org>
type VkIndirectCommandsStreamNV =
     VkStruct VkIndirectCommandsStreamNV' -- ' closing tick for hsc2hs

data VkIndirectCommandsStreamNV' -- ' closing tick for hsc2hs

instance VulkanMarshal VkIndirectCommandsStreamNV where
    type StructRep VkIndirectCommandsStreamNV =
         'StructMeta "VkIndirectCommandsStreamNV" VkIndirectCommandsStreamNV -- ' closing tick for hsc2hs
           (16)
{-# LINE 215 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           8
{-# LINE 216 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           '[('FieldMeta "buffer" VkBuffer 'False  -- ' closing tick for hsc2hs
                                                  (0)
{-# LINE 218 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "offset" VkDeviceSize 'False 
                                                      (8)
{-# LINE 223 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.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