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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Draw
       (VkDrawIndexedIndirectCommand, VkDrawIndirectCommand,
        VkDrawMeshTasksIndirectCommandNV)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal

-- | > typedef struct VkDrawIndexedIndirectCommand {
--   >     uint32_t                       indexCount;
--   >     uint32_t                       instanceCount;
--   >     uint32_t                       firstIndex;
--   >     int32_t                        vertexOffset;
--   >     uint32_t firstInstance;
--   > } VkDrawIndexedIndirectCommand;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkDrawIndexedIndirectCommand VkDrawIndexedIndirectCommand registry at www.khronos.org>
type VkDrawIndexedIndirectCommand =
     VkStruct VkDrawIndexedIndirectCommand' -- ' closing tick for hsc2hs

data VkDrawIndexedIndirectCommand' -- ' closing tick for hsc2hs

instance VulkanMarshal VkDrawIndexedIndirectCommand where
    type StructRep VkDrawIndexedIndirectCommand =
         'StructMeta "VkDrawIndexedIndirectCommand" -- ' closing tick for hsc2hs
           VkDrawIndexedIndirectCommand
           (20)
{-# LINE 34 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
           4
{-# LINE 35 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
           '[('FieldMeta "indexCount" Word32 'False  -- ' closing tick for hsc2hs
                                                    (0)
{-# LINE 37 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "instanceCount" Word32 'False 
                                                       (4)
{-# LINE 42 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "firstIndex" Word32 'False 
                                                    (8)
{-# LINE 47 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "vertexOffset" Int32 'False 
                                                     (12)
{-# LINE 52 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "firstInstance" Word32 'False 
                                                       (16)
{-# LINE 57 "src-gen/Graphics/Vulkan/Types/Struct/Draw.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 VkDrawIndirectCommand {
--   >     uint32_t                       vertexCount;
--   >     uint32_t                       instanceCount;
--   >     uint32_t                       firstVertex;
--   >     uint32_t firstInstance;
--   > } VkDrawIndirectCommand;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkDrawIndirectCommand VkDrawIndirectCommand registry at www.khronos.org>
type VkDrawIndirectCommand = VkStruct VkDrawIndirectCommand' -- ' closing tick for hsc2hs

data VkDrawIndirectCommand' -- ' closing tick for hsc2hs

instance VulkanMarshal VkDrawIndirectCommand where
    type StructRep VkDrawIndirectCommand =
         'StructMeta "VkDrawIndirectCommand" VkDrawIndirectCommand  -- ' closing tick for hsc2hs
                                                                   (16)
{-# LINE 80 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
           4
{-# LINE 81 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
           '[('FieldMeta "vertexCount" Word32 'False  -- ' closing tick for hsc2hs
                                                     (0)
{-# LINE 83 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "instanceCount" Word32 'False 
                                                       (4)
{-# LINE 88 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "firstVertex" Word32 'False 
                                                     (8)
{-# LINE 93 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "firstInstance" Word32 'False 
                                                       (12)
{-# LINE 98 "src-gen/Graphics/Vulkan/Types/Struct/Draw.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 VkDrawMeshTasksIndirectCommandNV {
--   >     uint32_t               taskCount;
--   >     uint32_t               firstTask;
--   > } VkDrawMeshTasksIndirectCommandNV;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkDrawMeshTasksIndirectCommandNV VkDrawMeshTasksIndirectCommandNV registry at www.khronos.org>
type VkDrawMeshTasksIndirectCommandNV =
     VkStruct VkDrawMeshTasksIndirectCommandNV' -- ' closing tick for hsc2hs

data VkDrawMeshTasksIndirectCommandNV' -- ' closing tick for hsc2hs

instance VulkanMarshal VkDrawMeshTasksIndirectCommandNV where
    type StructRep VkDrawMeshTasksIndirectCommandNV =
         'StructMeta "VkDrawMeshTasksIndirectCommandNV" -- ' closing tick for hsc2hs
           VkDrawMeshTasksIndirectCommandNV
           (8)
{-# LINE 121 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
           4
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
           '[('FieldMeta "taskCount" Word32 'False  -- ' closing tick for hsc2hs
                                                   (0)
{-# LINE 124 "src-gen/Graphics/Vulkan/Types/Struct/Draw.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "firstTask" Word32 'False 
                                                   (4)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/Draw.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