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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.CopyDescriptorSet
       (VkCopyDescriptorSet(..)) 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.Enum.StructureType (VkStructureType)
import           Graphics.Vulkan.Types.Handles            (VkDescriptorSet)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

-- | > typedef struct VkCopyDescriptorSet {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkDescriptorSet        srcSet;
--   >     uint32_t               srcBinding;
--   >     uint32_t               srcArrayElement;
--   >     VkDescriptorSet        dstSet;
--   >     uint32_t               dstBinding;
--   >     uint32_t               dstArrayElement;
--   >     uint32_t               descriptorCount;
--   > } VkCopyDescriptorSet;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkCopyDescriptorSet VkCopyDescriptorSet registry at www.khronos.org>
data VkCopyDescriptorSet = VkCopyDescriptorSet# Addr# ByteArray#

instance Eq VkCopyDescriptorSet where
        (VkCopyDescriptorSet# Addr#
a ByteArray#
_) == :: VkCopyDescriptorSet -> VkCopyDescriptorSet -> Bool
== x :: VkCopyDescriptorSet
x@(VkCopyDescriptorSet# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCopyDescriptorSet -> Int
forall a. Storable a => a -> Int
sizeOf VkCopyDescriptorSet
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

instance Ord VkCopyDescriptorSet where
        (VkCopyDescriptorSet# Addr#
a ByteArray#
_) compare :: VkCopyDescriptorSet -> VkCopyDescriptorSet -> Ordering
`compare` x :: VkCopyDescriptorSet
x@(VkCopyDescriptorSet# Addr#
b ByteArray#
_)
          = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCopyDescriptorSet -> Int
forall a. Storable a => a -> Int
sizeOf VkCopyDescriptorSet
x) Addr#
a Addr#
b

        {-# INLINE compare #-}

instance Storable VkCopyDescriptorSet where
        sizeOf :: VkCopyDescriptorSet -> Int
sizeOf ~VkCopyDescriptorSet
_ = (Int
56)
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkCopyDescriptorSet -> Int
alignment ~VkCopyDescriptorSet
_ = Int
8
{-# LINE 54 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE alignment #-}
        peek :: Ptr VkCopyDescriptorSet -> IO VkCopyDescriptorSet
peek = Ptr VkCopyDescriptorSet -> IO VkCopyDescriptorSet
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#

        {-# INLINE peek #-}
        poke :: Ptr VkCopyDescriptorSet -> VkCopyDescriptorSet -> IO ()
poke = Ptr VkCopyDescriptorSet -> VkCopyDescriptorSet -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkCopyDescriptorSet where
        unsafeAddr :: VkCopyDescriptorSet -> Addr#
unsafeAddr (VkCopyDescriptorSet# Addr#
a ByteArray#
_) = Addr#
a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray :: VkCopyDescriptorSet -> ByteArray#
unsafeByteArray (VkCopyDescriptorSet# Addr#
_ ByteArray#
b) = ByteArray#
b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkCopyDescriptorSet
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkCopyDescriptorSet
VkCopyDescriptorSet# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkCopyDescriptorSet where
        type StructFields VkCopyDescriptorSet =
             '["sType", "pNext", "srcSet", "srcBinding", "srcArrayElement", -- ' closing tick for hsc2hs
               "dstSet", "dstBinding", "dstArrayElement", "descriptorCount"]
        type CUnionType VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs
        type StructExtends VkCopyDescriptorSet = '[] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 96 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet -> FieldType "sType" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
0))
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "sType" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
0)
{-# LINE 107 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "sType" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
0)
{-# LINE 113 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 127 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet -> FieldType "pNext" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
8))
{-# LINE 134 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "pNext" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
8)
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "pNext" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
8)
{-# LINE 144 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-} HasField "srcSet" VkCopyDescriptorSet
         where
        type FieldType "srcSet" VkCopyDescriptorSet = VkDescriptorSet
        type FieldOptional "srcSet" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs
        type FieldOffset "srcSet" VkCopyDescriptorSet =
             (16)
{-# LINE 151 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}
        type FieldIsArray "srcSet" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
16)
{-# LINE 158 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "srcSet" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet -> FieldType "srcSet" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO VkDescriptorSet -> VkDescriptorSet
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO VkDescriptorSet
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
16))
{-# LINE 165 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "srcSet" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO VkDescriptorSet
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
16)
{-# LINE 169 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "srcSet" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "srcSet" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> VkDescriptorSet -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
16)
{-# LINE 175 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
24)
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "srcBinding" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet -> FieldType "srcBinding" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
24))
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "srcBinding" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
24)
{-# LINE 200 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "srcBinding" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "srcBinding" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
24)
{-# LINE 206 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
28)
{-# LINE 221 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "srcArrayElement" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet
-> FieldType "srcArrayElement" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
28))
{-# LINE 228 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "srcArrayElement" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
28)
{-# LINE 232 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "srcArrayElement" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "srcArrayElement" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
28)
{-# LINE 238 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-} HasField "dstSet" VkCopyDescriptorSet
         where
        type FieldType "dstSet" VkCopyDescriptorSet = VkDescriptorSet
        type FieldOptional "dstSet" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs
        type FieldOffset "dstSet" VkCopyDescriptorSet =
             (32)
{-# LINE 245 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}
        type FieldIsArray "dstSet" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
32)
{-# LINE 252 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "dstSet" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet -> FieldType "dstSet" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO VkDescriptorSet -> VkDescriptorSet
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO VkDescriptorSet
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
32))
{-# LINE 259 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "dstSet" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO VkDescriptorSet
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
32)
{-# LINE 263 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "dstSet" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "dstSet" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> VkDescriptorSet -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
32)
{-# LINE 269 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "dstBinding" VkCopyDescriptorSet where
        type FieldType "dstBinding" VkCopyDescriptorSet = Word32
        type FieldOptional "dstBinding" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs
        type FieldOffset "dstBinding" VkCopyDescriptorSet =
             (40)
{-# LINE 276 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}
        type FieldIsArray "dstBinding" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
40)
{-# LINE 283 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "dstBinding" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet -> FieldType "dstBinding" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
40))
{-# LINE 290 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "dstBinding" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
40)
{-# LINE 294 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "dstBinding" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "dstBinding" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
40)
{-# LINE 300 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "dstArrayElement" VkCopyDescriptorSet where
        type FieldType "dstArrayElement" VkCopyDescriptorSet = Word32
        type FieldOptional "dstArrayElement" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs
        type FieldOffset "dstArrayElement" VkCopyDescriptorSet =
             (44)
{-# LINE 307 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}
        type FieldIsArray "dstArrayElement" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
44)
{-# LINE 315 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "dstArrayElement" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet
-> FieldType "dstArrayElement" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
44))
{-# LINE 322 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "dstArrayElement" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
44)
{-# LINE 326 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "dstArrayElement" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "dstArrayElement" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
44)
{-# LINE 332 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "descriptorCount" VkCopyDescriptorSet where
        type FieldType "descriptorCount" VkCopyDescriptorSet = Word32
        type FieldOptional "descriptorCount" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs
        type FieldOffset "descriptorCount" VkCopyDescriptorSet =
             (48)
{-# LINE 339 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}
        type FieldIsArray "descriptorCount" VkCopyDescriptorSet = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
48)
{-# LINE 347 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "descriptorCount" VkCopyDescriptorSet where
        {-# NOINLINE getField #-}
        getField :: VkCopyDescriptorSet
-> FieldType "descriptorCount" VkCopyDescriptorSet
getField VkCopyDescriptorSet
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCopyDescriptorSet -> Ptr VkCopyDescriptorSet
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCopyDescriptorSet
x) (Int
48))
{-# LINE 354 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkCopyDescriptorSet
-> IO (FieldType "descriptorCount" VkCopyDescriptorSet)
readField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCopyDescriptorSet
p (Int
48)
{-# LINE 358 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "descriptorCount" VkCopyDescriptorSet where
        {-# INLINE writeField #-}
        writeField :: Ptr VkCopyDescriptorSet
-> FieldType "descriptorCount" VkCopyDescriptorSet -> IO ()
writeField Ptr VkCopyDescriptorSet
p
          = Ptr VkCopyDescriptorSet -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCopyDescriptorSet
p (Int
48)
{-# LINE 364 "src-gen/Graphics/Vulkan/Types/Struct/CopyDescriptorSet.hsc" #-}

instance Show VkCopyDescriptorSet where
        showsPrec :: Int -> VkCopyDescriptorSet -> ShowS
showsPrec Int
d VkCopyDescriptorSet
x
          = String -> ShowS
showString String
"VkCopyDescriptorSet {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"sType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkStructureType -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCopyDescriptorSet -> FieldType "sType" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkCopyDescriptorSet
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    String -> ShowS
showString String
"pNext = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> Ptr Void -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCopyDescriptorSet -> FieldType "pNext" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkCopyDescriptorSet
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                        String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                          String -> ShowS
showString String
"srcSet = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkDescriptorSet -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCopyDescriptorSet -> FieldType "srcSet" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"srcSet" VkCopyDescriptorSet
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                              String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                String -> ShowS
showString String
"srcBinding = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                  Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCopyDescriptorSet -> FieldType "srcBinding" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"srcBinding" VkCopyDescriptorSet
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                    String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                      String -> ShowS
showString String
"srcArrayElement = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                        Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCopyDescriptorSet
-> FieldType "srcArrayElement" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"srcArrayElement" VkCopyDescriptorSet
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                          String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                            String -> ShowS
showString String
"dstSet = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                              Int -> VkDescriptorSet -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCopyDescriptorSet -> FieldType "dstSet" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"dstSet" VkCopyDescriptorSet
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                  String -> ShowS
showString String
"dstBinding = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                    Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCopyDescriptorSet -> FieldType "dstBinding" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"dstBinding" VkCopyDescriptorSet
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                      String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                        String -> ShowS
showString String
"dstArrayElement = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                          Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
                                                            (VkCopyDescriptorSet
-> FieldType "dstArrayElement" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"dstArrayElement" VkCopyDescriptorSet
x)
                                                            ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                            String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                              String -> ShowS
showString String
"descriptorCount = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                                Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
                                                                  (VkCopyDescriptorSet
-> FieldType "descriptorCount" VkCopyDescriptorSet
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"descriptorCount" VkCopyDescriptorSet
x)
                                                                  ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'