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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.QueueFamilyProperties
       (VkQueueFamilyProperties(..), VkQueueFamilyProperties2(..),
        VkQueueFamilyProperties2KHR)
       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.Queue         (VkQueueFlags)
import           Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import           Graphics.Vulkan.Types.Struct.Extent      (VkExtent3D)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

-- | > typedef struct VkQueueFamilyProperties {
--   >     VkQueueFlags           queueFlags;
--   >     uint32_t               queueCount;
--   >     uint32_t               timestampValidBits;
--   >     VkExtent3D             minImageTransferGranularity;
--   > } VkQueueFamilyProperties;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkQueueFamilyProperties VkQueueFamilyProperties registry at www.khronos.org>
data VkQueueFamilyProperties = VkQueueFamilyProperties# Addr#
                                                        ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkQueueFamilyProperties where
        sizeOf :: VkQueueFamilyProperties -> Int
sizeOf ~VkQueueFamilyProperties
_ = (Int
24)
{-# LINE 50 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkQueueFamilyProperties where
        type StructFields VkQueueFamilyProperties =
             '["queueFlags", "queueCount", "timestampValidBits", -- ' closing tick for hsc2hs
               "minImageTransferGranularity"]
        type CUnionType VkQueueFamilyProperties = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkQueueFamilyProperties = 'True -- ' closing tick for hsc2hs
        type StructExtends VkQueueFamilyProperties = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "queueFlags" VkQueueFamilyProperties where
        type FieldType "queueFlags" VkQueueFamilyProperties = VkQueueFlags
        type FieldOptional "queueFlags" VkQueueFamilyProperties = 'True -- ' closing tick for hsc2hs
        type FieldOffset "queueFlags" VkQueueFamilyProperties =
             (0)
{-# LINE 88 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}
        type FieldIsArray "queueFlags" VkQueueFamilyProperties = 'False -- ' closing tick for hsc2hs

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "timestampValidBits" VkQueueFamilyProperties where
        type FieldType "timestampValidBits" VkQueueFamilyProperties =
             Word32
        type FieldOptional "timestampValidBits" VkQueueFamilyProperties =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "timestampValidBits" VkQueueFamilyProperties =
             (8)
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}
        type FieldIsArray "timestampValidBits" VkQueueFamilyProperties =
             'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkQueueFamilyProperties
-> IO (FieldType "timestampValidBits" VkQueueFamilyProperties)
readField Ptr VkQueueFamilyProperties
p
          = Ptr VkQueueFamilyProperties -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkQueueFamilyProperties
p (Int
8)
{-# LINE 174 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "timestampValidBits" VkQueueFamilyProperties where
        {-# INLINE writeField #-}
        writeField :: Ptr VkQueueFamilyProperties
-> FieldType "timestampValidBits" VkQueueFamilyProperties -> IO ()
writeField Ptr VkQueueFamilyProperties
p
          = Ptr VkQueueFamilyProperties -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkQueueFamilyProperties
p (Int
8)
{-# LINE 180 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "minImageTransferGranularity" VkQueueFamilyProperties
         where
        type FieldType "minImageTransferGranularity"
               VkQueueFamilyProperties
             = VkExtent3D
        type FieldOptional "minImageTransferGranularity"
               VkQueueFamilyProperties
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "minImageTransferGranularity"
               VkQueueFamilyProperties
             =
             (12)
{-# LINE 194 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}
        type FieldIsArray "minImageTransferGranularity"
               VkQueueFamilyProperties
             = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkQueueFamilyProperties
-> IO
     (FieldType "minImageTransferGranularity" VkQueueFamilyProperties)
readField Ptr VkQueueFamilyProperties
p
          = Ptr VkQueueFamilyProperties -> Int -> IO VkExtent3D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkQueueFamilyProperties
p (Int
12)
{-# LINE 216 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}

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

instance Show VkQueueFamilyProperties where
        showsPrec :: Int -> VkQueueFamilyProperties -> ShowS
showsPrec Int
d VkQueueFamilyProperties
x
          = String -> ShowS
showString String
"VkQueueFamilyProperties {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"queueFlags = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkQueueFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkQueueFamilyProperties
-> FieldType "queueFlags" VkQueueFamilyProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"queueFlags" VkQueueFamilyProperties
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
"queueCount = " 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 (VkQueueFamilyProperties
-> FieldType "queueCount" VkQueueFamilyProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"queueCount" VkQueueFamilyProperties
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
"timestampValidBits = " 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 (VkQueueFamilyProperties
-> FieldType "timestampValidBits" VkQueueFamilyProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"timestampValidBits" VkQueueFamilyProperties
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
"minImageTransferGranularity = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                  Int -> VkExtent3D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkQueueFamilyProperties
-> FieldType "minImageTransferGranularity" VkQueueFamilyProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"minImageTransferGranularity" VkQueueFamilyProperties
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                    Char -> ShowS
showChar Char
'}'

-- | > typedef struct VkQueueFamilyProperties2 {
--   >     VkStructureType sType;
--   >     void*                            pNext;
--   >     VkQueueFamilyProperties          queueFamilyProperties;
--   > } VkQueueFamilyProperties2;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkQueueFamilyProperties2 VkQueueFamilyProperties2 registry at www.khronos.org>
data VkQueueFamilyProperties2 = VkQueueFamilyProperties2# Addr#
                                                          ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkQueueFamilyProperties2 where
        type StructFields VkQueueFamilyProperties2 =
             '["sType", "pNext", "queueFamilyProperties"] -- ' closing tick for hsc2hs
        type CUnionType VkQueueFamilyProperties2 = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkQueueFamilyProperties2 = 'True -- ' closing tick for hsc2hs
        type StructExtends VkQueueFamilyProperties2 = '[] -- ' closing tick for hsc2hs

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "queueFamilyProperties" VkQueueFamilyProperties2 where
        type FieldType "queueFamilyProperties" VkQueueFamilyProperties2 =
             VkQueueFamilyProperties
        type FieldOptional "queueFamilyProperties" VkQueueFamilyProperties2
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "queueFamilyProperties" VkQueueFamilyProperties2 =
             (16)
{-# LINE 366 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}
        type FieldIsArray "queueFamilyProperties" VkQueueFamilyProperties2
             = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkQueueFamilyProperties2
-> IO (FieldType "queueFamilyProperties" VkQueueFamilyProperties2)
readField Ptr VkQueueFamilyProperties2
p
          = Ptr VkQueueFamilyProperties2 -> Int -> IO VkQueueFamilyProperties
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkQueueFamilyProperties2
p (Int
16)
{-# LINE 386 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "queueFamilyProperties" VkQueueFamilyProperties2
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkQueueFamilyProperties2
-> FieldType "queueFamilyProperties" VkQueueFamilyProperties2
-> IO ()
writeField Ptr VkQueueFamilyProperties2
p
          = Ptr VkQueueFamilyProperties2
-> Int -> VkQueueFamilyProperties -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkQueueFamilyProperties2
p (Int
16)
{-# LINE 393 "src-gen/Graphics/Vulkan/Types/Struct/QueueFamilyProperties.hsc" #-}

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

-- | Alias for `VkQueueFamilyProperties2`
type VkQueueFamilyProperties2KHR = VkQueueFamilyProperties2