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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.QueryPool
       (VkQueryPoolCreateInfo, VkQueryPoolCreateInfoINTEL,
        VkQueryPoolPerformanceCreateInfoKHR,
        VkQueryPoolPerformanceQueryCreateInfoINTEL)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.Bitmasks           (VkQueryPoolCreateFlags)
import Graphics.Vulkan.Types.Enum.Query         (VkQueryPipelineStatisticFlags,
                                                 VkQueryPoolSamplingModeINTEL,
                                                 VkQueryType)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)

-- | > typedef struct VkQueryPoolCreateInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkQueryPoolCreateFlags flags;
--   >     VkQueryType            queryType;
--   >     uint32_t               queryCount;
--   >     VkQueryPipelineStatisticFlags pipelineStatistics;
--   > } VkQueryPoolCreateInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryPoolCreateInfo VkQueryPoolCreateInfo registry at www.khronos.org>
type VkQueryPoolCreateInfo = VkStruct VkQueryPoolCreateInfo' -- ' closing tick for hsc2hs

data VkQueryPoolCreateInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkQueryPoolCreateInfo where
    type StructRep VkQueryPoolCreateInfo =
         'StructMeta "VkQueryPoolCreateInfo" VkQueryPoolCreateInfo  -- ' closing tick for hsc2hs
                                                                   (32)
{-# LINE 39 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
           8
{-# LINE 40 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 42 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False 
                                                   (8)
{-# LINE 47 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "flags" VkQueryPoolCreateFlags 'True 
                                                              (16)
{-# LINE 52 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "queryType" VkQueryType 'False 
                                                        (20)
{-# LINE 57 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "queryCount" Word32 'False 
                                                    (24)
{-# LINE 62 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipelineStatistics" VkQueryPipelineStatisticFlags -- ' closing tick for hsc2hs
                'True -- ' closing tick for hsc2hs
                (28)
{-# LINE 68 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.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

-- | Alias for `VkQueryPoolPerformanceQueryCreateInfoINTEL`
type VkQueryPoolCreateInfoINTEL =
     VkQueryPoolPerformanceQueryCreateInfoINTEL

-- | > typedef struct VkQueryPoolPerformanceCreateInfoKHR {
--   >     VkStructureType sType;
--   >     const void*                             pNext;
--   >     uint32_t                                queueFamilyIndex;
--   >     uint32_t                                counterIndexCount;
--   >     const uint32_t* pCounterIndices;
--   > } VkQueryPoolPerformanceCreateInfoKHR;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryPoolPerformanceCreateInfoKHR VkQueryPoolPerformanceCreateInfoKHR registry at www.khronos.org>
type VkQueryPoolPerformanceCreateInfoKHR =
     VkStruct VkQueryPoolPerformanceCreateInfoKHR' -- ' closing tick for hsc2hs

data VkQueryPoolPerformanceCreateInfoKHR' -- ' closing tick for hsc2hs

instance VulkanMarshal VkQueryPoolPerformanceCreateInfoKHR where
    type StructRep VkQueryPoolPerformanceCreateInfoKHR =
         'StructMeta "VkQueryPoolPerformanceCreateInfoKHR" -- ' closing tick for hsc2hs
           VkQueryPoolPerformanceCreateInfoKHR
           (32)
{-# LINE 98 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
           8
{-# LINE 99 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 101 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False 
                                                   (8)
{-# LINE 106 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "queueFamilyIndex" Word32 'False 
                                                          (16)
{-# LINE 111 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "counterIndexCount" Word32 'False 
                                                           (20)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pCounterIndices" (Ptr Word32) 'False 
                                                               (24)
{-# LINE 121 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[VkQueryPoolCreateInfo] -- ' closing tick for hsc2hs

-- | > typedef struct VkQueryPoolPerformanceQueryCreateInfoINTEL {
--   >     VkStructureType sType;
--   >     const void*                         pNext;
--   >     VkQueryPoolSamplingModeINTEL        performanceCountersSampling;
--   > } VkQueryPoolPerformanceQueryCreateInfoINTEL;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueryPoolPerformanceQueryCreateInfoINTEL VkQueryPoolPerformanceQueryCreateInfoINTEL registry at www.khronos.org>
type VkQueryPoolPerformanceQueryCreateInfoINTEL =
     VkStruct VkQueryPoolPerformanceQueryCreateInfoINTEL' -- ' closing tick for hsc2hs

data VkQueryPoolPerformanceQueryCreateInfoINTEL' -- ' closing tick for hsc2hs

instance VulkanMarshal VkQueryPoolPerformanceQueryCreateInfoINTEL
         where
    type StructRep VkQueryPoolPerformanceQueryCreateInfoINTEL =
         'StructMeta "VkQueryPoolPerformanceQueryCreateInfoINTEL" -- ' closing tick for hsc2hs
           VkQueryPoolPerformanceQueryCreateInfoINTEL
           (24)
{-# LINE 146 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
           8
{-# LINE 147 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 149 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False 
                                                   (8)
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "performanceCountersSampling" -- ' closing tick for hsc2hs
                VkQueryPoolSamplingModeINTEL
                'False -- ' closing tick for hsc2hs
                (16)
{-# LINE 161 "src-gen/Graphics/Vulkan/Types/Struct/QueryPool.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[VkQueryPoolCreateInfo] -- ' closing tick for hsc2hs