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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Command
       (VkCommandBufferAllocateInfo, VkCommandBufferBeginInfo,
        VkCommandBufferInheritanceInfo, VkCommandPoolCreateInfo)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.BaseTypes          (VkBool32)
import Graphics.Vulkan.Types.Enum.Command       (VkCommandBufferLevel,
                                                 VkCommandBufferUsageFlags,
                                                 VkCommandPoolCreateFlags)
import Graphics.Vulkan.Types.Enum.Query         (VkQueryControlFlags,
                                                 VkQueryPipelineStatisticFlags)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Handles            (VkCommandPool, VkFramebuffer,
                                                 VkRenderPass)

-- | > typedef struct VkCommandBufferAllocateInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkCommandPool          commandPool;
--   >     VkCommandBufferLevel   level;
--   >     uint32_t               commandBufferCount;
--   > } VkCommandBufferAllocateInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkCommandBufferAllocateInfo VkCommandBufferAllocateInfo registry at www.khronos.org>
type VkCommandBufferAllocateInfo =
     VkStruct VkCommandBufferAllocateInfo' -- ' closing tick for hsc2hs

data VkCommandBufferAllocateInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkCommandBufferAllocateInfo where
    type StructRep VkCommandBufferAllocateInfo =
         'StructMeta "VkCommandBufferAllocateInfo" -- ' closing tick for hsc2hs
           VkCommandBufferAllocateInfo
           (32)
{-# LINE 43 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           8
{-# LINE 44 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 46 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "commandPool" VkCommandPool 'False
                                                            (16)
{-# LINE 56 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "level" VkCommandBufferLevel 'False
                                                             (24)
{-# LINE 61 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "commandBufferCount" Word32 'False
                                                            (28)
{-# LINE 66 "src-gen/Graphics/Vulkan/Types/Struct/Command.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 VkCommandBufferBeginInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkCommandBufferUsageFlags  flags;
--   >     const VkCommandBufferInheritanceInfo*       pInheritanceInfo;
--   > } VkCommandBufferBeginInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkCommandBufferBeginInfo VkCommandBufferBeginInfo registry at www.khronos.org>
type VkCommandBufferBeginInfo = VkStruct VkCommandBufferBeginInfo' -- ' closing tick for hsc2hs

data VkCommandBufferBeginInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkCommandBufferBeginInfo where
    type StructRep VkCommandBufferBeginInfo =
         'StructMeta "VkCommandBufferBeginInfo" VkCommandBufferBeginInfo -- ' closing tick for hsc2hs
           (32)
{-# LINE 89 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           8
{-# LINE 90 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 92 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 97 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "flags" VkCommandBufferUsageFlags 'True
                                                                 (16)
{-# LINE 102 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pInheritanceInfo" (Ptr VkCommandBufferInheritanceInfo) -- ' closing tick for hsc2hs
                'True -- ' closing tick for hsc2hs
                (24)
{-# LINE 108 "src-gen/Graphics/Vulkan/Types/Struct/Command.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 VkCommandBufferInheritanceInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkRenderPass    renderPass;
--   >     uint32_t               subpass;
--   >     VkFramebuffer   framebuffer;
--   >     VkBool32               occlusionQueryEnable;
--   >     VkQueryControlFlags    queryFlags;
--   >     VkQueryPipelineStatisticFlags pipelineStatistics;
--   > } VkCommandBufferInheritanceInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkCommandBufferInheritanceInfo VkCommandBufferInheritanceInfo registry at www.khronos.org>
type VkCommandBufferInheritanceInfo =
     VkStruct VkCommandBufferInheritanceInfo' -- ' closing tick for hsc2hs

data VkCommandBufferInheritanceInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkCommandBufferInheritanceInfo where
    type StructRep VkCommandBufferInheritanceInfo =
         'StructMeta "VkCommandBufferInheritanceInfo" -- ' closing tick for hsc2hs
           VkCommandBufferInheritanceInfo
           (56)
{-# LINE 137 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           8
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 140 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 145 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "renderPass" VkRenderPass 'True
                                                         (16)
{-# LINE 150 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "subpass" Word32 'False
                                                 (24)
{-# LINE 155 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "framebuffer" VkFramebuffer 'True
                                                           (32)
{-# LINE 160 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "occlusionQueryEnable" VkBool32 'False
                                                                (40)
{-# LINE 165 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "queryFlags" VkQueryControlFlags 'True
                                                                (44)
{-# LINE 170 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipelineStatistics" VkQueryPipelineStatisticFlags -- ' closing tick for hsc2hs
                'True -- ' closing tick for hsc2hs
                (48)
{-# LINE 176 "src-gen/Graphics/Vulkan/Types/Struct/Command.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 VkCommandPoolCreateInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkCommandPoolCreateFlags   flags;
--   >     uint32_t               queueFamilyIndex;
--   > } VkCommandPoolCreateInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkCommandPoolCreateInfo VkCommandPoolCreateInfo registry at www.khronos.org>
type VkCommandPoolCreateInfo = VkStruct VkCommandPoolCreateInfo' -- ' closing tick for hsc2hs

data VkCommandPoolCreateInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkCommandPoolCreateInfo where
    type StructRep VkCommandPoolCreateInfo =
         'StructMeta "VkCommandPoolCreateInfo" VkCommandPoolCreateInfo -- ' closing tick for hsc2hs
           (24)
{-# LINE 199 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           8
{-# LINE 200 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 202 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 207 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "flags" VkCommandPoolCreateFlags 'True
                                                                (16)
{-# LINE 212 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "queueFamilyIndex" Word32 'False
                                                          (20)
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/Command.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