{-# 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
       (VkIndirectCommandsLayoutCreateInfoNVX,
        VkIndirectCommandsLayoutTokenNVX, VkIndirectCommandsTokenNVX)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.BaseTypes             (VkDeviceSize)
import Graphics.Vulkan.Types.Enum.IndirectCommands (VkIndirectCommandsLayoutUsageFlagsNVX,
                                                    VkIndirectCommandsTokenTypeNVX)
import Graphics.Vulkan.Types.Enum.Pipeline         (VkPipelineBindPoint)
import Graphics.Vulkan.Types.Enum.StructureType    (VkStructureType)
import Graphics.Vulkan.Types.Handles               (VkBuffer)

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

data VkIndirectCommandsLayoutCreateInfoNVX' -- ' closing tick for hsc2hs

instance VulkanMarshal VkIndirectCommandsLayoutCreateInfoNVX where
    type StructRep VkIndirectCommandsLayoutCreateInfoNVX =
         'StructMeta "VkIndirectCommandsLayoutCreateInfoNVX" -- ' closing tick for hsc2hs
           VkIndirectCommandsLayoutCreateInfoNVX
           (40)
{-# LINE 41 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           8
{-# LINE 42 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 44 "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 49 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipelineBindPoint" VkPipelineBindPoint 'False
                (16)
{-# LINE 54 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "flags" VkIndirectCommandsLayoutUsageFlagsNVX 'False
                (20)
{-# LINE 59 "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 64 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pTokens" (Ptr VkIndirectCommandsLayoutTokenNVX) 'False
                (32)
{-# LINE 69 "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 VkIndirectCommandsLayoutTokenNVX {
--   >     VkIndirectCommandsTokenTypeNVX      tokenType;
--   >     uint32_t                         bindingUnit;
--   >     uint32_t                         dynamicCount;
--   >     uint32_t                         divisor;
--   > } VkIndirectCommandsLayoutTokenNVX;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkIndirectCommandsLayoutTokenNVX VkIndirectCommandsLayoutTokenNVX registry at www.khronos.org>
type VkIndirectCommandsLayoutTokenNVX =
     VkStruct VkIndirectCommandsLayoutTokenNVX' -- ' closing tick for hsc2hs

data VkIndirectCommandsLayoutTokenNVX' -- ' closing tick for hsc2hs

instance VulkanMarshal VkIndirectCommandsLayoutTokenNVX where
    type StructRep VkIndirectCommandsLayoutTokenNVX =
         'StructMeta "VkIndirectCommandsLayoutTokenNVX" -- ' closing tick for hsc2hs
           VkIndirectCommandsLayoutTokenNVX
           (16)
{-# LINE 94 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           4
{-# LINE 95 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           '[('FieldMeta "tokenType" VkIndirectCommandsTokenTypeNVX 'False -- ' closing tick for hsc2hs
                (0)
{-# LINE 97 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "bindingUnit" Word32 'False
                                                     (4)
{-# LINE 102 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "dynamicCount" Word32 'False
                                                      (8)
{-# LINE 107 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "divisor" Word32 'False
                                                 (12)
{-# LINE 112 "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 VkIndirectCommandsTokenNVX {
--   >     VkIndirectCommandsTokenTypeNVX      tokenType;
--   >     VkBuffer                         buffer;
--   >     VkDeviceSize                     offset;
--   > } VkIndirectCommandsTokenNVX;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkIndirectCommandsTokenNVX VkIndirectCommandsTokenNVX registry at www.khronos.org>
type VkIndirectCommandsTokenNVX =
     VkStruct VkIndirectCommandsTokenNVX' -- ' closing tick for hsc2hs

data VkIndirectCommandsTokenNVX' -- ' closing tick for hsc2hs

instance VulkanMarshal VkIndirectCommandsTokenNVX where
    type StructRep VkIndirectCommandsTokenNVX =
         'StructMeta "VkIndirectCommandsTokenNVX" VkIndirectCommandsTokenNVX -- ' closing tick for hsc2hs
           (24)
{-# LINE 135 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           8
{-# LINE 136 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
           '[('FieldMeta "tokenType" VkIndirectCommandsTokenTypeNVX 'False -- ' closing tick for hsc2hs
                (0)
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "buffer" VkBuffer 'False
                                                  (8)
{-# LINE 143 "src-gen/Graphics/Vulkan/Types/Struct/IndirectCommands.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "offset" VkDeviceSize 'False
                                                      (16)
{-# LINE 148 "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