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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.VertexInput
       (VkVertexInputAttributeDescription(..),
        VkVertexInputBindingDescription(..),
        VkVertexInputBindingDivisorDescriptionEXT(..))
       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.Format          (VkFormat)
import           Graphics.Vulkan.Types.Enum.VertexInputRate (VkVertexInputRate)
import           System.IO.Unsafe                           (unsafeDupablePerformIO)

-- | > typedef struct VkVertexInputAttributeDescription {
--   >     uint32_t               location;
--   >     uint32_t               binding;
--   >     VkFormat               format;
--   >     uint32_t               offset;
--   > } VkVertexInputAttributeDescription;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkVertexInputAttributeDescription VkVertexInputAttributeDescription registry at www.khronos.org>
data VkVertexInputAttributeDescription = VkVertexInputAttributeDescription# Addr#
                                                                            ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkVertexInputAttributeDescription where
        sizeOf :: VkVertexInputAttributeDescription -> Int
sizeOf ~VkVertexInputAttributeDescription
_ = (Int
16)
{-# LINE 52 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkVertexInputAttributeDescription -> Int
alignment ~VkVertexInputAttributeDescription
_
          = Int
4
{-# LINE 56 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkVertexInputAttributeDescription where
        type StructFields VkVertexInputAttributeDescription =
             '["location", "binding", "format", "offset"] -- ' closing tick for hsc2hs
        type CUnionType VkVertexInputAttributeDescription = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkVertexInputAttributeDescription = 'False -- ' closing tick for hsc2hs
        type StructExtends VkVertexInputAttributeDescription = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "location" VkVertexInputAttributeDescription where
        type FieldType "location" VkVertexInputAttributeDescription =
             Word32
        type FieldOptional "location" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "location" VkVertexInputAttributeDescription =
             (0)
{-# LINE 94 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "location" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputAttributeDescription
-> IO (FieldType "location" VkVertexInputAttributeDescription)
readField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputAttributeDescription
p (Int
0)
{-# LINE 114 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "location" VkVertexInputAttributeDescription where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputAttributeDescription
-> FieldType "location" VkVertexInputAttributeDescription -> IO ()
writeField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputAttributeDescription
p (Int
0)
{-# LINE 120 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "binding" VkVertexInputAttributeDescription where
        type FieldType "binding" VkVertexInputAttributeDescription = Word32
        type FieldOptional "binding" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "binding" VkVertexInputAttributeDescription =
             (4)
{-# LINE 128 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "binding" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
4)
{-# LINE 137 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputAttributeDescription
-> IO (FieldType "binding" VkVertexInputAttributeDescription)
readField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputAttributeDescription
p (Int
4)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "binding" VkVertexInputAttributeDescription where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputAttributeDescription
-> FieldType "binding" VkVertexInputAttributeDescription -> IO ()
writeField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputAttributeDescription
p (Int
4)
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "format" VkVertexInputAttributeDescription where
        type FieldType "format" VkVertexInputAttributeDescription =
             VkFormat
        type FieldOptional "format" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "format" VkVertexInputAttributeDescription =
             (8)
{-# LINE 163 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "format" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputAttributeDescription
-> IO (FieldType "format" VkVertexInputAttributeDescription)
readField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> IO VkFormat
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputAttributeDescription
p (Int
8)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "format" VkVertexInputAttributeDescription where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputAttributeDescription
-> FieldType "format" VkVertexInputAttributeDescription -> IO ()
writeField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> VkFormat -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputAttributeDescription
p (Int
8)
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "offset" VkVertexInputAttributeDescription where
        type FieldType "offset" VkVertexInputAttributeDescription = Word32
        type FieldOptional "offset" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "offset" VkVertexInputAttributeDescription =
             (12)
{-# LINE 197 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "offset" VkVertexInputAttributeDescription =
             'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
12)
{-# LINE 206 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputAttributeDescription
-> IO (FieldType "offset" VkVertexInputAttributeDescription)
readField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputAttributeDescription
p (Int
12)
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "offset" VkVertexInputAttributeDescription where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputAttributeDescription
-> FieldType "offset" VkVertexInputAttributeDescription -> IO ()
writeField Ptr VkVertexInputAttributeDescription
p
          = Ptr VkVertexInputAttributeDescription -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputAttributeDescription
p (Int
12)
{-# LINE 223 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance Show VkVertexInputAttributeDescription where
        showsPrec :: Int -> VkVertexInputAttributeDescription -> ShowS
showsPrec Int
d VkVertexInputAttributeDescription
x
          = String -> ShowS
showString String
"VkVertexInputAttributeDescription {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"location = " 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 (VkVertexInputAttributeDescription
-> FieldType "location" VkVertexInputAttributeDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"location" VkVertexInputAttributeDescription
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
"binding = " 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 (VkVertexInputAttributeDescription
-> FieldType "binding" VkVertexInputAttributeDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"binding" VkVertexInputAttributeDescription
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
"format = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkFormat -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkVertexInputAttributeDescription
-> FieldType "format" VkVertexInputAttributeDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"format" VkVertexInputAttributeDescription
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
"offset = " 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 (VkVertexInputAttributeDescription
-> FieldType "offset" VkVertexInputAttributeDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"offset" VkVertexInputAttributeDescription
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

-- | > typedef struct VkVertexInputBindingDescription {
--   >     uint32_t               binding;
--   >     uint32_t               stride;
--   >     VkVertexInputRate      inputRate;
--   > } VkVertexInputBindingDescription;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkVertexInputBindingDescription VkVertexInputBindingDescription registry at www.khronos.org>
data VkVertexInputBindingDescription = VkVertexInputBindingDescription# Addr#
                                                                        ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkVertexInputBindingDescription where
        sizeOf :: VkVertexInputBindingDescription -> Int
sizeOf ~VkVertexInputBindingDescription
_ = (Int
12)
{-# LINE 264 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkVertexInputBindingDescription -> Int
alignment ~VkVertexInputBindingDescription
_
          = Int
4
{-# LINE 268 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkVertexInputBindingDescription where
        type StructFields VkVertexInputBindingDescription =
             '["binding", "stride", "inputRate"] -- ' closing tick for hsc2hs
        type CUnionType VkVertexInputBindingDescription = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkVertexInputBindingDescription = 'False -- ' closing tick for hsc2hs
        type StructExtends VkVertexInputBindingDescription = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "binding" VkVertexInputBindingDescription where
        type FieldType "binding" VkVertexInputBindingDescription = Word32
        type FieldOptional "binding" VkVertexInputBindingDescription =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "binding" VkVertexInputBindingDescription =
             (0)
{-# LINE 305 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "binding" VkVertexInputBindingDescription =
             'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputBindingDescription
-> IO (FieldType "binding" VkVertexInputBindingDescription)
readField Ptr VkVertexInputBindingDescription
p
          = Ptr VkVertexInputBindingDescription -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputBindingDescription
p (Int
0)
{-# LINE 325 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "binding" VkVertexInputBindingDescription where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputBindingDescription
-> FieldType "binding" VkVertexInputBindingDescription -> IO ()
writeField Ptr VkVertexInputBindingDescription
p
          = Ptr VkVertexInputBindingDescription -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputBindingDescription
p (Int
0)
{-# LINE 331 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "inputRate" VkVertexInputBindingDescription where
        type FieldType "inputRate" VkVertexInputBindingDescription =
             VkVertexInputRate
        type FieldOptional "inputRate" VkVertexInputBindingDescription =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "inputRate" VkVertexInputBindingDescription =
             (8)
{-# LINE 373 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "inputRate" VkVertexInputBindingDescription =
             'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputBindingDescription
-> IO (FieldType "inputRate" VkVertexInputBindingDescription)
readField Ptr VkVertexInputBindingDescription
p
          = Ptr VkVertexInputBindingDescription -> Int -> IO VkVertexInputRate
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputBindingDescription
p (Int
8)
{-# LINE 393 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "inputRate" VkVertexInputBindingDescription where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputBindingDescription
-> FieldType "inputRate" VkVertexInputBindingDescription -> IO ()
writeField Ptr VkVertexInputBindingDescription
p
          = Ptr VkVertexInputBindingDescription
-> Int -> VkVertexInputRate -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputBindingDescription
p (Int
8)
{-# LINE 399 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance Show VkVertexInputBindingDescription where
        showsPrec :: Int -> VkVertexInputBindingDescription -> ShowS
showsPrec Int
d VkVertexInputBindingDescription
x
          = String -> ShowS
showString String
"VkVertexInputBindingDescription {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"binding = " 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 (VkVertexInputBindingDescription
-> FieldType "binding" VkVertexInputBindingDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"binding" VkVertexInputBindingDescription
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
"stride = " 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 (VkVertexInputBindingDescription
-> FieldType "stride" VkVertexInputBindingDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"stride" VkVertexInputBindingDescription
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
"inputRate = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkVertexInputRate -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkVertexInputBindingDescription
-> FieldType "inputRate" VkVertexInputBindingDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"inputRate" VkVertexInputBindingDescription
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

-- | > typedef struct VkVertexInputBindingDivisorDescriptionEXT {
--   >     uint32_t          binding;
--   >     uint32_t          divisor;
--   > } VkVertexInputBindingDivisorDescriptionEXT;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkVertexInputBindingDivisorDescriptionEXT VkVertexInputBindingDivisorDescriptionEXT registry at www.khronos.org>
data VkVertexInputBindingDivisorDescriptionEXT = VkVertexInputBindingDivisorDescriptionEXT# Addr#
                                                                                            ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkVertexInputBindingDivisorDescriptionEXT where
        sizeOf :: VkVertexInputBindingDivisorDescriptionEXT -> Int
sizeOf ~VkVertexInputBindingDivisorDescriptionEXT
_
          = (Int
8)
{-# LINE 438 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkVertexInputBindingDivisorDescriptionEXT -> Int
alignment ~VkVertexInputBindingDivisorDescriptionEXT
_
          = Int
4
{-# LINE 442 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkVertexInputBindingDivisorDescriptionEXT
         where
        type StructFields VkVertexInputBindingDivisorDescriptionEXT =
             '["binding", "divisor"] -- ' closing tick for hsc2hs
        type CUnionType VkVertexInputBindingDivisorDescriptionEXT = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkVertexInputBindingDivisorDescriptionEXT =
             'False -- ' closing tick for hsc2hs
        type StructExtends VkVertexInputBindingDivisorDescriptionEXT = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "binding" VkVertexInputBindingDivisorDescriptionEXT where
        type FieldType "binding" VkVertexInputBindingDivisorDescriptionEXT
             = Word32
        type FieldOptional "binding"
               VkVertexInputBindingDivisorDescriptionEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "binding"
               VkVertexInputBindingDivisorDescriptionEXT
             =
             (0)
{-# LINE 488 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "binding"
               VkVertexInputBindingDivisorDescriptionEXT
             = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputBindingDivisorDescriptionEXT
-> IO
     (FieldType "binding" VkVertexInputBindingDivisorDescriptionEXT)
readField Ptr VkVertexInputBindingDivisorDescriptionEXT
p
          = Ptr VkVertexInputBindingDivisorDescriptionEXT -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputBindingDivisorDescriptionEXT
p (Int
0)
{-# LINE 510 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "binding" VkVertexInputBindingDivisorDescriptionEXT
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputBindingDivisorDescriptionEXT
-> FieldType "binding" VkVertexInputBindingDivisorDescriptionEXT
-> IO ()
writeField Ptr VkVertexInputBindingDivisorDescriptionEXT
p
          = Ptr VkVertexInputBindingDivisorDescriptionEXT
-> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputBindingDivisorDescriptionEXT
p (Int
0)
{-# LINE 517 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "divisor" VkVertexInputBindingDivisorDescriptionEXT where
        type FieldType "divisor" VkVertexInputBindingDivisorDescriptionEXT
             = Word32
        type FieldOptional "divisor"
               VkVertexInputBindingDivisorDescriptionEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "divisor"
               VkVertexInputBindingDivisorDescriptionEXT
             =
             (4)
{-# LINE 529 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}
        type FieldIsArray "divisor"
               VkVertexInputBindingDivisorDescriptionEXT
             = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
4)
{-# LINE 539 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

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

        {-# INLINE readField #-}
        readField :: Ptr VkVertexInputBindingDivisorDescriptionEXT
-> IO
     (FieldType "divisor" VkVertexInputBindingDivisorDescriptionEXT)
readField Ptr VkVertexInputBindingDivisorDescriptionEXT
p
          = Ptr VkVertexInputBindingDivisorDescriptionEXT -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkVertexInputBindingDivisorDescriptionEXT
p (Int
4)
{-# LINE 551 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "divisor" VkVertexInputBindingDivisorDescriptionEXT
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkVertexInputBindingDivisorDescriptionEXT
-> FieldType "divisor" VkVertexInputBindingDivisorDescriptionEXT
-> IO ()
writeField Ptr VkVertexInputBindingDivisorDescriptionEXT
p
          = Ptr VkVertexInputBindingDivisorDescriptionEXT
-> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkVertexInputBindingDivisorDescriptionEXT
p (Int
4)
{-# LINE 558 "src-gen/Graphics/Vulkan/Types/Struct/VertexInput.hsc" #-}

instance Show VkVertexInputBindingDivisorDescriptionEXT where
        showsPrec :: Int -> VkVertexInputBindingDivisorDescriptionEXT -> ShowS
showsPrec Int
d VkVertexInputBindingDivisorDescriptionEXT
x
          = String -> ShowS
showString String
"VkVertexInputBindingDivisorDescriptionEXT {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"binding = " 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 (VkVertexInputBindingDivisorDescriptionEXT
-> FieldType "binding" VkVertexInputBindingDivisorDescriptionEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"binding" VkVertexInputBindingDivisorDescriptionEXT
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
"divisor = " 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 (VkVertexInputBindingDivisorDescriptionEXT
-> FieldType "divisor" VkVertexInputBindingDivisorDescriptionEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"divisor" VkVertexInputBindingDivisorDescriptionEXT
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'