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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Command
       (VkCommandBufferAllocateInfo(..), VkCommandBufferBeginInfo(..),
        VkCommandBufferInheritanceInfo(..), VkCommandPoolCreateInfo(..))
       where
import           Foreign.Storable                         (Storable (..))
import           GHC.Base                                 (Addr#, ByteArray#,
                                                           byteArrayContents#,
                                                           plusAddr#)
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)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

-- | > 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>
data VkCommandBufferAllocateInfo = VkCommandBufferAllocateInfo# Addr#
                                                                ByteArray#

instance Eq VkCommandBufferAllocateInfo where
        (VkCommandBufferAllocateInfo# a _) ==
          x@(VkCommandBufferAllocateInfo# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkCommandBufferAllocateInfo where
        (VkCommandBufferAllocateInfo# a _) `compare`
          x@(VkCommandBufferAllocateInfo# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkCommandBufferAllocateInfo where
        sizeOf ~_ = (32)
{-# LINE 57 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_ = (8)
{-# LINE 60 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkCommandBufferAllocateInfo where
        unsafeAddr (VkCommandBufferAllocateInfo# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkCommandBufferAllocateInfo# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkCommandBufferAllocateInfo#
              (plusAddr# (byteArrayContents# b) off)
              b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkCommandBufferAllocateInfo where
        type StructFields VkCommandBufferAllocateInfo =
             '["sType", "pNext", "commandPool", "level", "commandBufferCount"] -- ' closing tick for hsc2hs
        type CUnionType VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs
        type StructExtends VkCommandBufferAllocateInfo = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "sType" VkCommandBufferAllocateInfo where
        type FieldType "sType" VkCommandBufferAllocateInfo =
             VkStructureType
        type FieldOptional "sType" VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkCommandBufferAllocateInfo =
             (0)
{-# LINE 97 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "sType" VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (0)
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkCommandBufferAllocateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 112 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkCommandBufferAllocateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pNext" VkCommandBufferAllocateInfo where
        type FieldType "pNext" VkCommandBufferAllocateInfo = Ptr Void
        type FieldOptional "pNext" VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkCommandBufferAllocateInfo =
             (8)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "pNext" VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (8)
{-# LINE 137 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkCommandBufferAllocateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 144 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkCommandBufferAllocateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "commandPool" VkCommandBufferAllocateInfo where
        type FieldType "commandPool" VkCommandBufferAllocateInfo =
             VkCommandPool
        type FieldOptional "commandPool" VkCommandBufferAllocateInfo =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "commandPool" VkCommandBufferAllocateInfo =
             (16)
{-# LINE 163 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "commandPool" VkCommandBufferAllocateInfo =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (16)
{-# LINE 172 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "commandPool" VkCommandBufferAllocateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 179 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (16)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "commandPool" VkCommandBufferAllocateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "level" VkCommandBufferAllocateInfo where
        type FieldType "level" VkCommandBufferAllocateInfo =
             VkCommandBufferLevel
        type FieldOptional "level" VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "level" VkCommandBufferAllocateInfo =
             (24)
{-# LINE 197 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "level" VkCommandBufferAllocateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (24)
{-# LINE 205 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "level" VkCommandBufferAllocateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 212 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (24)
{-# LINE 216 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "level" VkCommandBufferAllocateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 222 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "commandBufferCount" VkCommandBufferAllocateInfo where
        type FieldType "commandBufferCount" VkCommandBufferAllocateInfo =
             Word32
        type FieldOptional "commandBufferCount" VkCommandBufferAllocateInfo
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "commandBufferCount" VkCommandBufferAllocateInfo =
             (28)
{-# LINE 231 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "commandBufferCount" VkCommandBufferAllocateInfo
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (28)
{-# LINE 240 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "commandBufferCount" VkCommandBufferAllocateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (28))
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (28)
{-# LINE 251 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "commandBufferCount" VkCommandBufferAllocateInfo
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (28)
{-# LINE 258 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance Show VkCommandBufferAllocateInfo where
        showsPrec d x
          = showString "VkCommandBufferAllocateInfo {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "commandPool = " .
                            showsPrec d (getField @"commandPool" x) .
                              showString ", " .
                                showString "level = " .
                                  showsPrec d (getField @"level" x) .
                                    showString ", " .
                                      showString "commandBufferCount = " .
                                        showsPrec d (getField @"commandBufferCount" x) .
                                          showChar '}'

-- | > 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>
data VkCommandBufferBeginInfo = VkCommandBufferBeginInfo# Addr#
                                                          ByteArray#

instance Eq VkCommandBufferBeginInfo where
        (VkCommandBufferBeginInfo# a _) ==
          x@(VkCommandBufferBeginInfo# b _) = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkCommandBufferBeginInfo where
        (VkCommandBufferBeginInfo# a _) `compare`
          x@(VkCommandBufferBeginInfo# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkCommandBufferBeginInfo where
        sizeOf ~_ = (32)
{-# LINE 303 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_ = (8)
{-# LINE 306 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkCommandBufferBeginInfo where
        unsafeAddr (VkCommandBufferBeginInfo# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkCommandBufferBeginInfo# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkCommandBufferBeginInfo# (plusAddr# (byteArrayContents# b) off)
              b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkCommandBufferBeginInfo where
        type StructFields VkCommandBufferBeginInfo =
             '["sType", "pNext", "flags", "pInheritanceInfo"] -- ' closing tick for hsc2hs
        type CUnionType VkCommandBufferBeginInfo = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkCommandBufferBeginInfo = 'False -- ' closing tick for hsc2hs
        type StructExtends VkCommandBufferBeginInfo = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "sType" VkCommandBufferBeginInfo where
        type FieldType "sType" VkCommandBufferBeginInfo = VkStructureType
        type FieldOptional "sType" VkCommandBufferBeginInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkCommandBufferBeginInfo =
             (0)
{-# LINE 341 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "sType" VkCommandBufferBeginInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (0)
{-# LINE 348 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkCommandBufferBeginInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 355 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 359 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkCommandBufferBeginInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 365 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pNext" VkCommandBufferBeginInfo where
        type FieldType "pNext" VkCommandBufferBeginInfo = Ptr Void
        type FieldOptional "pNext" VkCommandBufferBeginInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkCommandBufferBeginInfo =
             (8)
{-# LINE 372 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "pNext" VkCommandBufferBeginInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (8)
{-# LINE 379 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkCommandBufferBeginInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 386 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 390 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkCommandBufferBeginInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 396 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "flags" VkCommandBufferBeginInfo where
        type FieldType "flags" VkCommandBufferBeginInfo =
             VkCommandBufferUsageFlags
        type FieldOptional "flags" VkCommandBufferBeginInfo = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkCommandBufferBeginInfo =
             (16)
{-# LINE 404 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "flags" VkCommandBufferBeginInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset = (16)
{-# LINE 411 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkCommandBufferBeginInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 418 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (16)
{-# LINE 422 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "flags" VkCommandBufferBeginInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 428 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pInheritanceInfo" VkCommandBufferBeginInfo where
        type FieldType "pInheritanceInfo" VkCommandBufferBeginInfo =
             Ptr VkCommandBufferInheritanceInfo
        type FieldOptional "pInheritanceInfo" VkCommandBufferBeginInfo =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "pInheritanceInfo" VkCommandBufferBeginInfo =
             (24)
{-# LINE 437 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "pInheritanceInfo" VkCommandBufferBeginInfo =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (24)
{-# LINE 446 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pInheritanceInfo" VkCommandBufferBeginInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 453 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (24)
{-# LINE 457 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pInheritanceInfo" VkCommandBufferBeginInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 463 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance Show VkCommandBufferBeginInfo where
        showsPrec d x
          = showString "VkCommandBufferBeginInfo {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "flags = " .
                            showsPrec d (getField @"flags" x) .
                              showString ", " .
                                showString "pInheritanceInfo = " .
                                  showsPrec d (getField @"pInheritanceInfo" x) . showChar '}'

-- | > 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>
data VkCommandBufferInheritanceInfo = VkCommandBufferInheritanceInfo# Addr#
                                                                      ByteArray#

instance Eq VkCommandBufferInheritanceInfo where
        (VkCommandBufferInheritanceInfo# a _) ==
          x@(VkCommandBufferInheritanceInfo# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkCommandBufferInheritanceInfo where
        (VkCommandBufferInheritanceInfo# a _) `compare`
          x@(VkCommandBufferInheritanceInfo# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkCommandBufferInheritanceInfo where
        sizeOf ~_ = (56)
{-# LINE 509 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_
          = (8)
{-# LINE 513 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkCommandBufferInheritanceInfo where
        unsafeAddr (VkCommandBufferInheritanceInfo# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkCommandBufferInheritanceInfo# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkCommandBufferInheritanceInfo#
              (plusAddr# (byteArrayContents# b) off)
              b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkCommandBufferInheritanceInfo where
        type StructFields VkCommandBufferInheritanceInfo =
             '["sType", "pNext", "renderPass", "subpass", "framebuffer", -- ' closing tick for hsc2hs
               "occlusionQueryEnable", "queryFlags", "pipelineStatistics"]
        type CUnionType VkCommandBufferInheritanceInfo = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkCommandBufferInheritanceInfo = 'False -- ' closing tick for hsc2hs
        type StructExtends VkCommandBufferInheritanceInfo = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "sType" VkCommandBufferInheritanceInfo where
        type FieldType "sType" VkCommandBufferInheritanceInfo =
             VkStructureType
        type FieldOptional "sType" VkCommandBufferInheritanceInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkCommandBufferInheritanceInfo =
             (0)
{-# LINE 551 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "sType" VkCommandBufferInheritanceInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (0)
{-# LINE 559 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkCommandBufferInheritanceInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 566 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 570 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkCommandBufferInheritanceInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 576 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pNext" VkCommandBufferInheritanceInfo where
        type FieldType "pNext" VkCommandBufferInheritanceInfo = Ptr Void
        type FieldOptional "pNext" VkCommandBufferInheritanceInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkCommandBufferInheritanceInfo =
             (8)
{-# LINE 583 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "pNext" VkCommandBufferInheritanceInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (8)
{-# LINE 591 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkCommandBufferInheritanceInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 598 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 602 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkCommandBufferInheritanceInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 608 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "renderPass" VkCommandBufferInheritanceInfo where
        type FieldType "renderPass" VkCommandBufferInheritanceInfo =
             VkRenderPass
        type FieldOptional "renderPass" VkCommandBufferInheritanceInfo =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "renderPass" VkCommandBufferInheritanceInfo =
             (16)
{-# LINE 617 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "renderPass" VkCommandBufferInheritanceInfo =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (16)
{-# LINE 626 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "renderPass" VkCommandBufferInheritanceInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 633 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (16)
{-# LINE 637 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "renderPass" VkCommandBufferInheritanceInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 643 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "subpass" VkCommandBufferInheritanceInfo where
        type FieldType "subpass" VkCommandBufferInheritanceInfo = Word32
        type FieldOptional "subpass" VkCommandBufferInheritanceInfo =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "subpass" VkCommandBufferInheritanceInfo =
             (24)
{-# LINE 651 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "subpass" VkCommandBufferInheritanceInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (24)
{-# LINE 659 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "subpass" VkCommandBufferInheritanceInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 666 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (24)
{-# LINE 670 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "subpass" VkCommandBufferInheritanceInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 676 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "framebuffer" VkCommandBufferInheritanceInfo where
        type FieldType "framebuffer" VkCommandBufferInheritanceInfo =
             VkFramebuffer
        type FieldOptional "framebuffer" VkCommandBufferInheritanceInfo =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "framebuffer" VkCommandBufferInheritanceInfo =
             (32)
{-# LINE 685 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "framebuffer" VkCommandBufferInheritanceInfo =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (32)
{-# LINE 694 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "framebuffer" VkCommandBufferInheritanceInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (32))
{-# LINE 701 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (32)
{-# LINE 705 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "framebuffer" VkCommandBufferInheritanceInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (32)
{-# LINE 711 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "occlusionQueryEnable" VkCommandBufferInheritanceInfo
         where
        type FieldType "occlusionQueryEnable"
               VkCommandBufferInheritanceInfo
             = VkBool32
        type FieldOptional "occlusionQueryEnable"
               VkCommandBufferInheritanceInfo
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "occlusionQueryEnable"
               VkCommandBufferInheritanceInfo
             =
             (40)
{-# LINE 725 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "occlusionQueryEnable"
               VkCommandBufferInheritanceInfo
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (40)
{-# LINE 735 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "occlusionQueryEnable" VkCommandBufferInheritanceInfo
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (40))
{-# LINE 743 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (40)
{-# LINE 747 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "occlusionQueryEnable" VkCommandBufferInheritanceInfo
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (40)
{-# LINE 754 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "queryFlags" VkCommandBufferInheritanceInfo where
        type FieldType "queryFlags" VkCommandBufferInheritanceInfo =
             VkQueryControlFlags
        type FieldOptional "queryFlags" VkCommandBufferInheritanceInfo =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "queryFlags" VkCommandBufferInheritanceInfo =
             (44)
{-# LINE 763 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "queryFlags" VkCommandBufferInheritanceInfo =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (44)
{-# LINE 772 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "queryFlags" VkCommandBufferInheritanceInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (44))
{-# LINE 779 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (44)
{-# LINE 783 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "queryFlags" VkCommandBufferInheritanceInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (44)
{-# LINE 789 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pipelineStatistics" VkCommandBufferInheritanceInfo where
        type FieldType "pipelineStatistics" VkCommandBufferInheritanceInfo
             = VkQueryPipelineStatisticFlags
        type FieldOptional "pipelineStatistics"
               VkCommandBufferInheritanceInfo
             = 'True -- ' closing tick for hsc2hs
        type FieldOffset "pipelineStatistics"
               VkCommandBufferInheritanceInfo
             =
             (48)
{-# LINE 801 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "pipelineStatistics"
               VkCommandBufferInheritanceInfo
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (48)
{-# LINE 811 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pipelineStatistics" VkCommandBufferInheritanceInfo
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (48))
{-# LINE 819 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (48)
{-# LINE 823 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pipelineStatistics" VkCommandBufferInheritanceInfo
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (48)
{-# LINE 830 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance Show VkCommandBufferInheritanceInfo where
        showsPrec d x
          = showString "VkCommandBufferInheritanceInfo {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "renderPass = " .
                            showsPrec d (getField @"renderPass" x) .
                              showString ", " .
                                showString "subpass = " .
                                  showsPrec d (getField @"subpass" x) .
                                    showString ", " .
                                      showString "framebuffer = " .
                                        showsPrec d (getField @"framebuffer" x) .
                                          showString ", " .
                                            showString "occlusionQueryEnable = " .
                                              showsPrec d (getField @"occlusionQueryEnable" x) .
                                                showString ", " .
                                                  showString "queryFlags = " .
                                                    showsPrec d (getField @"queryFlags" x) .
                                                      showString ", " .
                                                        showString "pipelineStatistics = " .
                                                          showsPrec d
                                                            (getField @"pipelineStatistics" x)
                                                            . showChar '}'

-- | > 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>
data VkCommandPoolCreateInfo = VkCommandPoolCreateInfo# Addr#
                                                        ByteArray#

instance Eq VkCommandPoolCreateInfo where
        (VkCommandPoolCreateInfo# a _) == x@(VkCommandPoolCreateInfo# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkCommandPoolCreateInfo where
        (VkCommandPoolCreateInfo# a _) `compare`
          x@(VkCommandPoolCreateInfo# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkCommandPoolCreateInfo where
        sizeOf ~_ = (24)
{-# LINE 885 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_ = (8)
{-# LINE 888 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkCommandPoolCreateInfo where
        unsafeAddr (VkCommandPoolCreateInfo# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkCommandPoolCreateInfo# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkCommandPoolCreateInfo# (plusAddr# (byteArrayContents# b) off) b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkCommandPoolCreateInfo where
        type StructFields VkCommandPoolCreateInfo =
             '["sType", "pNext", "flags", "queueFamilyIndex"] -- ' closing tick for hsc2hs
        type CUnionType VkCommandPoolCreateInfo = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkCommandPoolCreateInfo = 'False -- ' closing tick for hsc2hs
        type StructExtends VkCommandPoolCreateInfo = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "sType" VkCommandPoolCreateInfo where
        type FieldType "sType" VkCommandPoolCreateInfo = VkStructureType
        type FieldOptional "sType" VkCommandPoolCreateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkCommandPoolCreateInfo =
             (0)
{-# LINE 922 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "sType" VkCommandPoolCreateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (0)
{-# LINE 929 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkCommandPoolCreateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 936 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 940 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkCommandPoolCreateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 946 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pNext" VkCommandPoolCreateInfo where
        type FieldType "pNext" VkCommandPoolCreateInfo = Ptr Void
        type FieldOptional "pNext" VkCommandPoolCreateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkCommandPoolCreateInfo =
             (8)
{-# LINE 953 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "pNext" VkCommandPoolCreateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (8)
{-# LINE 960 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkCommandPoolCreateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 967 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 971 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkCommandPoolCreateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 977 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "flags" VkCommandPoolCreateInfo where
        type FieldType "flags" VkCommandPoolCreateInfo =
             VkCommandPoolCreateFlags
        type FieldOptional "flags" VkCommandPoolCreateInfo = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkCommandPoolCreateInfo =
             (16)
{-# LINE 985 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "flags" VkCommandPoolCreateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset = (16)
{-# LINE 992 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkCommandPoolCreateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 999 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (16)
{-# LINE 1003 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "flags" VkCommandPoolCreateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 1009 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "queueFamilyIndex" VkCommandPoolCreateInfo where
        type FieldType "queueFamilyIndex" VkCommandPoolCreateInfo = Word32
        type FieldOptional "queueFamilyIndex" VkCommandPoolCreateInfo =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "queueFamilyIndex" VkCommandPoolCreateInfo =
             (20)
{-# LINE 1017 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
        type FieldIsArray "queueFamilyIndex" VkCommandPoolCreateInfo =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (20)
{-# LINE 1026 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "queueFamilyIndex" VkCommandPoolCreateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (20))
{-# LINE 1033 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (20)
{-# LINE 1037 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "queueFamilyIndex" VkCommandPoolCreateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (20)
{-# LINE 1043 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}

instance Show VkCommandPoolCreateInfo where
        showsPrec d x
          = showString "VkCommandPoolCreateInfo {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "flags = " .
                            showsPrec d (getField @"flags" x) .
                              showString ", " .
                                showString "queueFamilyIndex = " .
                                  showsPrec d (getField @"queueFamilyIndex" x) . showChar '}'